Changeset 2992 for LMDZ5


Ignore:
Timestamp:
Sep 21, 2017, 11:51:25 AM (7 years ago)
Author:
oboucher
Message:

Adding p, z, and t of tropopause in output files.
Stratosphere_mask is streamlined a bit.
This includes a treatment of missing values.

Location:
LMDZ5/trunk
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/DefLists/field_def_lmdz.xml

    r2991 r2992  
    460460        <field id="dqthe2d"    long_name="Thermal dQ"    unit="(kg/m2)/s" />
    461461        <field id="dqajs2d"    long_name="Dry ajdust dQ"    unit="(kg/m2)/s" />
     462        <field id="tatp"    long_name="Dry ajdust dQ"    unit="(kg/m2)/s" />
     463        <field id="p_tropopause"  long_name="Tropopause pressure" unit="Pa"   detect_missing_value=".true."  />
     464        <field id="z_tropopause"  long_name="Tropopause height" unit="m"      detect_missing_value=".true."  />
     465        <field id="t_tropopause"  long_name="Tropopause temperature" unit="K" detect_missing_value=".true."  />
    462466    </field_group>
    463467
     
    680684        <field id="OD1020_strat_only"  long_name="Stratospheric Aerosol Optical depth at 1020 nm "       unit="1" />
    681685        <field id="surf_PM25_sulf"     long_name="Sulfate PM2.5 concentration at the surface"            unit="ug/m3" />
    682         <field id="p_tropopause"       long_name="Tropopause pressure"                                   unit="Pa" />
    683686        <field id="budg_dep_dry_h2so4" long_name="H2SO4 dry deposition flux"                             unit="kg(S)/m2/s" />
    684687        <field id="budg_dep_wet_h2so4" long_name="H2SO4 wet deposition flux"                             unit="kg(S)/m2/s" />
  • LMDZ5/trunk/libf/phylmd/phys_local_var_mod.F90

    r2953 r2992  
    430430!$OMP THREADPRIVATE(sissnow,runoff,albsol3_lic)
    431431
     432      REAL, ALLOCATABLE, SAVE, DIMENSION(:) :: p_tropopause, z_tropopause, t_tropopause
     433!$OMP THREADPRIVATE(p_tropopause, z_tropopause, t_tropopause)
     434
    432435#ifdef CPP_StratAer
    433436!
     
    461464      REAL, ALLOCATABLE, SAVE, DIMENSION(:) :: surf_PM25_sulf
    462465!$OMP THREADPRIVATE(surf_PM25_sulf)
    463       REAL, ALLOCATABLE, SAVE, DIMENSION(:) :: p_tropopause
    464 !$OMP THREADPRIVATE(p_tropopause)
    465466      REAL, ALLOCATABLE, SAVE, DIMENSION(:,:) :: vsed_aer
    466467!$OMP THREADPRIVATE(vsed_aer)
     
    499500!$OMP THREADPRIVATE(budg_sed_part)
    500501#endif
    501       REAL, ALLOCATABLE, SAVE, DIMENSION(:) :: pr_tropopause
    502 !$OMP THREADPRIVATE(pr_tropopause)
    503502
    504503CONTAINS
     
    749748      ALLOCATE (sissnow(klon),runoff(klon),albsol3_lic(klon))
    750749
     750      ALLOCATE (p_tropopause(klon))
     751      ALLOCATE (z_tropopause(klon))
     752      ALLOCATE (t_tropopause(klon))
     753
    751754#ifdef CPP_StratAer
    752755      ALLOCATE (R2SO4(klon,klev))
     
    782785      ALLOCATE (budg_sed_part(klon))
    783786      ALLOCATE (surf_PM25_sulf(klon))
    784       ALLOCATE (p_tropopause(klon))
    785787      ALLOCATE (vsed_aer(klon,klev))
    786788#endif
    787       ALLOCATE (pr_tropopause(klon))
    788789
    789790END SUBROUTINE phys_local_var_init
     
    10121013      DEALLOCATE (zxsnow,snowhgt,qsnow,to_ice,sissnow,runoff,albsol3_lic)
    10131014
     1015      DEALLOCATE (p_tropopause)
     1016      DEALLOCATE (z_tropopause)
     1017      DEALLOCATE (t_tropopause)
     1018
    10141019#ifdef CPP_StratAer
    10151020! variables for strat. aerosol CK
     
    10281033      DEALLOCATE (tausum_strat)
    10291034      DEALLOCATE (surf_PM25_sulf)
    1030       DEALLOCATE (p_tropopause)
    10311035      DEALLOCATE (vsed_aer)
    10321036      DEALLOCATE (budg_3D_ocs_to_so2)
     
    10491053      DEALLOCATE (budg_sed_part)
    10501054#endif
    1051       DEALLOCATE (pr_tropopause)
    10521055
    10531056END SUBROUTINE phys_local_var_end
  • LMDZ5/trunk/libf/phylmd/phys_output_ctrlout_mod.F90

    r2958 r2992  
    12251225    'lcc', 'Cloud liquid fraction at top of cloud', '1', (/ ('', i=1, 10) /))
    12261226
     1227!--tropopause pressure
     1228  TYPE(ctrl_out), SAVE :: o_p_tropopause = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 1/), &
     1229    'p_tropopause', 'Tropopause pressure', 'Pa', (/ ('', i=1, 10) /))
     1230!--tropopause height
     1231  TYPE(ctrl_out), SAVE :: o_z_tropopause = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 1/), &
     1232    'z_tropopause', 'Tropopause height', 'm', (/ ('', i=1, 10) /))
     1233!--tropopause temperature
     1234  TYPE(ctrl_out), SAVE :: o_t_tropopause = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 1/), &
     1235    't_tropopause', 'Tropopause temperature', 'K', (/ ('', i=1, 10) /))
     1236
    12271237#ifdef CPP_StratAer
    12281238!--extinction coefficient
     
    12851295  TYPE(ctrl_out), SAVE :: o_budg_sed_part = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 1/), &
    12861296    'budg_sed_part', 'Ground sedimentation flux of strat. particles', 'kg(S)/m2/s', (/ ('', i=1, 10) /))
    1287 !--tropopause height
    1288   TYPE(ctrl_out), SAVE :: o_p_tropopause = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 1/), &
    1289     'p_tropopause', 'Tropopause pressure', 'Pa', (/ ('', i=1, 10) /))
    12901297!--surface PM25 due to strat aerosol
    12911298  TYPE(ctrl_out), SAVE :: o_surf_PM25_sulf = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 1/), &
  • LMDZ5/trunk/libf/phylmd/phys_output_write_mod.F90

    r2989 r2992  
    184184         o_map_emis_Anv, o_map_pcld_Anv, o_map_tcld_Anv, &
    185185         o_map_ntot, o_map_hc,o_map_hist,o_map_Cb,o_map_ThCi,o_map_Anv, &
    186          o_alt_tropo
     186         o_alt_tropo, &
     187! Tropopause
     188         o_p_tropopause, o_z_tropopause, o_t_tropopause
    187189
    188190#ifdef CPP_StratAer
     
    196198         o_budg_ocs_to_so2, o_budg_so2_to_h2so4, o_budg_h2so4_to_part, &
    197199         o_surf_PM25_sulf, o_ext_strat_550, o_tau_strat_550, &
    198          o_p_tropopause, o_vsed_aer, o_tau_strat_1020, o_ext_strat_1020, o_f_r_wet
     200         o_vsed_aer, o_tau_strat_1020, o_ext_strat_1020, o_f_r_wet
    199201#endif
    200202
     
    287289         east_gwstress, west_gwstress, &
    288290         d_q_ch4, pmfd, pmfu, ref_liq, ref_ice, rhwriteSTD, &
    289          ep, epmax_diag ! epmax_cape
     291         ep, epmax_diag, &  ! epmax_cape
     292         p_tropopause, t_tropopause, z_tropopause
    290293
    291294#ifdef CPP_StratAer
     
    298301         budg_emi_ocs, budg_emi_so2, budg_emi_h2so4, budg_emi_part, &
    299302         budg_ocs_to_so2, budg_so2_to_h2so4, budg_h2so4_to_part, &
    300          surf_PM25_sulf, tau_strat_550, p_tropopause, tausum_strat, &
     303         surf_PM25_sulf, tau_strat_550, tausum_strat, &
    301304         vsed_aer, tau_strat_1020, f_r_wet
    302305#endif
     
    12201223          ENDIF
    12211224       ENDIF
     1225
     1226       CALL histwrite_phy(o_p_tropopause, p_tropopause)
     1227       CALL histwrite_phy(o_t_tropopause, t_tropopause)
     1228       CALL histwrite_phy(o_z_tropopause, z_tropopause)
     1229
    12221230#ifdef CPP_StratAer
    12231231       IF (type_trac=='coag') THEN
     
    12441252          CALL histwrite_phy(o_budg_sed_part,        budg_sed_part)
    12451253          CALL histwrite_phy(o_surf_PM25_sulf, surf_PM25_sulf)
    1246           CALL histwrite_phy(o_p_tropopause, p_tropopause)
    12471254          CALL histwrite_phy(o_vsed_aer, vsed_aer)
    12481255          CALL histwrite_phy(o_f_r_wet, f_r_wet)
  • LMDZ5/trunk/libf/phylmd/physiq_mod.F90

    r2989 r2992  
    34963496             CALL readaerosolstrato1_rrtm(debut)
    34973497            ELSEIF (flag_aerosol_strat.EQ.2) THEN
    3498              CALL stratosphere_mask(t_seri, pplay, latitude_deg)
     3498             CALL stratosphere_mask(missing_val, t_seri, pplay, latitude_deg)
    34993499             CALL readaerosolstrato2_rrtm(debut)
    35003500            ELSE
     
    35143514#ifdef CPP_StratAer
    35153515       !--compute stratospheric mask
    3516        CALL stratosphere_mask(t_seri, pplay, latitude_deg)
     3516       CALL stratosphere_mask(missing_val, t_seri, pplay, latitude_deg)
    35173517       !--interactive strat aerosols
    35183518       CALL calcaerosolstrato_rrtm(pplay,t_seri,paprs,debut)
  • LMDZ5/trunk/libf/phylmd/stratosphere_mask.F90

    r2773 r2992  
    22! $Id$
    33!
    4 SUBROUTINE stratosphere_mask(t_seri, pplay, xlat)
     4SUBROUTINE stratosphere_mask(missing_val, t_seri, pplay, xlat)
    55
    66!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    2222!       gamma           tropopause criterion, e.g. -0.002 K/m
    2323!
    24 ! output:   tp(nlon, nlat)      tropopause pressure in Pa, -999. if undefined
    25 !           ttp(nlon, nlat)     tropopause temperature in K, -999. if undefined
    26 !           ztp(nlon, nlat)     tropopause height in m, -999. if undefined
    27 !       tperr           # of undetermined values
     24! output:   p_tropopause(klon)     tropopause pressure in Pa with missing values
     25!           t_tropopause(klon)     tropopause temperature in K with missing values
     26!           z_tropopause(klon)     tropopause height in m with missing values
     27!           stratomask             stratospheric mask withtout missing values
     28!           ifil                  # of undetermined values
    2829!
    2930!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    3132USE dimphy
    3233USE phys_local_var_mod, ONLY: stratomask
    33 #ifdef CPP_StratAer
    34 USE phys_local_var_mod, ONLY: p_tropopause
    35 #endif
     34USE phys_local_var_mod, ONLY: p_tropopause, z_tropopause, t_tropopause
    3635USE print_control_mod, ONLY: lunout, prt_level
    3736
    3837IMPLICIT NONE
    3938
     39REAL, INTENT(IN)                       :: missing_val ! missing value, also XIOS
    4040REAL,DIMENSION(klon,klev),INTENT(IN)   :: t_seri  ! Temperature
    4141REAL,DIMENSION(klon,klev),INTENT(IN)   :: pplay   ! pression pour le mileu de chaque couche (en Pa)
     
    4646REAL, PARAMETER                        :: gamma=-0.002
    4747LOGICAL, PARAMETER                     :: dofill=.true.
    48 REAL,DIMENSION(klon)                   :: tp, ttp, ztp
     48REAL,DIMENSION(klon)                   :: tp
    4949REAL,DIMENSION(klev)                   :: t, p
    50 INTEGER                                :: tperr, i, k, invert, ifil
     50INTEGER                                :: i, k, ifil
    5151REAL                                   :: ptrp, ttrp, ztrp, psrf, zsrf, pi
    5252
    5353pi     = 4.*ATAN(1.)
    5454
    55 tperr = 0
     55!--computing tropopause
    5656DO i=1,klon
    5757  DO k=1,klev
     
    6161  psrf=pplay(i,1)
    6262  zsrf=0.0
    63   call twmo(klev, t, p, psrf, zsrf, plimu, pliml, gamma, ptrp, ttrp, ztrp)
     63  call twmo(missing_val, klev, t, p, psrf, zsrf, plimu, pliml, gamma, ptrp, ttrp, ztrp)
    6464  tp(i)=ptrp
    65   ttp(i)=ttrp
    66   ztp(i)=ztrp
    67   IF (ptrp.lt.0.0) THEN
    68     tperr = tperr+1
    69   ENDIF
     65  p_tropopause(i)=ptrp
     66  z_tropopause(i)=ztrp
     67  t_tropopause(i)=ttrp
    7068ENDDO
    7169
    72 ! fill holes
     70!--filling holes in tp but not in p_tropopause
    7371IF (dofill) THEN
    7472  ifil=0
    7573  DO i=1,klon
    76   IF (tp(i).lt.-990.) THEN
     74  IF (ABS(tp(i)/missing_val-1.0).LT.0.01) THEN
    7775    !set missing values to very simple profile (neighbour averaging too expensive in LMDZ)
    7876    tp(i)=50000.-20000.*cos(xlat(i)/360.*2.*pi)
     
    8179  ENDDO
    8280!
    83   IF (ifil.ne.tperr) THEN
    84     CALL abort_physic('stratosphere_mask', 'inconsistency',1)
    85   ENDIF
    8681ENDIF
    8782!
     
    9691ENDDO
    9792
    98 !--this is only diagnosedd in the case of StratAer
    99 !--but it could be useful to LMDz
    100 #ifdef CPP_StratAer
    101 p_tropopause(:)=tp(:)
    102 #endif
    103 
    104 IF (ifil.gt.0 .and. prt_level >5) THEN
     93IF (ifil.GT.0 .AND. prt_level >5) THEN
    10594  write(lunout,*)'Tropopause: number of undetermined values =', ifil
    10695ENDIF
     
    113102!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    114103
    115 subroutine twmo(level, t, p, ps, zs, plimu, pliml, gamma, ptrp, ttrp, ztrp)
     104subroutine twmo(missing_val, level, t, p, ps, zs, plimu, pliml, gamma, ptrp, ttrp, ztrp)
    116105
    117106implicit none
     
    120109
    121110integer,intent(in)              :: level
     111real,intent(in)                 :: missing_val
    122112real,intent(in),dimension(level):: t, p
    123113real,intent(in)                 :: plimu, pliml, gamma, ps, zs
     
    134124integer  :: icount, jj, j
    135125
    136 ptrp=-999.0             
    137 ttrp=-999.0                 
    138 ztrp=-999.0                 
     126ptrp=missing_val
     127ttrp=missing_val
     128ztrp=missing_val
    139129
    140130faktor = -RG/R
  • LMDZ5/trunk/libf/phylmd/tropopause_m.F90

    r2971 r2992  
    11MODULE tropopause_m
    22
    3 !  USE phys_local_var_mod, ONLY: ptrop => pr_tropopause
    43  IMPLICIT NONE
    54  PRIVATE
Note: See TracChangeset for help on using the changeset viewer.