Changeset 2213 in lmdz_wrf


Ignore:
Timestamp:
Nov 5, 2018, 3:57:05 PM (6 years ago)
Author:
lfita
Message:

Improving/Enhancing? the range_faces

Location:
trunk/tools
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • trunk/tools/diag_tools.py

    r2212 r2213  
    13701370    return var1, var2, vardims, varvdims
    13711371
    1372 def Forcompute_range_faces(lon, lat, hgt, face, Nfilt, dimns, dimvns):
     1372def Forcompute_range_faces(lon, lat, hgt, face, Nfilt, newrng, dimns, dimvns):
    13731373    """ Function to compute faces [uphill, valley, downhill] of sections of a mountain
    13741374      rage, along a given face
     
    13791379      face= which face (axis along which produce slices) to use to compute the faces: WE, SN
    13801380      Nfilt= number of grid points to use to filter the topographic values
     1381      newrng= number of grid points as distance to start a new mountain range
    13811382      [dimns]= list of the name of the dimensions of [smois]
    13821383      [dimvns]= list of the name of the variables with the values of the
     
    13931394        dy = hgt.shape[0]
    13941395
    1395         dhgtt, peakst, valleyst, ofacest, ffacest =                                  \
     1396        hgtmaxt, pthgtmaxt, dhgtt, peakst, valleyst, ofacest, ffacest =              \
    13961397          fdin.module_fordiagnostics.compute_range_faces(lon=lon[:].transpose(),     \
    13971398          lat=lat[:].transpose(), hgt=hgt[:].transpose(), face=face, nfilt=Nfilt,    \
    1398           d1=dx, d2=dy)
     1399          newrange=newrng, d1=dx, d2=dy)
     1400        hgtmax = hgtmaxt.transpose()
     1401        pthgtmax = pthgtmaxt.transpose()
    13991402        dhgt = dhgtt.transpose()
    14001403        peaks = peakst.transpose()
     
    14081411        quit(-1)
    14091412
    1410     return dhgt, peaks, valleys, origfaces, filtfaces, vardims, varvdims
     1413    return hgtmax, pthgtmax, dhgt, peaks, valleys, origfaces, filtfaces, vardims,    \
     1414      varvdims
    14111415
    14121416####### ###### ##### #### ### ## # END Fortran diagnostics
  • trunk/tools/diagnostics.py

    r2212 r2213  
    681681        ncvar.insert_variable(ncobj, 'hurs', diagout, diagoutd, diagoutvd, newnc)
    682682
    683 # range_faces: LON, LAT, HGT, 'face:['WE'/'SN']:[Nptfilt]'
     683# range_faces: LON, LAT, HGT, 'face:['WE'/'SN']:[Nptfilt]:[Nptnewrange]'
    684684    elif diagn == 'range_faces':
    685685           
     
    688688        var2 = ncobj.variables[depvars[2]][:]
    689689        face = depvars[3].split(':')[1]
    690         Nptfilt = depvars[3].split(':')[2]
     690        Nptfilt = int(depvars[3].split(':')[2])
     691        Nptnewrange = int(depvars[3].split(':')[3])
    691692
    692693        dnamesvar = list(ncobj.variables[depvars[0]].dimensions)
     
    702703            hgt = var2[:]
    703704
    704         dhgt, peaks, valleys, origfaces, diagout, diagoutd, diagoutvd =              \
    705           diag.Forcompute_range_faces(lon, lat, hgt, face, Nptfilt, dnamesvar,       \
    706           dvnamesvar)
    707 
    708         # Removing the nonChecking variable-dimensions from the initial list
    709         varsadd = []
    710         diagoutvd = list(dvnames)
    711         for nonvd in NONchkvardims:
    712             if gen.searchInlist(dvnames,nonvd): diagoutvd.remove(nonvd)
    713             varsadd.append(nonvd)
     705        orogmax, ptorogmax, dhgt, peaks, valleys, origfaces, diagout, diagoutd,      \
     706          diagoutvd = diag.Forcompute_range_faces(lon, lat, hgt, face, Nptfilt,      \
     707          Nptnewrange, dnamesvar, dvnamesvar)
     708
     709        # Removing the nonChecking variable-dimensions from the initial list
     710        varsadd = []
     711        diagoutvd = list(dvnames)
     712        for nonvd in NONchkvardims:
     713            if gen.searchInlist(dvnames,nonvd): diagoutvd.remove(nonvd)
     714            varsadd.append(nonvd)
     715
     716        # adding variables to output file
     717        if face == 'WE': axis = 'lon'
     718        elif face == 'SN': axis = 'lat'
     719
     720        ncvar.insert_variable(ncobj, 'orogmax', orogmax, diagoutd, diagoutvd,        \
     721          newnc)
     722        ovar = newnc.variables['orogmax']
     723        ncvar.set_attribute(ovar, 'deriv', axis)
     724
     725        ncvar.insert_variable(ncobj, 'ptorogmax', ptorogmax, diagoutd, diagoutvd,    \
     726          newnc)
     727        ovar = newnc.variables['ptorogmax']
     728        ncvar.set_attribute(ovar, 'deriv', axis)
    714729
    715730        ncvar.insert_variable(ncobj, 'hgtderivdeg', dhgt, diagoutd, diagoutvd,       \
    716731          newnc)
    717732        ovar = newnc.variables['orogderivdeg']
    718         if face == 'WE': axis = 'lon'
    719         elif face == 'SN': axis = 'lat'
    720733        ncvar.set_attribute(ovar, 'deriv', axis)
    721734
  • trunk/tools/module_ForDiagnostics.f90

    r2212 r2213  
    949949  END SUBROUTINE compute_fog_FRAML50
    950950
    951   SUBROUTINE compute_range_faces(d1, d2, lon, lat, hgt, face, Nfilt, derivhgt, peaks, valleys,        &
    952     origfaces, filtfaces)
     951  SUBROUTINE compute_range_faces(d1, d2, lon, lat, hgt, face, Nfilt, newrange, hgtmax, pthgtmax,      &
     952    derivhgt, peaks, valleys, origfaces, filtfaces)
    953953! Subroutine to compute faces [uphill, valleys, downhill] of a mountain range along a given face
    954954
    955955    IMPLICIT NONE
    956956
    957     INTEGER, INTENT(in)                                  :: d1, d2, Nfilt
     957    INTEGER, INTENT(in)                                  :: d1, d2, Nfilt, newrange
    958958    REAL(r_k), DIMENSION(d1,d2), INTENT(in)              :: lon, lat, hgt
    959959    CHARACTER(len=*)                                     :: face
    960     REAL(r_k), DIMENSION(d1,d2), INTENT(out)             :: derivhgt
    961     INTEGER, DIMENSION(d1,d2), INTENT(out)               :: origfaces, filtfaces, peaks, valleys
     960    REAL(r_k), DIMENSION(d1,d2), INTENT(out)             :: derivhgt, hgtmax
     961    INTEGER, DIMENSION(d1,d2), INTENT(out)               :: pthgtmax, origfaces, filtfaces, peaks,    &
     962      valleys
    962963 
    963964! Local
    964965    INTEGER                                              :: i, j
    965     INTEGER                                              :: Npeaks, Nvalleys
     966    INTEGER                                              :: pthgtmax1, Npeaks, Nvalleys
     967    REAL(r_k)                                            :: hgtmax1
    966968    INTEGER, DIMENSION(d1)                               :: ipeaks1, ivalleys1
    967969    INTEGER, DIMENSION(d2)                               :: ipeaks2, ivalleys2
     
    973975! face: which face (axis along which produce slices) to use to compute the faces: WE, SN
    974976! Nfilt: number of grid points to use to filter the topographic values
     977! newrange: number of grid points as distance to start a new mountain range
     978! hgtmax: maximum height of the face [m]
     979! pthgtmax: grid point of the maximum height [1]
    975980! derivhgt: topograpic derivative along axis [m deg-1]
    976981! peaks: peak point
     
    983988    peaks = 0
    984989    valleys = 0
     990    pthgtmax = 0
    985991    IF (TRIM(face) == 'WE') THEN
    986992      DO j=1, d2
    987         PRINT *,'Lluis:',j
    988         CALL var_range_faces(d1, lon(:,j), lat(:,j), hgt(:,j), Nfilt, derivhgt(:,j), Npeaks,          &
    989           ipeaks1, Nvalleys, ivalleys1, origfaces(:,j), filtfaces(:,j))
     993        CALL var_range_faces(d1, lon(:,j), lat(:,j), hgt(:,j), Nfilt, newrange, hgtmax1, pthgtmax1,   &
     994          derivhgt(:,j), Npeaks, ipeaks1, Nvalleys, ivalleys1, origfaces(:,j), filtfaces(:,j))
     995        hgtmax(:,j) = hgtmax1
     996        pthgtmax(pthgtmax1,j) = 1
    990997        DO i=1, Npeaks
    991998          peaks(ipeaks1(i),j) = 1
     
    9971004    ELSE IF (TRIM(face) == 'SN') THEN
    9981005      DO i=1, d1
    999         CALL var_range_faces(d2, lon(i,:), lat(i,:), hgt(i,:), Nfilt, derivhgt(i,:), Npeaks,          &
    1000           ipeaks2, Nvalleys, ivalleys2, origfaces(i,:), filtfaces(i,:))
     1006        CALL var_range_faces(d2, lon(i,:), lat(i,:), hgt(i,:), Nfilt, newrange, hgtmax1, pthgtmax1,   &
     1007          derivhgt(i,:), Npeaks, ipeaks2, Nvalleys, ivalleys2, origfaces(i,:), filtfaces(i,:))
     1008        hgtmax(i,:) = hgtmax1
     1009        pthgtmax(i,pthgtmax1) = 1
    10011010        DO j=1, Npeaks
    10021011          peaks(i,ipeaks2(j)) = 1
  • trunk/tools/module_ForDiagnosticsVars.f90

    r2212 r2213  
    15801580  END SUBROUTINE var_fog_FRAML50
    15811581
    1582   SUBROUTINE var_range_faces(d, lon, lat, hgt, filt, dhgt, Npeaks, ipeaks, Nvalleys, ivalleys,        &
    1583     faces0, faces)
     1582  SUBROUTINE var_range_faces(d, lon, lat, hgt, filt, newrange, hgtmax, ihgtmax, dhgt, Npeaks, ipeaks, &
     1583    Nvalleys, ivalleys, faces0, faces)
    15841584! Subroutine to compute faces [uphill, valleys, downhill] of a monuntain range along a face
    15851585
    15861586    IMPLICIT NONE
    15871587
    1588     INTEGER, INTENT(in)                                  :: d, filt
     1588    INTEGER, INTENT(in)                                  :: d, filt, newrange
    15891589    REAL(r_k), DIMENSION(d), INTENT(in)                  :: lon, lat, hgt
    1590     REAL(r_k), DIMENSION(d), INTENT(out)                 :: dhgt
    1591     INTEGER, DIMENSION(d), INTENT(out)                   :: ipeaks, ivalleys, faces0, faces
    1592     INTEGER, INTENT(out)                                 :: Npeaks, Nvalleys
     1590    INTEGER, INTENT(out)                                 :: ihgtmax
     1591    REAL(r_k), INTENT(out)                               :: hgtmax
     1592    REAL(r_k), DIMENSION(d), INTENT(out)                 :: dhgt, rangeshgtmax
     1593    INTEGER, DIMENSION(d), INTENT(out)                   :: ipeaks, ivalleys, faces0, faces,          &
     1594      irangeshgtmax
     1595    INTEGER, INTENT(out)                                 :: Npeaks, Nvalleys, Nranges
    15931596
    15941597! Local
    1595     INTEGER                                              :: i, j, k, l, m
    1596     INTEGER                                              :: iface
     1598    INTEGER                                              :: i, j, j1, k, l, m
     1599    INTEGER                                              :: iface, Nranges
    15971600    INTEGER                                              :: Nfaces, Nfaces1, Npeaks1, Nvalleys1
    15981601    INTEGER                                              :: fbeg, fend
    15991602    INTEGER, DIMENSION(1)                                :: ihmax
    1600     REAL(r_k)                                            :: hgtmax
    16011603    INTEGER, DIMENSION(d)                                :: ddhgt, Ndhgt
    16021604    INTEGER, DIMENSION(d)                                :: faces1, Ndhgt1, ipeaks1, ivalleys1
    1603     REAL(r_k), DIMENSION(d)                              :: peaks, valleys, peaks1, valleys1
     1605    REAL(r_k), DIMENSION(d)                              :: dLl, peaks, valleys, peaks1, valleys1
    16041606    LOGICAL                                              :: peakwithin, valleywithin
    16051607
     
    16091611! hgt: topograpical height [m]
    16101612! filt: number of grid points to use to filter the topographic values. used to define:
    1611 !   the minimum length of a given section
     1613!   the minimum length of a given section 
    16121614!   running mean filter
     1615! newrange: number of grid points as distance to start a new mountain range
    16131616
    16141617    fname = 'var_range_faces'
    16151618
    1616     PRINT *, 'heights:', hgt
     1619    !PRINT *, 'heights:', hgt
    16171620
    16181621    ! Looking for the maximum height
    16191622    hgtmax = MAXVAL(hgt)
    16201623    ihmax = MAXLOC(hgt)
    1621 
    1622     PRINT *, 'height max:', hgtmax, 'location:', ihmax
     1624    ihgtmax = ihmax(1)
     1625
     1626    !PRINT *, 'height max:', hgtmax, 'location:', ihmax
    16231627
    16241628    ! Filtering height [NOT needed]
     
    16261630
    16271631    ! range slope
     1632    dLl = SQRT((lon(2:d)-lon(1:d-1))**2+(lat(2:d)-lat(1:d-1))**2)
    16281633    dhgt(1:d) = hgt(2:d) - hgt(1:d-1)
    1629 
    1630     PRINT *, 'slope:', dhgt
     1634    dhgt = dhgt/dLl
     1635
     1636    !PRINT *, 'slope:', dhgt
    16311637
    16321638    ! Initial classification
     
    16551661    END DO
    16561662
    1657     PRINT *, 'faces:', faces0
    1658     PRINT *, Npeaks, ' peaks:', peaks(1:Npeaks), ' ipeak:', ipeaks(1:Npeaks)
    1659     PRINT *, Nvalleys, ' valleys:', valleys(1:Nvalleys), ' ivalley:', ivalleys(1:Nvalleys)
     1663    !PRINT *, 'faces:', faces0
     1664    !PRINT *, Npeaks, ' peaks:', peaks(1:Npeaks), ' ipeak:', ipeaks(1:Npeaks)
     1665    !PRINT *, Nvalleys, ' valleys:', valleys(1:Nvalleys), ' ivalley:', ivalleys(1:Nvalleys)
    16601666
    16611667    ! tendency of the slope
     
    16741680    END DO
    16751681
    1676     PRINT *, Nfaces, ' length faces:', Ndhgt(1:Nfaces)
     1682    !PRINT *, Nfaces, ' length faces:', Ndhgt(1:Nfaces)
     1683
     1684    ! Defining quantitiy of ranges within the face
     1685    Nranges = 1
     1686    IF (Npeaks > 2) THEN
     1687      DO i=1, Npeaks-1
     1688        IF (ipeaks(j+1)-ipeaks(j) < newrange)) THEN
     1689         AQUI
     1690        END IF
     1691      END DO
     1692    END IF
     1693
     1694    ! Defining valleys as that consecutive grid points below surroungind peaks from the same range
     1695    IF (Npeaks > 1) THEN
     1696      j = 1
     1697      j1 = 2
     1698      DO i=2, d
     1699        IF (i >= ipeaks(j) .AND. i < ipeaks(j+1) .AND. (ipeaks(j+1)-ipeaks(j) < newrange)) THEN
     1700          IF (hgt(i) < peaks(j) .AND. hgt(i) < peaks(j+1)) faces0(i) = 0
     1701          IF (i == ipeaks(j) .AND. hgt(i) < hgtmax) faces0(i) = 0
     1702        ELSE IF (i == ipeaks(j+1)) THEN
     1703          j = j1
     1704          j1 = j1 + 1
     1705          IF (j1 > Npeaks) EXIT
     1706        END IF
     1707      END DO
     1708    END IF
    16771709
    16781710    ! classification using filt.
     
    17381770    END IF
    17391771
    1740     PRINT *, '# lon[0] lat[1] heights[2] slope[3] faces0[4] faces1[5] faces1[6] ddhgt[7]'
    1741     DO i=1, d
    1742       PRINT *, lon(i), lat(i), hgt(i), dhgt(i), faces0(i), faces1(i), faces(i), ddhgt(i)
    1743     END DO
     1772    !PRINT *, '# lon[0] lat[1] heights[2] slope[3] faces0[4] faces1[5] faces1[6] ddhgt[7]'
     1773    !DO i=1, d
     1774    !  PRINT *, lon(i), lat(i), hgt(i), dhgt(i), faces0(i), faces1(i), faces(i), ddhgt(i)
     1775    !END DO
    17441776
    17451777    RETURN
  • trunk/tools/variables_values.dat

    r2212 r2213  
    387387slp, psl, air_pressure_at_sea_level, 85000., 104000., sea|level|pressure, Pa, Greens, $psl$, psl
    388388WRFmslp, psl, air_pressure_at_sea_level, 85000., 104000., mean|sea|level|pressure, Pa, Greens, $psl$, psl
     389ptorog, ptorog, orography_point,  0., 3000., surface|altitude|point, m, terrain, $ptorog$, ptorog
    389390qth, qth, thermal_plume_total_water_content, 0., 25., total|water|cotent|in|thermal|plume, mm, YlOrRd, $prw^{th}_{plume}$, prwth_plume
    390391q_th, qth, thermal_plume_total_water_content, 0., 25., total|water|cotent|in|thermal|plume, mm, YlOrRd, $prw^{th}_{plume}$, prwth_plume
Note: See TracChangeset for help on using the changeset viewer.