Changeset 2992
- Timestamp:
- Sep 21, 2017, 11:51:25 AM (7 years ago)
- Location:
- LMDZ5/trunk
- Files:
-
- 7 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ5/trunk/DefLists/field_def_lmdz.xml
r2991 r2992 460 460 <field id="dqthe2d" long_name="Thermal dQ" unit="(kg/m2)/s" /> 461 461 <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." /> 462 466 </field_group> 463 467 … … 680 684 <field id="OD1020_strat_only" long_name="Stratospheric Aerosol Optical depth at 1020 nm " unit="1" /> 681 685 <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" />683 686 <field id="budg_dep_dry_h2so4" long_name="H2SO4 dry deposition flux" unit="kg(S)/m2/s" /> 684 687 <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 430 430 !$OMP THREADPRIVATE(sissnow,runoff,albsol3_lic) 431 431 432 REAL, ALLOCATABLE, SAVE, DIMENSION(:) :: p_tropopause, z_tropopause, t_tropopause 433 !$OMP THREADPRIVATE(p_tropopause, z_tropopause, t_tropopause) 434 432 435 #ifdef CPP_StratAer 433 436 ! … … 461 464 REAL, ALLOCATABLE, SAVE, DIMENSION(:) :: surf_PM25_sulf 462 465 !$OMP THREADPRIVATE(surf_PM25_sulf) 463 REAL, ALLOCATABLE, SAVE, DIMENSION(:) :: p_tropopause464 !$OMP THREADPRIVATE(p_tropopause)465 466 REAL, ALLOCATABLE, SAVE, DIMENSION(:,:) :: vsed_aer 466 467 !$OMP THREADPRIVATE(vsed_aer) … … 499 500 !$OMP THREADPRIVATE(budg_sed_part) 500 501 #endif 501 REAL, ALLOCATABLE, SAVE, DIMENSION(:) :: pr_tropopause502 !$OMP THREADPRIVATE(pr_tropopause)503 502 504 503 CONTAINS … … 749 748 ALLOCATE (sissnow(klon),runoff(klon),albsol3_lic(klon)) 750 749 750 ALLOCATE (p_tropopause(klon)) 751 ALLOCATE (z_tropopause(klon)) 752 ALLOCATE (t_tropopause(klon)) 753 751 754 #ifdef CPP_StratAer 752 755 ALLOCATE (R2SO4(klon,klev)) … … 782 785 ALLOCATE (budg_sed_part(klon)) 783 786 ALLOCATE (surf_PM25_sulf(klon)) 784 ALLOCATE (p_tropopause(klon))785 787 ALLOCATE (vsed_aer(klon,klev)) 786 788 #endif 787 ALLOCATE (pr_tropopause(klon))788 789 789 790 END SUBROUTINE phys_local_var_init … … 1012 1013 DEALLOCATE (zxsnow,snowhgt,qsnow,to_ice,sissnow,runoff,albsol3_lic) 1013 1014 1015 DEALLOCATE (p_tropopause) 1016 DEALLOCATE (z_tropopause) 1017 DEALLOCATE (t_tropopause) 1018 1014 1019 #ifdef CPP_StratAer 1015 1020 ! variables for strat. aerosol CK … … 1028 1033 DEALLOCATE (tausum_strat) 1029 1034 DEALLOCATE (surf_PM25_sulf) 1030 DEALLOCATE (p_tropopause)1031 1035 DEALLOCATE (vsed_aer) 1032 1036 DEALLOCATE (budg_3D_ocs_to_so2) … … 1049 1053 DEALLOCATE (budg_sed_part) 1050 1054 #endif 1051 DEALLOCATE (pr_tropopause)1052 1055 1053 1056 END SUBROUTINE phys_local_var_end -
LMDZ5/trunk/libf/phylmd/phys_output_ctrlout_mod.F90
r2958 r2992 1225 1225 'lcc', 'Cloud liquid fraction at top of cloud', '1', (/ ('', i=1, 10) /)) 1226 1226 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 1227 1237 #ifdef CPP_StratAer 1228 1238 !--extinction coefficient … … 1285 1295 TYPE(ctrl_out), SAVE :: o_budg_sed_part = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 1/), & 1286 1296 'budg_sed_part', 'Ground sedimentation flux of strat. particles', 'kg(S)/m2/s', (/ ('', i=1, 10) /)) 1287 !--tropopause height1288 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) /))1290 1297 !--surface PM25 due to strat aerosol 1291 1298 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 184 184 o_map_emis_Anv, o_map_pcld_Anv, o_map_tcld_Anv, & 185 185 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 187 189 188 190 #ifdef CPP_StratAer … … 196 198 o_budg_ocs_to_so2, o_budg_so2_to_h2so4, o_budg_h2so4_to_part, & 197 199 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_wet200 o_vsed_aer, o_tau_strat_1020, o_ext_strat_1020, o_f_r_wet 199 201 #endif 200 202 … … 287 289 east_gwstress, west_gwstress, & 288 290 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 290 293 291 294 #ifdef CPP_StratAer … … 298 301 budg_emi_ocs, budg_emi_so2, budg_emi_h2so4, budg_emi_part, & 299 302 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, & 301 304 vsed_aer, tau_strat_1020, f_r_wet 302 305 #endif … … 1220 1223 ENDIF 1221 1224 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 1222 1230 #ifdef CPP_StratAer 1223 1231 IF (type_trac=='coag') THEN … … 1244 1252 CALL histwrite_phy(o_budg_sed_part, budg_sed_part) 1245 1253 CALL histwrite_phy(o_surf_PM25_sulf, surf_PM25_sulf) 1246 CALL histwrite_phy(o_p_tropopause, p_tropopause)1247 1254 CALL histwrite_phy(o_vsed_aer, vsed_aer) 1248 1255 CALL histwrite_phy(o_f_r_wet, f_r_wet) -
LMDZ5/trunk/libf/phylmd/physiq_mod.F90
r2989 r2992 3496 3496 CALL readaerosolstrato1_rrtm(debut) 3497 3497 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) 3499 3499 CALL readaerosolstrato2_rrtm(debut) 3500 3500 ELSE … … 3514 3514 #ifdef CPP_StratAer 3515 3515 !--compute stratospheric mask 3516 CALL stratosphere_mask( t_seri, pplay, latitude_deg)3516 CALL stratosphere_mask(missing_val, t_seri, pplay, latitude_deg) 3517 3517 !--interactive strat aerosols 3518 3518 CALL calcaerosolstrato_rrtm(pplay,t_seri,paprs,debut) -
LMDZ5/trunk/libf/phylmd/stratosphere_mask.F90
r2773 r2992 2 2 ! $Id$ 3 3 ! 4 SUBROUTINE stratosphere_mask( t_seri, pplay, xlat)4 SUBROUTINE stratosphere_mask(missing_val, t_seri, pplay, xlat) 5 5 6 6 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! … … 22 22 ! gamma tropopause criterion, e.g. -0.002 K/m 23 23 ! 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 28 29 ! 29 30 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! … … 31 32 USE dimphy 32 33 USE phys_local_var_mod, ONLY: stratomask 33 #ifdef CPP_StratAer 34 USE phys_local_var_mod, ONLY: p_tropopause 35 #endif 34 USE phys_local_var_mod, ONLY: p_tropopause, z_tropopause, t_tropopause 36 35 USE print_control_mod, ONLY: lunout, prt_level 37 36 38 37 IMPLICIT NONE 39 38 39 REAL, INTENT(IN) :: missing_val ! missing value, also XIOS 40 40 REAL,DIMENSION(klon,klev),INTENT(IN) :: t_seri ! Temperature 41 41 REAL,DIMENSION(klon,klev),INTENT(IN) :: pplay ! pression pour le mileu de chaque couche (en Pa) … … 46 46 REAL, PARAMETER :: gamma=-0.002 47 47 LOGICAL, PARAMETER :: dofill=.true. 48 REAL,DIMENSION(klon) :: tp , ttp, ztp48 REAL,DIMENSION(klon) :: tp 49 49 REAL,DIMENSION(klev) :: t, p 50 INTEGER :: tperr, i, k, invert, ifil50 INTEGER :: i, k, ifil 51 51 REAL :: ptrp, ttrp, ztrp, psrf, zsrf, pi 52 52 53 53 pi = 4.*ATAN(1.) 54 54 55 tperr = 0 55 !--computing tropopause 56 56 DO i=1,klon 57 57 DO k=1,klev … … 61 61 psrf=pplay(i,1) 62 62 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) 64 64 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 70 68 ENDDO 71 69 72 ! fill holes70 !--filling holes in tp but not in p_tropopause 73 71 IF (dofill) THEN 74 72 ifil=0 75 73 DO i=1,klon 76 IF ( tp(i).lt.-990.) THEN74 IF (ABS(tp(i)/missing_val-1.0).LT.0.01) THEN 77 75 !set missing values to very simple profile (neighbour averaging too expensive in LMDZ) 78 76 tp(i)=50000.-20000.*cos(xlat(i)/360.*2.*pi) … … 81 79 ENDDO 82 80 ! 83 IF (ifil.ne.tperr) THEN84 CALL abort_physic('stratosphere_mask', 'inconsistency',1)85 ENDIF86 81 ENDIF 87 82 ! … … 96 91 ENDDO 97 92 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 93 IF (ifil.GT.0 .AND. prt_level >5) THEN 105 94 write(lunout,*)'Tropopause: number of undetermined values =', ifil 106 95 ENDIF … … 113 102 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 114 103 115 subroutine twmo( level, t, p, ps, zs, plimu, pliml, gamma, ptrp, ttrp, ztrp)104 subroutine twmo(missing_val, level, t, p, ps, zs, plimu, pliml, gamma, ptrp, ttrp, ztrp) 116 105 117 106 implicit none … … 120 109 121 110 integer,intent(in) :: level 111 real,intent(in) :: missing_val 122 112 real,intent(in),dimension(level):: t, p 123 113 real,intent(in) :: plimu, pliml, gamma, ps, zs … … 134 124 integer :: icount, jj, j 135 125 136 ptrp= -999.0137 ttrp= -999.0138 ztrp= -999.0126 ptrp=missing_val 127 ttrp=missing_val 128 ztrp=missing_val 139 129 140 130 faktor = -RG/R -
LMDZ5/trunk/libf/phylmd/tropopause_m.F90
r2971 r2992 1 1 MODULE tropopause_m 2 2 3 ! USE phys_local_var_mod, ONLY: ptrop => pr_tropopause4 3 IMPLICIT NONE 5 4 PRIVATE
Note: See TracChangeset
for help on using the changeset viewer.