Changeset 1795 in lmdz_wrf for trunk/tools/module_ForDiagnostics.f90


Ignore:
Timestamp:
Mar 12, 2018, 3:37:19 PM (7 years ago)
Author:
lfita
Message:

Adding:

`psl_ecmwf': sea-level pressure computation following ECMWF

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/tools/module_ForDiagnostics.f90

    r1784 r1795  
    2424! compute_clt3D3: Computation of total cloudiness from a 3D CLDFRA being 3rd dimension the z-dim
    2525! compute_clt: Computation of total cloudiness
     26! compute_psl_ecmwf: Compute sea level pressure using ECMWF method following Mats Hamrud and Philippe Courtier [Pa]
    2627! compute_massvertint1D: Subroutine to vertically integrate a 1D variable in eta vertical coordinates
    2728! compute_vertint1D: Subroutine to vertically integrate a 1D variable in any vertical coordinates
     
    602603  END SUBROUTINE compute_cape_afwa4D
    603604
     605  SUBROUTINE compute_psl_ecmwf(ps, hgt, T, press, unpress, psl, d1, d2, d4)
     606! Subroutine to compute sea level pressure using ECMWF method following Mats Hamrud and Philippe Courtier [Pa]
     607
     608    IMPLICIT NONE
     609
     610    INTEGER, INTENT(in)                                  :: d1, d2, d4
     611    REAL(r_k), DIMENSION(d1,d2,d4), INTENT(in)           :: ps, T, press, unpress
     612    REAL(r_k), DIMENSION(d1,d2), INTENT(in)              :: hgt
     613    REAL(r_k), DIMENSION(d1,d2,d4), INTENT(out)          :: psl
     614 
     615! Local
     616    INTEGER                                              :: i, j, it
     617
     618!!!!!!! Variables
     619! ps: surface pressure [Pa]
     620! hgt: terrain height [m]
     621! T: temperature at first half-mass level [K]
     622! press: pressure at first full levels [Pa]
     623! unpress: pressure at first mass (half) levels [Pa]
     624! psl: sea-level pressure [Pa]
     625
     626    fname = 'compute_psl_ecmwf'
     627
     628    DO i=1, d1
     629      DO j=1, d2
     630        DO it=1, d4
     631          CALL var_psl_ecmwf(ps(i,j,it), hgt(i,j), T(i,j,it), unpress(i,j,it), press(i,j,it),         &
     632            psl(i,j,it))
     633        END DO
     634      END DO
     635    END DO
     636
     637    RETURN
     638
     639  END SUBROUTINE compute_psl_ecmwf
     640
    604641  SUBROUTINE compute_zmla_generic4D(tpot, qratio, z, hgt, zmla3D, d1, d2, d3, d4)
    605642! Subroutine to compute pbl-height following a generic method
Note: See TracChangeset for help on using the changeset viewer.