Changeset 1355 in lmdz_wrf


Ignore:
Timestamp:
Nov 25, 2016, 9:57:52 PM (8 years ago)
Author:
lfita
Message:

Fixing some issues of the `reprojection' modules
Generalizing the use of `module_generic'
Definition of errormsg' and warnmsg' in 'module_generic.F90'

Location:
trunk/tools
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/tools/interpolate.F90

    r1184 r1355  
    225225  REAL(r_k), ALLOCATABLE, DIMENSION(:,:)                 :: fractionlon, fractionlat
    226226  INTEGER                                                :: fracdx, fracdy
    227   CHARACTER(LEN=50)                                      :: fname, errormsg
     227  CHARACTER(LEN=50)                                      :: fname
    228228
    229229!!!!!!! Variables
  • trunk/tools/module_ForInterpolate.F90

    r1185 r1355  
    1010MODULE module_ForInterpolate
    1111
     12  USE module_generic
     13
    1214  CONTAINS
    1315
     
    1517  Nperx, Npery, ilonlat, mindiffLl)
    1618! Function to search a given value from a coarser version of the data
    17 
    18   USE module_generic
    1919
    2020  IMPLICIT NONE
     
    206206  iv, lonv, latv, per, Nperx, Npery, mindiff, ilonlat, mindiffLl)
    207207! Function to search a given value from a coarser version of the data
    208 
    209   USE module_generic
    210208
    211209  IMPLICIT NONE
     
    437435! Function to search a given value from a coarser version of the data
    438436
    439   USE module_generic
    440 
    441437  IMPLICIT NONE
    442438
     
    489485!   approche from percentages of the whole domain
    490486
    491   USE module_generic
    492 
    493487  IMPLICIT NONE
    494488
     
    592586! Subroutine which finds the closest grid point within a projection throughout a first guest
    593587!   and then whole domain approche from percentages of the whole domain
    594 
    595   USE module_generic
    596588
    597589  IMPLICIT NONE
     
    724716! Subroutine which provides the indices for a given interpolation of a projection
    725717
    726   USE module_generic
    727 
    728718  IMPLICIT NONE
    729719
     
    738728  INTEGER                                                :: i,j,iv, ix, iy
    739729  REAL(r_k)                                              :: mindiffLl, dist
    740   REAL(r_k)                                              :: inclon, inclat, maxdiffprojlonlat
     730  REAL(r_k)                                              :: inclon, inclat, maxdiffprojlonlat,        &
     731    maxdiffinlonlat
    741732  REAL(r_k), DIMENSION(idimx,idimy)                      :: difflonlat
     733  REAL(r_k), DIMENSION(idimx,idimy)                      :: idifflon, idifflat
    742734  REAL(r_k), DIMENSION(pdimx,pdimy)                      :: difflon, difflat
    743735  REAL(r_k), DIMENSION(2)                                :: extremelon, extremelat, ipos
     
    763755  extremelat = (/ MINVAL(projlat), MAXVAL(projlat) /)
    764756 
     757  ! Maximum distance between grid points in input projection
     758  idifflon = 0.
     759  idifflat = 0.
     760  idifflon(1:idimx-1,:) = inlonv(2:idimx,:)-inlonv(1:idimx-1,:)
     761  idifflat(:,1:idimy-1) = inlatv(:,2:idimy)-inlatv(:,1:idimy-1)
     762  maxdiffinlonlat = MAXVAL(SQRT(idifflon**2. + idifflat**2.))
    765763  ! Maximum distance between grid points in target projection
    766764  difflon = 0.
     
    770768  maxdiffprojlonlat = MAXVAL(SQRT(difflon**2. + difflat**2.))
    771769
     770  IF (maxdiffinlonlat > maxdiffprojlonlat) THEN
     771    PRINT *,TRIM(warnmsg)
     772    PRINT *,'  ' //TRIM(fname)// '; input resolution: ', maxdiffinlonlat, ' is coarser than target:', &
     773      maxdiffprojlonlat, ' !!'
     774  END IF
     775
    772776  ! Using case outside loop to be more efficient
    773777  SELECT CASE(TRIM(intkind))
     
    781785          difflonlat = SQRT((projlon(i,j)-inlonv)**2. + (projlat(i,j)-inlatv)**2.)
    782786          mindiffLl = MINVAL(difflonlat)
    783           IF (mindiffLl > maxdiffprojlonlat) THEN
     787          IF ( (mindiffLl > maxdiffprojlonlat) .AND. (mindiffLl > maxdiffinlonlat)) THEN
    784788            outLlw(3,:,i,j) = 0.
    785789            outLlw(3,:,i,j) = -1.
     
    852856          ! We do not want that values larger that the maximum distance between target grid points
    853857!          PRINT *,i,j,':',mindiffLl,'maxdiffLl:',maxdiffprojlonlat
    854           IF (mindiffLl .gt. maxdiffprojlonlat) THEN
     858          IF ((mindiffLl .gt. maxdiffprojlonlat) .AND. (mindiffLl > maxdiffinlonlat)) THEN
    855859!            PRINT *,'  ' // TRIM(fname) // ': reprojected minimum distance to nearest grid point:',   &
    856860!              mindiffLl, ' larger than the maximum distance between grid points in target projection!!'
     
    870874  idimy, pdimx, pdimy)
    871875! Subroutine to interpolate a 2D variable
    872 
    873   USE module_generic
    874876
    875877  IMPLICIT NONE
     
    949951  idimy, pdimx, pdimy, d3)
    950952! Subroutine to interpolate a 3D variable
    951 
    952   USE module_generic
    953953
    954954  IMPLICIT NONE
     
    10321032  idimy, pdimx, pdimy, d3, d4)
    10331033! Subroutine to interpolate a 4D variable
    1034 
    1035   USE module_generic
    10361034
    10371035  IMPLICIT NONE
     
    11191117  idimy, pdimx, pdimy, d3, d4, d5)
    11201118! Subroutine to interpolate a 5D variable
    1121 
    1122   USE module_generic
    11231119
    11241120  IMPLICIT NONE
     
    12111207! Subroutine which finds the closest grid point within a projection
    12121208
    1213   USE module_generic
    1214 
    12151209  IMPLICIT NONE
    12161210
     
    13091303  Ninpts)
    13101304! Subroutine which finds the closest grid point within a projection with 1D longitudes and latitudes
    1311 
    1312   USE module_generic
    13131305
    13141306  IMPLICIT NONE
  • trunk/tools/module_generic.F90

    r1313 r1355  
    88  ! Fill value at 64 bits
    99  REAL(r_k)                                              :: fillval64 = 1.e20
     10  CHARACTER(len=50), PARAMETER                           :: errormsg = 'ERROR -- error -- ERROR -- error'
     11  CHARACTER(len=50), PARAMETER                           :: warnmsg = 'WARNING -- warning -- WARNING -- warning'
    1012
    1113  CONTAINS
Note: See TracChangeset for help on using the changeset viewer.