Opened 5 years ago

Closed 5 years ago

#803 closed bug (Done)

IMPORTANT: Global and EAST longitudes are now allowed in regrid.F

Reported by: arango Owned by:
Priority: major Milestone: Release ROMS/TOMS 3.7
Component: Nonlinear Version: 3.7
Keywords: Cc:

Description

This one has been in my TODO lists for a long time. Finally, I have a global forcing data with longitudes ranging between 0-360 for an application.

  • Updated regrid.F to allow global grids and EAST longitudes. Introduced a new work variable GRID(:)%MyLon for the interpolation of data to ROMS grid, and passed as argument:
         SUBROUTINE regrid (ng, model, ncname, ncid,                       &
        &                   ncvname, ncvarid, gtype, iflag,                &
        &                   Nx, Ny, Finp, Amin, Amax,                      &
        &                   LBi, UBi, LBj, UBj,                            &
        &                   Imin, Imax, Jmin, Jmax,                        &
        &                   MyXout, Xout, Yout, Fout)
    
    
    as MyXout dummy argument. The Following code is added for processing application grid longitude. Notice that input data longitude is not modified:
    !
    !  Copy longitude coordinate Xout to MyXout. If the longitude of the
    !  data is from a global grid [0-360] or in degrees_east, convert Xout
    !  to east longitudes (MyXout) to facilitate regridding. In such case,
    !  positive multiples of 360 map to 360 and negative multiples of 360
    !  map to zero using the MODULO intrinsic Fortran function.
    !
          IF ((Xmin.ge.0.0_r8).and.(Xmax.gt.0.0_r8).and.                    &
         &    ((Xmax-Xmin).gt.315.0_r8)) THEN
            EastLon=.TRUE.
            MyLonMin=MODULO(LonMin(ng), 360.0_r8)
            IF ((MyLonMin.eq.0.0_r8).and.                                   &
         &          (LonMin(ng).gt.0.0_r8)) MyLonMin=360.0_r8
            MyLonMax=MODULO(LonMax(ng), 360.0_r8)
            IF ((MyLonMax.eq.0.0_r8).and.                                   &
         &          (LonMax(ng).gt.0.0_r8)) MyLonMax=360.0_r8
          ELSE
            EastLon=.FALSE.
            MyLonMin=LonMin(ng)
            MyLonMax=LonMax(ng)
          END IF
          IF (EastLon) THEN
            DO j=Jmin,Jmax
              DO i=Imin,Imax
                MyXout(i,j)=MODULO(Xout(i,j), 360.0_r8)   ! range [0 360]
                IF ((MyXout(i,j).eq.0.0_r8).and.                            &
         &          (Xout(i,j).gt.0.0_r8)) MyXout(i,j)=360.0_r8
              END DO
            END DO
          ELSE
            DO j=Jmin,Jmax
              DO i=Imin,Imax
                MyXout(i,j)=Xout(i,j)                     ! range [-180 180]
              END DO
            END DO
          END IF
    
    The routine nf_fread2d.F was modified to add the extra argument to the regrid call. the mod_grid.F now includes the MyLon variable in the structure.
  • The routines in check_multifile.F and inquiry.F are more robust by allowing lowercase, uppercase or a combination when searching for the time coordinste associated with a NetCDF variable
        IF ((INDEX(TRIM(lowercase(var_name(i))),'time').ne.0).and.      &
     &            (var_ndim(i).eq.1)) THEN
          TvarName=TRIM(var_name(i))
          foundit=.TRUE.
          EXIT
          ...
        END IF

Notice that we convert to lowercase to simplify the comparison in the conditional.

  • Corrected argument to load_l in read_stapar.F:
               CASE ('Sout(idTsur)')
                 Npts=load_l(Nval, Cval, MT, Ngrids, Ltracer)
                 DO ng=1,Ngrids
                   DO itrc=1,NAT
                     Sout(idTsur(itrc),ng)=Ltracer(itrc,ng)
                   END DO
                 END DO
    
    Many thanks to John Warner for reporting this issue.

Change History (1)

comment:1 by arango, 5 years ago

Resolution: Done
Status: newclosed
Note: See TracTickets for help on using tickets.