Changeset 733 in lmdz_wrf for trunk


Ignore:
Timestamp:
Apr 27, 2016, 11:28:38 AM (9 years ago)
Author:
lfita
Message:

Adding new modules on 'module_ForInterpolate':

  • Interpolate: finds the closest grid point within a projection
  • lonlatFind: Function to search a given value from a coarser version of the data
Location:
trunk/tools
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/tools/module_ForInterpolate.F90

    r730 r733  
    197197END SUBROUTINE CoarselonlatFind
    198198
     199SUBROUTINE lonlatFind(dx, dy, ilon, ilat, nxlon, nxlat, lonv, latv, ilonlat, mindiffLl)
     200! Function to search a given value from a coarser version of the data
     201
     202  USE module_generic
     203
     204  IMPLICIT NONE
     205
     206  INTEGER, PARAMETER                                     :: r_k = KIND(1.d0)
     207  INTEGER, INTENT(in)                                    :: dx, dy
     208  REAL(r_k), DIMENSION(dx,dy), INTENT(in)                :: ilon, ilat
     209  REAL(r_k), INTENT(in)                                  :: lonv, latv
     210  REAL(r_k), DIMENSION(2), INTENT(in)                    :: nxlon, nxlat
     211  INTEGER, DIMENSION(2), INTENT(out)                     :: ilonlat
     212  REAL(r_k), INTENT(out)                                 :: mindiffLl
     213! Local
     214  REAL(r_k), DIMENSION(dx,dy)                            :: difflonlat
     215  CHARACTER(LEN=50)                                      :: fname
     216 
     217! Variables
     218! ilon, ilat: original 2D matrices with the longitudes and the latitudes
     219! lonv, latv: longitude and latitude to find
     220! nxlon, nxlat: minimum and maximum longitude and latitude of the target lon,lat
     221
     222  fname = 'lonlatFind'
     223
     224  IF (lonv < nxlon(1) .OR. lonv > nxlon(2)) THEN
     225    PRINT *, TRIM(ErrWarnMsg('err'))
     226    PRINT *,'  ' // TRIM(fname) // ': longitude outside data range!!'
     227    PRINT *,'    given value:', lonv,' outside (',nxlon(1),' ,',nxlon(2),' )'
     228    STOP
     229  END IF
     230  IF (latv < nxlat(1) .OR. latv > nxlat(2)) THEN
     231    PRINT *, TRIM(ErrWarnMsg('err'))
     232    PRINT *,'  ' // TRIM(fname) // ': latitude outside data range!!'
     233    PRINT *,'    given value:', latv,' outside (',nxlat(1),' ,',nxlat(2),' )'
     234    STOP
     235  END IF
     236
     237! Find point
     238  difflonlat = SQRT((ilon-lonv)**2. + (ilat-latv)**2.)
     239  mindiffLl = MINVAL(difflonlat)
     240  ilonlat = index2DArrayR(difflonlat, dx, dy, mindiffLl)
     241
     242!  PRINT *,'mindiffLl:', mindiffLl, ' ilatlon:', ilatlon
     243!  PRINT *,'lon, lat:', lon(ilonlat(1),ilonlat(2)), ' ,', lat(ilonlat(1),ilonlat(2))
     244
     245  RETURN
     246
     247END SUBROUTINE lonlatFind
     248
    199249SUBROUTINE CoarseInterpolate(projlon, projlat, lonvs, latvs, percen, mindiff, ivar, newvar, newvarin, &
    200250  newvarinpt, newvarindiff, dimx, dimy, Ninpts)
     
    211261  INTEGER, INTENT(in)                                    :: Ninpts
    212262  REAL(r_k), DIMENSION(Ninpts), INTENT(in)               :: ivar, lonvs, latvs
    213   REAL(r_k)                                              :: mindiff, percen
     263  REAL(r_k), INTENT(in)                                  :: mindiff, percen
    214264  REAL(r_k), DIMENSION(dimx,dimy), INTENT(out)           :: newvar
    215265  INTEGER, DIMENSION(dimx,dimy), INTENT(out)             :: newvarin
     
    280330  END DO
    281331
    282   PRINT *,'  ' // TRIM(fname) // ' fractions of:'
    283   PRINT *,' lon _______ (',dfracdx,', ',dfracdy,')'
    284   DO i=1,dfracdx
    285     PRINT *,fractionlon(i,:)
    286   END DO
    287   PRINT *,' lat_______'
    288   DO i=1,dfracdx
    289     PRINT *,fractionlat(i,:)
    290   END DO
     332!  PRINT *,'  ' // TRIM(fname) // ' fractions of:'
     333!  PRINT *,' lon _______ (',dfracdx,', ',dfracdy,')'
     334!  DO i=1,dfracdx
     335!    PRINT *,fractionlon(i,:)
     336!  END DO
     337!  PRINT *,' lat_______'
     338!  DO i=1,dfracdx
     339!    PRINT *,fractionlat(i,:)
     340!  END DO
    291341
    292342  DO iv=1,Ninpts
     
    295345        fractionlat, lonvs(iv), latvs(iv), percen, dfracdx, dfracdy, ilonlat, mindiffLl)
    296346
     347      PRINT *,'  Lluis: iv',iv,', ', mindiffLl,'<= ',mindiff,' ilonlat:',ilonlat
    297348      IF (mindiffLl <= mindiff) THEN
    298349!        percendone(iv,Ninpts,0.5,'done:')
     
    329380END SUBROUTINE CoarseInterpolate
    330381
     382SUBROUTINE Interpolate(projlon, projlat, lonvs, latvs, mindiff, ivar, newvar, newvarin, newvarinpt,   &
     383  newvarindiff, dimx, dimy, Ninpts)
     384! Subroutine which finds the closest grid point within a projection
     385
     386  USE module_generic
     387
     388  IMPLICIT NONE
     389
     390  INTEGER, PARAMETER                                     :: r_k = KIND(1.d0)
     391  INTEGER, INTENT(in)                                    :: dimx, dimy
     392  REAL(r_k), DIMENSION(dimx,dimy), INTENT(in)            :: projlon, projlat
     393  INTEGER, INTENT(in)                                    :: Ninpts
     394  REAL(r_k), DIMENSION(Ninpts), INTENT(in)               :: ivar, lonvs, latvs
     395  REAL(r_k), INTENT(in)                                  :: mindiff
     396  REAL(r_k), DIMENSION(dimx,dimy), INTENT(out)           :: newvar
     397  INTEGER, DIMENSION(dimx,dimy), INTENT(out)             :: newvarin
     398  INTEGER, DIMENSION(Ninpts), INTENT(out)                :: newvarinpt
     399  REAL(r_k), DIMENSION(Ninpts), INTENT(out)              :: newvarindiff
     400
     401! Local
     402  INTEGER                                                :: iv,i,j
     403  INTEGER                                                :: ierr
     404  INTEGER, DIMENSION(2)                                  :: ilonlat
     405  REAL(r_k), DIMENSION(dimx,dimy)                        :: difflonlat
     406  REAL(r_k)                                              :: mindiffLl
     407  INTEGER                                                :: Ninpts1
     408  REAL(r_k), DIMENSION(2)                                :: extremelon, extremelat
     409  CHARACTER(LEN=50)                                      :: fname
     410
     411!!!!!!! Variables
     412! dimx, dimy: dimension length of the target interpolation
     413! proj[lon/lat]: longitudes and latitudes of the target interpolation
     414! Ninpts: number of points to interpolate
     415! [lon/lat]vs: longitudes and latitudes of the points to interpolate
     416! mindiff: minimal accepted distance to the target point
     417! ivar: values to localize in the target projection
     418! newvar: localisation of the [lon/lat]vs point in the target projection
     419! newvarin: number of point from the input data
     420! newvarinpt: integer value indicating if the value has been already located (0: no, 1: yes)
     421! newvarindiff: distance of point from the input data to the closest target point
     422! ncid: netCDF output file id
     423
     424  fname = 'Interpolate'
     425  Ninpts1 = Ninpts/100
     426
     427  extremelon = (/ MINVAL(projlon), MAXVAL(projlon) /)
     428  extremelat = (/ MINVAL(projlat), MAXVAL(projlat) /)
     429
     430  DO iv=1,Ninpts
     431    IF (newvarinpt(iv) == 0) THEN
     432! Not using the subroutine, not efficient!
     433!      CALL lonlatFind(dimx, dimy, projlon, projlat, extremelon, extremelat, lonvs(iv), latvs(iv),     &
     434!        ilonlat, mindiffLl)
     435
     436      IF (lonvs(iv) < extremelon(1) .OR. lonvs(iv) > extremelon(2)) THEN
     437        PRINT *, TRIM(ErrWarnMsg('err'))
     438        PRINT *,'  ' // TRIM(fname) // ': longitude outside data range!!'
     439        PRINT *,'    given value:', lonvs(iv),' outside (',extremelon(1),' ,',extremelon(2),' )'
     440        STOP
     441      END IF
     442      IF (latvs(iv) < extremelat(1) .OR. latvs(iv) > extremelat(2)) THEN
     443        PRINT *, TRIM(ErrWarnMsg('err'))
     444        PRINT *,'  ' // TRIM(fname) // ': latitude outside data range!!'
     445        PRINT *,'    given value:', latvs(iv),' outside (',extremelat(1),' ,',extremelat(2),' )'
     446        STOP
     447      END IF
     448
     449! Find point
     450      difflonlat = SQRT((projlon-lonvs(iv))**2. + (projlat-latvs(iv))**2.)
     451      mindiffLl = MINVAL(difflonlat)
     452      ilonlat = index2DArrayR(difflonlat, dimx, dimy, mindiffLl)
     453
     454      IF (mindiffLl <= mindiff) THEN
     455!        percendone(iv,Ninpts,0.5,'done:')
     456
     457        IF (ilonlat(1) >= 0 .AND. ilonlat(1) >= 0) THEN
     458          newvar(ilonlat(1),ilonlat(2)) = ivar(iv)
     459          newvarin(ilonlat(1),ilonlat(2)) = iv
     460          newvarinpt(iv) = 1
     461          newvarindiff(iv) = mindiffLl
     462!          PRINT *,'Lluis iv:', newvarin(ilonlat(1),ilonlat(2)), ' localized:', newvarinpt(iv),        &
     463!            ' values:', newvar(ilonlat(1),ilonlat(2)), ' invalues:', ivar(iv), ' mindist:',           &
     464!            newvarindiff(iv), ' point:',ilonlat   
     465        ELSE
     466          PRINT *,TRIM(ErrWarnMsg('err'))
     467          PRINT *,'  ' // TRIM(fname) // ': point iv:', iv, ' at', lonvs(iv), ' ,', latvs(iv),        &
     468            ' not relocated !!'
     469          PRINT *,'    mindiffl:', mindiffLl, ' ilon:', ilonlat(1), ' ilat:', ilonlat(2)
     470          STOP
     471        END IF
     472
     473!        IF (MOD(iv,Ninpts1) == 0) newnc.sync()
     474!      ELSE
     475! Because doing boxes and Goode is not conitnuos, we should jump this error message
     476!        PRINT *,TRIM(ErrWarnMsg('err'))
     477!        PRINT *,'  ' // TRIM(fname) // ': for point #', iv,' lon,lat in incomplet map:', lonvs(iv),   &
     478!          ' ,', latvs(iv), ' there is not a set of lon,lat in the completed map closer than: ',       &
     479!          mindiff, ' !!'
     480!        PRINT *,'    found minimum difference:', mindiffLl
     481!        STOP
     482      END IF
     483    END IF
     484  END DO
     485
     486END SUBROUTINE Interpolate
     487
    331488END MODULE module_ForInterpolate
  • trunk/tools/nc_var_tools.py

    r732 r733  
    1974619746            ovars = ovar[iri:ire].astype('float64')
    1974719747
     19748#            newvar,newvarin,newvarinpt[pts],newvarindiff[pts] =                      \
     19749#              fin.module_forinterpolate.coarseinterpolate(projlon, projlat,          \
     19750#              lonvss, latvss, np.float64(fracd), np.float64(mindiff), ovars)
    1974819751            newvar,newvarin,newvarinpt[pts],newvarindiff[pts] =                      \
    19749               fin.module_forinterpolate.coarseinterpolate(projlon, projlat,          \
    19750               lonvss, latvss, np.float64(fracd), np.float64(mindiff), ovars)
     19752              fin.module_forinterpolate.interpolate(projlon, projlat,                \
     19753              lonvss, latvss, np.float64(mindiff), ovars)
    1975119754            newnc.sync()
    1975219755
Note: See TracChangeset for help on using the changeset viewer.