- Timestamp:
- Dec 9, 2025, 3:08:05 PM (2 days ago)
- Location:
- LMDZ6/trunk/libf/phylmd/StratAer
- Files:
-
- 10 edited
-
aer_sedimnt.f90 (modified) (2 diffs)
-
coagulate.f90 (modified) (4 diffs)
-
interp_sulf_input.f90 (modified) (6 diffs)
-
micphy_tstep.f90 (modified) (3 diffs)
-
nucleation_tstep_mod.f90 (modified) (2 diffs)
-
ocs_to_so2.f90 (modified) (2 diffs)
-
so2_to_h2so4.f90 (modified) (3 diffs)
-
stratH2O_methox.f90 (modified) (1 diff)
-
strataer_local_var_mod.f90 (modified) (4 diffs)
-
traccoag_mod.f90 (modified) (2 diffs)
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/phylmd/StratAer/aer_sedimnt.f90
r5268 r5924 18 18 19 19 USE phys_local_var_mod, ONLY: mdw, budg_sed_part, DENSO4, DENSO4B, f_r_wet, f_r_wetB, vsed_aer 20 USE strataer_local_var_mod, ONLY: flag_ new_strat_compo20 USE strataer_local_var_mod, ONLY: flag_strat_compo 21 21 USE dimphy, ONLY : klon,klev 22 22 USE infotrac_phy … … 90 90 91 91 ! stokes-velocity with cunnigham slip- flow correction 92 IF(flag_ new_strat_compo) THEN92 IF(flag_strat_compo) THEN 93 93 ! stokes-velocity with cunnigham slip- flow correction 94 94 ZVAER(JL,JK,nb) = 2./9.*(DENSO4B(JL,JK,nb)*1000.-ZRHO)*RG/zvis(JL,JK)*(f_r_wetB(JL,JK,nb)*mdw(nb)/2.)**2.* & -
LMDZ6/trunk/libf/phylmd/StratAer/coagulate.f90
r5285 r5924 28 28 USE infotrac_phy 29 29 USE phys_local_var_mod, ONLY: DENSO4, DENSO4B, f_r_wet, f_r_wetB 30 USE strataer_local_var_mod, ONLY: flag_ new_strat_compo30 USE strataer_local_var_mod, ONLY: flag_strat_compo 31 31 32 32 IMPLICIT NONE … … 129 129 IF (is_strato(ilon,ilev)) THEN 130 130 !compute actual wet particle radius & volume for every grid box 131 IF(flag_ new_strat_compo) THEN131 IF(flag_strat_compo) THEN 132 132 DO i=1, nbtr_bin 133 133 radiuswet(i)=f_r_wetB(ilon,ilev,i)*mdw(i)/2. … … 174 174 !--pre-compute the thermal velocity of a particle thvelpar(i) from equation 20 175 175 thvelpar=0.0 176 IF(flag_ new_strat_compo) THEN176 IF(flag_strat_compo) THEN 177 177 DO i=1, nbtr_bin 178 178 m_par(i)=4./3.*RPI*radiuswet(i)**3.*DENSO4B(ilon,ilev,i)*1000. … … 275 275 ! =(Vdry(k)*tr_t(ilon,ilev,k)+pdtcoag*num_dry)/( (1.+pdtcoag*denom)*Vdry(k) ) 276 276 ! with num_dry=...beta(i,j)*Vdry(i)*.... 277 ! so in old STRATAER (.not.flag_ new_strat_compo), it was correct277 ! so in old STRATAER (.not.flag_strat_compo), it was correct 278 278 ENDIF 279 279 -
LMDZ6/trunk/libf/phylmd/StratAer/interp_sulf_input.f90
r5559 r5924 19 19 USE aerophys 20 20 USE yomcst_mod_h 21 USE strataer_local_var_mod, ONLY : flag_ newclim_file,flag_verbose_strataer21 USE strataer_local_var_mod, ONLY : flag_verbose_strataer 22 22 23 23 IMPLICIT NONE … … 125 125 126 126 !--init ncdf variables 127 IF(flag_newclim_file) THEN 128 nc_fname = "ocs_so2_h2so4_annual_lmdz.nc" 129 nc_lat = "LAT" 130 nc_lon = "LON" 131 ELSE 132 ! old file for retro compatibility 133 nc_fname = "ocs_so2_annual_lmdz.nc" 134 nc_lat = "lat" 135 nc_lon = "lon" 136 ENDIF 137 127 nc_fname = "ocs_so2_h2so4_annual_lmdz.nc" 128 nc_lat = "LAT" 129 nc_lon = "LON" 130 138 131 !--reading emission files 139 132 CALL nf95_open(nc_fname, nf90_nowrite, ncid_in) … … 180 173 IF(flag_verbose_strataer) print *,'code erreur SO2_lifetime_in=', ncerr, varid 181 174 182 IF(flag_newclim_file) THEN 183 CALL nf95_inq_varid(ncid_in, "O3", varid) 184 ncerr = nf90_get_var(ncid_in, varid, O3_clim_in) 185 IF(flag_verbose_strataer) print *,'code erreur O3=', ncerr, varid 186 187 CALL nf95_inq_varid(ncid_in, "H2SO4_LIFET", varid) 188 ncerr = nf90_get_var(ncid_in, varid, H2SO4_lifetime_in) 189 IF(flag_verbose_strataer) print *,'code erreur H2SO4_lifetime_in=', ncerr, varid 190 ENDIF 175 CALL nf95_inq_varid(ncid_in, "O3", varid) 176 ncerr = nf90_get_var(ncid_in, varid, O3_clim_in) 177 IF(flag_verbose_strataer) print *,'code erreur O3=', ncerr, varid 178 179 CALL nf95_inq_varid(ncid_in, "H2SO4_LIFET", varid) 180 ncerr = nf90_get_var(ncid_in, varid, H2SO4_lifetime_in) 181 IF(flag_verbose_strataer) print *,'code erreur H2SO4_lifetime_in=', ncerr, varid 191 182 192 183 CALL nf95_close(ncid_in) … … 215 206 216 207 ! O3 from 2d model is not tracer, in VMR 217 IF(flag_newclim_file) THEN 218 H2SO4_lifetime_mth(:,j,:) = H2SO4_lifetime_in(:,n_lat+1-j,:,mth_cur) 219 ! new input files 220 O3_clim_mth(:,j,:) = 1.e-6*O3_clim_in(:,n_lat+1-j,:,mth_cur) 221 ELSE 222 H2SO4_lifetime_mth(:,j,:) = 1.e-6 223 O3_clim_mth(:,j,:) = 1.e-6 224 ENDIF 208 H2SO4_lifetime_mth(:,j,:) = H2SO4_lifetime_in(:,n_lat+1-j,:,mth_cur) 209 ! new input files 210 O3_clim_mth(:,j,:) = 1.e-6*O3_clim_in(:,n_lat+1-j,:,mth_cur) 225 211 ENDDO 226 212 … … 279 265 MAX(0.0,MIN(paprs_glo(i,k),paprs_input(kk))-MAX(paprs_glo(i,k+1),paprs_input(kk+1))) & 280 266 *SO2_lifetime_tmp(i,kk)/(paprs_glo(i,k)-paprs_glo(i,k+1)) 281 IF(flag_newclim_file) THEN 282 H2SO4_lifetime_glo(i,k)=H2SO4_lifetime_glo(i,k)+ & 283 MAX(0.0,MIN(paprs_glo(i,k),paprs_input(kk)) & 284 -MAX(paprs_glo(i,k+1),paprs_input(kk+1))) & 285 *H2SO4_lifetime_tmp(i,kk)/(paprs_glo(i,k)-paprs_glo(i,k+1)) 286 ENDIF 267 H2SO4_lifetime_glo(i,k)=H2SO4_lifetime_glo(i,k)+ & 268 MAX(0.0,MIN(paprs_glo(i,k),paprs_input(kk)) & 269 -MAX(paprs_glo(i,k+1),paprs_input(kk+1))) & 270 *H2SO4_lifetime_tmp(i,kk)/(paprs_glo(i,k)-paprs_glo(i,k+1)) 287 271 288 272 OCS_clim_glo(i,k)=OCS_clim_glo(i,k)+ & … … 292 276 MAX(0.0,MIN(paprs_glo(i,k),paprs_input(kk))-MAX(paprs_glo(i,k+1),paprs_input(kk+1))) & 293 277 *SO2_clim_tmp(i,kk)/(paprs_glo(i,k)-paprs_glo(i,k+1)) 294 IF(flag_newclim_file) THEN 295 O3_clim_glo(i,k)=O3_clim_glo(i,k)+ & 296 MAX(0.0,MIN(paprs_glo(i,k),paprs_input(kk)) & 297 -MAX(paprs_glo(i,k+1),paprs_input(kk+1))) & 298 *O3_clim_tmp(i,kk)/(paprs_glo(i,k)-paprs_glo(i,k+1)) 299 ENDIF 278 O3_clim_glo(i,k)=O3_clim_glo(i,k)+ & 279 MAX(0.0,MIN(paprs_glo(i,k),paprs_input(kk)) & 280 -MAX(paprs_glo(i,k+1),paprs_input(kk+1))) & 281 *O3_clim_tmp(i,kk)/(paprs_glo(i,k)-paprs_glo(i,k+1)) 300 282 ENDDO 301 283 ENDDO -
LMDZ6/trunk/libf/phylmd/StratAer/micphy_tstep.f90
r5268 r5924 57 57 & 1.*(7.990811e-4 + 1.*(-7.458060e-4 + 1.*2.58139e-4 ))))) 58 58 59 IF(.not.flag_ new_strat_compo) THEN59 IF(.not.flag_strat_compo) THEN 60 60 ! STRAACT (R2SO4, t_seri -> H2SO4 activity coefficient (ACTSO4)) for cond/evap 61 61 CALL STRAACT(ACTSO4) … … 97 97 ENDIF 98 98 ! compute cond/evap rate in kg(H2SO4)/kgA/s 99 IF(flag_ new_strat_compo) THEN99 IF(flag_strat_compo) THEN 100 100 R2SO4ik(:) = R2SO4B(ilon,ilev,:) 101 101 DENSO4ik(:) = DENSO4B(ilon,ilev,:) … … 144 144 & *pplay(ilon,ilev)/t_seri(ilon,ilev)/RD/1.E6/mH2SO4mol 145 145 ! compute cond/evap rate in kg(H2SO4)/kgA/s (now only evap for pdtphys) 146 IF(flag_ new_strat_compo) THEN146 IF(flag_strat_compo) THEN 147 147 CALL condens_evapor_rate_kelvin(rhoa,t_seri(ilon,ilev),pplay(ilon,ilev), & 148 148 & R2SO4(ilon,ilev),DENSO4(ilon,ilev),f_r_wet(ilon,ilev), & -
LMDZ6/trunk/libf/phylmd/StratAer/nucleation_tstep_mod.f90
r5285 r5924 11 11 USE aerophys 12 12 USE infotrac_phy 13 USE strataer_local_var_mod, ONLY : flag_new_nucl 13 USE print_control_mod, ONLY : lunout 14 USE strataer_local_var_mod, ONLY : flag_nucl 14 15 15 16 IMPLICIT NONE … … 41 42 42 43 ! call nucleation routine 43 IF (.NOT.flag_new_nucl) THEN 44 ! Use older routine from Hanna Vehkamäki (FMI) 45 CALL binapara(t_seri,rh,rhoa,jnuc_n,x_n,ntot_n,rc_n) 46 ! when total number of molecules is too small 47 ! then set jnuc_n to collision rate of two H2SO4 molecules (following personal communication of Ulrike Niemeier and Hanna Vehkamäki) 48 IF (ntot_n < 4.0) THEN 49 VH2SO4mol=mH2SO4mol/(1.E-3*(a_xm+t_seri*(b_xm+t_seri*c_xm))) !cm3 50 jnuc_n = rhoa**2. *(3./4.*RPI)**(1./6.) *(12.*RKBOL*t_seri/mH2SO4mol)**0.5 & 51 & *100.*(2.*VH2SO4mol**(1./3.))**2. !1/(cm3s) 52 ntot_n=2.0 53 x_n=1.0 54 ENDIF 55 ELSE 56 ! Use new routine from Anni Maattanen (LATMOS) 57 csi=0.0 ! no charged nucleation for now 58 ipr=-1.0 ! dummy value to make sure charged nucleation does not occur 59 airn=0.0 ! NOT IN USE 60 ! airn=pplay/t_seri/RD/1.E3*RNAVO/RMD ! molec cm-3 (for future use, to be confirmed) 61 CALL newbinapara(t_seri,rh,rhoa,csi,airn,ipr,jnuc_n,ntot_n,jnuc_i,ntot_i, & 62 & x_n,x_i,na_n,na_i,rc_n,rc_i,n_i,kinetic_n,kinetic_i) 63 ENDIF 64 44 SELECT CASE(flag_nucl) 45 CASE(1) 46 ! Use older routine from Hanna Vehkamäki (FMI) 47 CALL binapara(t_seri,rh,rhoa,jnuc_n,x_n,ntot_n,rc_n) 48 ! when total number of molecules is too small 49 ! then set jnuc_n to collision rate of two H2SO4 molecules (following personal communication of Ulrike Niemeier and Hanna Vehkamäki) 50 IF (ntot_n < 4.0) THEN 51 VH2SO4mol=mH2SO4mol/(1.E-3*(a_xm+t_seri*(b_xm+t_seri*c_xm))) !cm3 52 jnuc_n = rhoa**2. *(3./4.*RPI)**(1./6.) *(12.*RKBOL*t_seri/mH2SO4mol)**0.5 & 53 & *100.*(2.*VH2SO4mol**(1./3.))**2. !1/(cm3s) 54 ntot_n=2.0 55 x_n=1.0 56 ENDIF 57 58 CASE(2) 59 ! Use new routine from Anni Maattanen (LATMOS) 60 csi=0.0 ! no charged nucleation for now 61 ipr=-1.0 ! dummy value to make sure charged nucleation does not occur 62 airn=0.0 ! NOT IN USE 63 ! airn=pplay/t_seri/RD/1.E3*RNAVO/RMD ! molec cm-3 (for future use, to be confirmed) 64 CALL newbinapara(t_seri,rh,rhoa,csi,airn,ipr,jnuc_n,ntot_n,jnuc_i,ntot_i, & 65 & x_n,x_i,na_n,na_i,rc_n,rc_i,n_i,kinetic_n,kinetic_i) 66 67 CASE DEFAULT 68 ! Unknown value 69 WRITE(lunout,*) 'ERROR : unknown value for nucleation method flag_nucl=',flag_nucl,' ! Only 1 or 2 are avalaible.' 70 CALL abort_physic('nucleation_tstep_mod','Wrong value for flag_nucl.',1) 71 72 END SELECT 73 65 74 ! convert jnuc_n from particles/cm3/s to kg(H2SO4)/kgA/s 66 75 nucl_rate=jnuc_n*ntot_n*x_n*mH2SO4mol/(pplay/t_seri/RD/1.E6) -
LMDZ6/trunk/libf/phylmd/StratAer/ocs_to_so2.f90
r5268 r5924 9 9 USE yomcst_mod_h, ONLY : RG 10 10 USE phys_local_var_mod, ONLY : OCS_lifetime, budg_3D_ocs_to_so2, budg_ocs_to_so2 11 USE strataer_local_var_mod, ONLY : flag_min_rreduce 12 11 13 12 IMPLICIT NONE 14 13 … … 37 36 rreduce = OCS_lifetime(ilon,ilev) 38 37 ! Check lifetime rreduce < timestep*3 (such as H2SO4 loss > 0.28*H2SO4) with exp(-1/3)=0.72 39 IF(flag_min_rreduce) THEN 40 IF (rreduce .LT. (3.*pdtphys)) rreduce = 3.*pdtphys 41 ENDIF 38 IF (rreduce .LT. (3.*pdtphys)) rreduce = 3.*pdtphys 42 39 budg_3D_ocs_to_so2(ilon,ilev)=tr_seri(ilon,ilev,id_OCS_strat)*(1.0-exp(-pdtphys/rreduce)) 43 40 tr_seri(ilon,ilev,id_OCS_strat)=tr_seri(ilon,ilev,id_OCS_strat) - budg_3D_ocs_to_so2(ilon,ilev) -
LMDZ6/trunk/libf/phylmd/StratAer/so2_to_h2so4.f90
r5605 r5924 10 10 ! lifetime (sec) et O3_clim (VMR) 11 11 USE phys_local_var_mod, ONLY : SO2_lifetime,H2SO4_lifetime,O3_clim,budg_3D_so2_to_h2so4,budg_so2_to_h2so4,SO2_chlm 12 USE strataer_local_var_mod, ONLY : flag_OH_reduced, flag_H2SO4_photolysis , flag_min_rreduce12 USE strataer_local_var_mod, ONLY : flag_OH_reduced, flag_H2SO4_photolysis 13 13 14 14 IMPLICIT NONE … … 100 100 ! Check lifetime rreduce < timestep*1.5 (such as SO2 loss > 0.5*SO2) with exp(-1/1.5)=0.52 101 101 ! Check lifetime rreduce < timestep*3 (such as SO2 loss > 0.28*SO2) with exp(-1/3)=0.72 102 IF(flag_min_rreduce) THEN 103 IF (rreduce .LT. (3.*pdtphys)) rreduce = 3.*pdtphys 104 ENDIF 102 IF (rreduce .LT. (3.*pdtphys)) rreduce = 3.*pdtphys 105 103 budg_3D_so2_to_h2so4(ilon,ilev)=tr_seri(ilon,ilev,id_SO2_strat)*(1.0-exp(-pdtphys/rreduce)) 106 104 tr_seri(ilon,ilev,id_SO2_strat)=tr_seri(ilon,ilev,id_SO2_strat) - budg_3D_so2_to_h2so4(ilon,ilev) … … 132 130 ! Check lifetime rreduce < timestep*1.5 (such as H2SO4 loss > 0.5*H2SO4) with exp(-1/1.5)=0.52 133 131 ! Check lifetime rreduce < timestep*3 (such as H2SO4 loss > 0.28*H2SO4) with exp(-1/3)=0.72 134 IF(flag_min_rreduce) THEN 135 IF (rreduce .LT. (3.*pdtphys)) rreduce = 3.*pdtphys 136 ENDIF 132 IF (rreduce .LT. (3.*pdtphys)) rreduce = 3.*pdtphys 137 133 dummyso4toso2 = (mSO2mol/mH2SO4mol)*tr_seri(ilon,ilev,id_H2SO4_strat)*(1.0-exp(-pdtphys/rreduce)) 138 134 budg_3D_so2_to_h2so4(ilon,ilev) = budg_3D_so2_to_h2so4(ilon,ilev) + dummyso4toso2 -
LMDZ6/trunk/libf/phylmd/StratAer/stratH2O_methox.f90
r5338 r5924 20 20 USE aerophys 21 21 USE yomcst_mod_h 22 USE strataer_local_var_mod, ONLY : flag_newclim_file23 22 24 23 IMPLICIT NONE -
LMDZ6/trunk/libf/phylmd/StratAer/strataer_local_var_mod.f90
r5652 r5924 14 14 !$OMP THREADPRIVATE(flag_emit_distrib) 15 15 16 ! flag to choose nucleation nucleation method 17 LOGICAL,SAVE :: flag_new_nucl ! T=new routine from A. Maattanen (LATMOS), F=older routine from H. Vehkamäki (FMI) 18 !$OMP THREADPRIVATE(flag_new_nucl) 19 20 ! Use relative humidity from 2D model stratospheric H2O because LMDz is too dry in the stratosphere 21 ! (no CH4 oxidation) 22 LOGICAL,SAVE :: flag_H2O2d_nucleation 23 !$OMP THREADPRIVATE(flag_H2O2d_nucleation) 16 ! flag to choose nucleation method 17 INTEGER,SAVE :: flag_nucl ! 1: routine from H. Vehkamäki (FMI), 2: routine from A. Maattanen (LATMOS) 18 !$OMP THREADPRIVATE(flag_nucl) 24 19 25 20 ! OH reduction from SO2. OH is reduced when its reaction with SO2 competes sufficiently with its reaction … … 33 28 !$OMP THREADPRIVATE(flag_H2SO4_photolysis) 34 29 35 ! flag for minimum lifetime (=1.5 pdt phys) 36 LOGICAL,SAVE :: flag_min_rreduce 37 !$OMP THREADPRIVATE(flag_min_rreduce) 38 39 ! flag to read new climato (O3, H2O & H2SO4_LIFET) 40 LOGICAL,SAVE :: flag_newclim_file 41 !$OMP THREADPRIVATE(flag_newclim_file) 42 43 ! flag to choose new H2SO4 density and weight percent from Tabazadeh et al. (1994). 44 LOGICAL,SAVE :: flag_new_strat_compo 45 !$OMP THREADPRIVATE(flag_new_strat_compo) 30 ! Parameterization method to compute H2SO4/H2O aerosol composition 31 INTEGER,SAVE :: flag_strat_compo ! 1: S. Bekki et al., 2: Tabazadeh et al. 1997 32 !$OMP THREADPRIVATE(flag_strat_compo) 46 33 47 34 ! Verbose mode to get more print info … … 184 171 flag_emit = 0 ! Background (default) 185 172 flag_emit_distrib = 0 ! Gaussian (default) 186 flag_n ew_nucl = .TRUE.! Define nucleation routine (default: A. Maattanen - LATMOS)173 flag_nucl = 2 ! Define nucleation routine (default: A. Maattanen - LATMOS) 187 174 flag_verbose_strataer = .FALSE. ! verbose mode 188 flag_newclim_file = .TRUE. ! Define input climato file (default: all climato)189 flag_H2O2d_nucleation = .FALSE. ! Use H2O 2D climato (default: No)190 175 flag_OH_reduced = .FALSE. ! OH reduce (default: No) 191 176 flag_H2SO4_photolysis = .FALSE. ! H2SO4 photolysis (default: No) 192 flag_min_rreduce = .TRUE. ! Minimum lifetime=1.5 pdt phys (default: Yes) 193 flag_new_strat_compo =.FALSE. ! H2SO4/H2O weight percent & density routine (default: S. Bekki) 177 flag_strat_compo = 2 ! H2SO4/H2O composition routine (default: Tabazadeh et al. 1997) 194 178 ok_qemiss = .FALSE. ! H2O emission flag 195 179 … … 219 203 CALL getin_p('flag_emit_distrib',flag_emit_distrib) 220 204 CALL getin_p('flag_verbose_strataer',flag_verbose_strataer) 221 CALL getin_p('flag_new_nucl',flag_new_nucl) 222 CALL getin_p('flag_newclim_file',flag_newclim_file) 223 CALL getin_p('flag_H2O2d_nucleation',flag_H2O2d_nucleation) 205 CALL getin_p('flag_nucl',flag_nucl) 224 206 CALL getin_p('flag_OH_reduced',flag_OH_reduced) 225 207 CALL getin_p('flag_H2SO4_photolysis',flag_H2SO4_photolysis) 226 CALL getin_p('flag_min_rreduce',flag_min_rreduce) 227 CALL getin_p('flag_new_strat_compo',flag_new_strat_compo) 208 CALL getin_p('flag_strat_compo',flag_strat_compo) 228 209 CALL getin_p('ok_qemiss',ok_qemiss) 229 230 !============= Test flag coherence =============231 IF (.NOT. flag_newclim_file) THEN232 IF (flag_H2SO4_photolysis .OR. flag_OH_reduced .OR. flag_H2O2d_nucleation) THEN233 WRITE(lunout,*) 'ERROR : flag_newclim_file=',flag_newclim_file, &234 ' whereas flag_H2SO4_photolysis=',flag_H2SO4_photolysis,', flag_OH_reduced=',flag_OH_reduced, &235 ' and flag_H2O2d_nucleation=',flag_H2O2d_nucleation236 CALL abort_physic('strataer_local_var_mod','Incompatible options in physiq_def file !',1)237 ENDIF238 IF(flag_min_rreduce) THEN239 WRITE(lunout,*) 'Warning : flag_min_rreduce will be ignored with old climato file !'240 ENDIF241 ENDIF242 210 243 211 !============= Print params ============= 244 212 IF (is_master) THEN 245 213 WRITE(lunout,*) 'flag_emit = ',flag_emit 246 WRITE(lunout,*) 'IN STRATAER : flag_new_nucl = ',flag_new_nucl 247 WRITE(lunout,*) 'IN STRATAER : flag_newclim_file = ',flag_newclim_file 214 WRITE(lunout,*) 'IN STRATAER : flag_nucl = ',flag_nucl 248 215 WRITE(lunout,*) 'IN STRATAER : flag_emit_distrib = ',flag_emit_distrib 249 216 WRITE(lunout,*) 'IN STRATAER : flag_verbose_strataer = ',flag_verbose_strataer 250 217 IF (flag_emit == 1 .OR. flag_emit == 4) THEN 251 WRITE(lunout,*) 'IN STRATAER : flag_H2O2d_nucleation = ',flag_H2O2d_nucleation252 218 WRITE(lunout,*) 'IN STRATAER : flag_OH_reduced = ',flag_OH_reduced 253 219 WRITE(lunout,*) 'IN STRATAER : flag_H2SO4_photolysis = ',flag_H2SO4_photolysis 254 WRITE(lunout,*) 'IN STRATAER : flag_min_rreduce = ',flag_min_rreduce 255 WRITE(lunout,*) 'IN STRATAER : flag_new_strat_compo = ',flag_new_strat_compo 220 WRITE(lunout,*) 'IN STRATAER : flag_strat_compo = ',flag_strat_compo 256 221 WRITE(lunout,*) 'IN STRATAER : ok_qemiss = ',ok_qemiss 257 222 ENDIF -
LMDZ6/trunk/libf/phylmd/StratAer/traccoag_mod.f90
r5367 r5924 121 121 WHERE (stratomask.GT.0.5) is_strato=.TRUE. 122 122 123 IF(flag_ new_strat_compo) THEN124 IF(debutphy) WRITE(lunout,*) 'traccoag: COMPO/DENSITY (Tabazadeh 97) + H2O kelvin effect', flag_ new_strat_compo123 IF(flag_strat_compo) THEN 124 IF(debutphy) WRITE(lunout,*) 'traccoag: COMPO/DENSITY (Tabazadeh 97) + H2O kelvin effect', flag_strat_compo 125 125 ! STRACOMP (H2O, P, t_seri, R -> R2SO4 + Kelvin effect) : Taba97, Socol, etc... 126 126 CALL stracomp_kelvin(sh,t_seri,pplay) 127 127 ELSE 128 IF(debutphy) WRITE(lunout,*) 'traccoag: COMPO from Bekki 2D model', flag_ new_strat_compo128 IF(debutphy) WRITE(lunout,*) 'traccoag: COMPO from Bekki 2D model', flag_strat_compo 129 129 ! STRACOMP (H2O, P, t_seri -> aerosol composition (R2SO4)) 130 130 ! H2SO4 mass fraction in aerosol (%) … … 383 383 & *pplay(i,j)/t_seri(i,j)/RD ! [air mass concentration in kg air /m3A] 384 384 385 IF(flag_ new_strat_compo) THEN385 IF(flag_strat_compo) THEN 386 386 ! SAD_sulfate: SAD WET sulfate aerosols (cm2/cm3) 387 387 SAD_sulfate(i,j) = SAD_sulfate(i,j) + nd_mode(i,j,it) & ! [DRY part/m3A (in bin it)]
Note: See TracChangeset
for help on using the changeset viewer.
