[3526] | 1 | ! |
---|
| 2 | ! $Id: micphy_tstep.F90 4950 2024-05-22 13:16:36Z asima $ |
---|
| 3 | ! |
---|
[2690] | 4 | SUBROUTINE micphy_tstep(pdtphys,tr_seri,t_seri,pplay,paprs,rh,is_strato) |
---|
| 5 | |
---|
[3526] | 6 | USE geometry_mod, ONLY : latitude_deg !NL- latitude corr. to local domain |
---|
[2690] | 7 | USE dimphy, ONLY : klon,klev |
---|
| 8 | USE aerophys |
---|
[4293] | 9 | USE infotrac_phy, ONLY : nbtr_bin, nbtr_sulgas, nbtr, id_H2SO4_strat |
---|
[4950] | 10 | USE phys_local_var_mod, ONLY: mdw, budg_3D_nucl, budg_3D_cond_evap, budg_h2so4_to_part, R2SO4, DENSO4, & |
---|
| 11 | f_r_wet, R2SO4B, DENSO4B, f_r_wetB |
---|
[2690] | 12 | USE nucleation_tstep_mod |
---|
| 13 | USE cond_evap_tstep_mod |
---|
| 14 | USE sulfate_aer_mod, ONLY : STRAACT |
---|
[2695] | 15 | USE YOMCST, ONLY : RPI, RD, RG |
---|
[3526] | 16 | USE print_control_mod, ONLY: lunout |
---|
[4950] | 17 | USE strataer_local_var_mod ! contains also RRSI and Vbin |
---|
[3526] | 18 | |
---|
[2690] | 19 | IMPLICIT NONE |
---|
| 20 | |
---|
| 21 | !-------------------------------------------------------- |
---|
| 22 | |
---|
| 23 | ! transfer variables when calling this routine |
---|
| 24 | REAL,INTENT(IN) :: pdtphys ! Pas d'integration pour la physique (seconde) |
---|
| 25 | REAL,DIMENSION(klon,klev,nbtr),INTENT(INOUT) :: tr_seri ! Concentration Traceur [U/KgA] |
---|
| 26 | REAL,DIMENSION(klon,klev),INTENT(IN) :: t_seri ! Temperature |
---|
| 27 | REAL,DIMENSION(klon,klev),INTENT(IN) :: pplay ! pression pour le mileu de chaque couche (en Pa) |
---|
| 28 | REAL,DIMENSION(klon,klev+1),INTENT(IN) :: paprs ! pression pour chaque inter-couche (en Pa) |
---|
| 29 | REAL,DIMENSION(klon,klev),INTENT(IN) :: rh ! humidite relative |
---|
| 30 | LOGICAL,DIMENSION(klon,klev),INTENT(IN) :: is_strato |
---|
| 31 | |
---|
| 32 | ! local variables in coagulation routine |
---|
| 33 | INTEGER, PARAMETER :: nbtstep=4 ! Max number of time steps in microphysics per time step in physics |
---|
[3098] | 34 | INTEGER :: it,ilon,ilev,count_tstep |
---|
[2690] | 35 | REAL :: rhoa !H2SO4 number density [molecules/cm3] |
---|
| 36 | REAL :: ntot !total number of molecules in the critical cluster (ntot>4) |
---|
| 37 | REAL :: x ! molefraction of H2SO4 in the critical cluster |
---|
| 38 | REAL a_xm, b_xm, c_xm |
---|
| 39 | REAL PDT, dt |
---|
| 40 | REAL H2SO4_init |
---|
| 41 | REAL ACTSO4(klon,klev) |
---|
| 42 | REAL nucl_rate |
---|
| 43 | REAL cond_evap_rate |
---|
| 44 | REAL evap_rate |
---|
| 45 | REAL FL(nbtr_bin) |
---|
| 46 | REAL ASO4(nbtr_bin) |
---|
| 47 | REAL DNDR(nbtr_bin) |
---|
[4293] | 48 | REAL H2SO4_sat |
---|
[4950] | 49 | REAL R2SO4ik(nbtr_bin), DENSO4ik(nbtr_bin), f_r_wetik(nbtr_bin) |
---|
| 50 | |
---|
[2690] | 51 | !coefficients for H2SO4 density parametrization used for nucleation if ntot<4 |
---|
| 52 | a_xm = 0.7681724 + 1.*(2.1847140 + 1.*(7.1630022 + 1.*(-44.31447 + & |
---|
| 53 | & 1.*(88.75606 + 1.*(-75.73729 + 1.*23.43228))))) |
---|
| 54 | b_xm = 1.808225e-3 + 1.*(-9.294656e-3 + 1.*(-0.03742148 + 1.*(0.2565321 + & |
---|
| 55 | & 1.*(-0.5362872 + 1.*(0.4857736 - 1.*0.1629592))))) |
---|
| 56 | c_xm = -3.478524e-6 + 1.*(1.335867e-5 + 1.*(5.195706e-5 + 1.*(-3.717636e-4 + & |
---|
| 57 | & 1.*(7.990811e-4 + 1.*(-7.458060e-4 + 1.*2.58139e-4 ))))) |
---|
| 58 | |
---|
[4950] | 59 | IF(.not.flag_new_strat_compo) THEN |
---|
| 60 | ! STRAACT (R2SO4, t_seri -> H2SO4 activity coefficient (ACTSO4)) for cond/evap |
---|
| 61 | CALL STRAACT(ACTSO4) |
---|
| 62 | ENDIF |
---|
| 63 | |
---|
[2690] | 64 | DO ilon=1, klon |
---|
[3094] | 65 | ! |
---|
| 66 | !--initialisation of diagnostic |
---|
| 67 | budg_h2so4_to_part(ilon)=0.0 |
---|
| 68 | ! |
---|
[2690] | 69 | DO ilev=1, klev |
---|
[3094] | 70 | ! |
---|
| 71 | !--initialisation of diagnostic |
---|
| 72 | budg_3D_nucl(ilon,ilev)=0.0 |
---|
| 73 | budg_3D_cond_evap(ilon,ilev)=0.0 |
---|
| 74 | ! |
---|
[2690] | 75 | ! only in the stratosphere |
---|
| 76 | IF (is_strato(ilon,ilev)) THEN |
---|
| 77 | ! initialize sulfur fluxes |
---|
| 78 | H2SO4_init=tr_seri(ilon,ilev,id_H2SO4_strat) |
---|
| 79 | ! adaptive timestep for nucleation and condensation |
---|
| 80 | PDT=pdtphys |
---|
| 81 | count_tstep=0 |
---|
[2695] | 82 | DO WHILE (PDT>0.0) |
---|
[2690] | 83 | count_tstep=count_tstep+1 |
---|
[2695] | 84 | IF (count_tstep .GT. nbtstep) EXIT |
---|
[2690] | 85 | ! convert tr_seri(GASH2SO4) (in kg/kgA) to H2SO4 number density (in molecules/cm3) |
---|
| 86 | rhoa=tr_seri(ilon,ilev,id_H2SO4_strat) & |
---|
| 87 | & *pplay(ilon,ilev)/t_seri(ilon,ilev)/RD/1.E6/mH2SO4mol |
---|
| 88 | ! compute nucleation rate in kg(H2SO4)/kgA/s |
---|
| 89 | CALL nucleation_rate(rhoa,t_seri(ilon,ilev),pplay(ilon,ilev),rh(ilon,ilev), & |
---|
[3526] | 90 | & a_xm,b_xm,c_xm,nucl_rate,ntot,x) |
---|
| 91 | !NL - add nucleation box (if flag on) |
---|
| 92 | IF (flag_nuc_rate_box) THEN |
---|
[3527] | 93 | IF (latitude_deg(ilon).LE.nuclat_min .OR. latitude_deg(ilon).GE.nuclat_max & |
---|
| 94 | .OR. pplay(ilon,ilev).GE.nucpres_max .AND. pplay(ilon,ilev).LE.nucpres_min) THEN |
---|
[3526] | 95 | nucl_rate=0.0 |
---|
| 96 | ENDIF |
---|
| 97 | ENDIF |
---|
[2690] | 98 | ! compute cond/evap rate in kg(H2SO4)/kgA/s |
---|
[4950] | 99 | IF(flag_new_strat_compo) THEN |
---|
| 100 | R2SO4ik(:) = R2SO4B(ilon,ilev,:) |
---|
| 101 | DENSO4ik(:) = DENSO4B(ilon,ilev,:) |
---|
| 102 | f_r_wetik(:) = f_r_wetB(ilon,ilev,:) |
---|
| 103 | CALL condens_evapor_rate_kelvin(rhoa,t_seri(ilon,ilev),pplay(ilon,ilev), & |
---|
| 104 | & R2SO4(ilon,ilev),DENSO4(ilon,ilev),f_r_wet(ilon,ilev), & |
---|
| 105 | & R2SO4ik,DENSO4ik,f_r_wetik,FL,ASO4,DNDR) |
---|
| 106 | ELSE |
---|
| 107 | CALL condens_evapor_rate(rhoa,t_seri(ilon,ilev),pplay(ilon,ilev), & |
---|
| 108 | & ACTSO4(ilon,ilev),R2SO4(ilon,ilev),DENSO4(ilon,ilev),f_r_wet(ilon,ilev), & |
---|
| 109 | & FL,ASO4,DNDR) |
---|
| 110 | ENDIF |
---|
[4293] | 111 | ! Compute H2SO4 saturate vapor for big particules |
---|
| 112 | H2SO4_sat = DNDR(nbtr_bin)/(pplay(ilon,ilev)/t_seri(ilon,ilev)/RD/1.E6/mH2SO4mol) |
---|
[2690] | 113 | ! consider only condensation (positive FL) |
---|
[3098] | 114 | DO it=1,nbtr_bin |
---|
| 115 | FL(it)=MAX(FL(it),0.) |
---|
[2690] | 116 | ENDDO |
---|
| 117 | ! compute total H2SO4 cond flux for all particles |
---|
| 118 | cond_evap_rate=0.0 |
---|
[3098] | 119 | DO it=1, nbtr_bin |
---|
| 120 | cond_evap_rate=cond_evap_rate+tr_seri(ilon,ilev,it+nbtr_sulgas)*FL(it)*mH2SO4mol |
---|
[2690] | 121 | ENDDO |
---|
| 122 | ! determine appropriate time step |
---|
[4293] | 123 | dt=(H2SO4_init-H2SO4_sat)/float(nbtstep)/MAX(1.e-30, nucl_rate+cond_evap_rate) !cond_evap_rate pos. for cond. and neg. for evap. |
---|
[2690] | 124 | IF (dt.LT.0.0) THEN |
---|
| 125 | dt=PDT |
---|
| 126 | ENDIF |
---|
| 127 | dt=MIN(dt,PDT) |
---|
| 128 | ! update H2SO4 concentration |
---|
| 129 | tr_seri(ilon,ilev,id_H2SO4_strat)=MAX(0.,tr_seri(ilon,ilev,id_H2SO4_strat)-(nucl_rate+cond_evap_rate)*dt) |
---|
| 130 | ! apply cond to bins |
---|
[4950] | 131 | CALL condens_evapor_part(dt,FL,ASO4,f_r_wet(ilon,ilev),tr_seri(ilon,ilev,:)) |
---|
[2690] | 132 | ! apply nucl. to bins |
---|
[4950] | 133 | CALL nucleation_part(nucl_rate,ntot,x,dt,tr_seri(ilon,ilev,:)) |
---|
[2690] | 134 | ! compute fluxes as diagnostic in [kg(S)/m2/layer/s] (now - for evap and + for cond) |
---|
[2752] | 135 | budg_3D_cond_evap(ilon,ilev)=budg_3D_cond_evap(ilon,ilev)+mSatom/mH2SO4mol & |
---|
[2690] | 136 | & *cond_evap_rate*(paprs(ilon,ilev)-paprs(ilon,ilev+1))/RG*dt/pdtphys |
---|
[2752] | 137 | budg_3D_nucl(ilon,ilev)=budg_3D_nucl(ilon,ilev)+mSatom/mH2SO4mol & |
---|
[2690] | 138 | & *nucl_rate*(paprs(ilon,ilev)-paprs(ilon,ilev+1))/RG*dt/pdtphys |
---|
| 139 | ! update time step |
---|
| 140 | PDT=PDT-dt |
---|
| 141 | ENDDO |
---|
| 142 | ! convert tr_seri(GASH2SO4) (in kg/kgA) to H2SO4 number density (in molecules/cm3) |
---|
| 143 | rhoa=tr_seri(ilon,ilev,id_H2SO4_strat) & |
---|
| 144 | & *pplay(ilon,ilev)/t_seri(ilon,ilev)/RD/1.E6/mH2SO4mol |
---|
| 145 | ! compute cond/evap rate in kg(H2SO4)/kgA/s (now only evap for pdtphys) |
---|
[4950] | 146 | IF(flag_new_strat_compo) THEN |
---|
| 147 | CALL condens_evapor_rate_kelvin(rhoa,t_seri(ilon,ilev),pplay(ilon,ilev), & |
---|
| 148 | & R2SO4(ilon,ilev),DENSO4(ilon,ilev),f_r_wet(ilon,ilev), & |
---|
| 149 | & R2SO4ik,DENSO4ik,f_r_wetik,FL,ASO4,DNDR) |
---|
| 150 | ELSE |
---|
| 151 | CALL condens_evapor_rate(rhoa,t_seri(ilon,ilev),pplay(ilon,ilev), & |
---|
| 152 | & ACTSO4(ilon,ilev),R2SO4(ilon,ilev),DENSO4(ilon,ilev),f_r_wet(ilon,ilev), & |
---|
| 153 | & FL,ASO4,DNDR) |
---|
| 154 | ENDIF |
---|
[2690] | 155 | ! limit evaporation (negative FL) over one physics time step to H2SO4 content of the droplet |
---|
[3098] | 156 | DO it=1,nbtr_bin |
---|
| 157 | FL(it)=MAX(FL(it)*pdtphys,0.-ASO4(it))/pdtphys |
---|
[2690] | 158 | ! consider only evap (negative FL) |
---|
[3098] | 159 | FL(it)=MIN(FL(it),0.) |
---|
[2690] | 160 | ENDDO |
---|
| 161 | ! compute total H2SO4 evap flux for all particles |
---|
| 162 | evap_rate=0.0 |
---|
[3098] | 163 | DO it=1, nbtr_bin |
---|
| 164 | evap_rate=evap_rate+tr_seri(ilon,ilev,it+nbtr_sulgas)*FL(it)*mH2SO4mol |
---|
[2690] | 165 | ENDDO |
---|
| 166 | ! update H2SO4 concentration after evap |
---|
| 167 | tr_seri(ilon,ilev,id_H2SO4_strat)=MAX(0.,tr_seri(ilon,ilev,id_H2SO4_strat)-evap_rate*pdtphys) |
---|
| 168 | ! apply evap to bins |
---|
[4950] | 169 | CALL condens_evapor_part(pdtphys,FL,ASO4,f_r_wet(ilon,ilev),tr_seri(ilon,ilev,:)) |
---|
[2690] | 170 | ! compute fluxes as diagnostic in [kg(S)/m2/layer/s] (now - for evap and + for cond) |
---|
[2752] | 171 | budg_3D_cond_evap(ilon,ilev)=budg_3D_cond_evap(ilon,ilev)+mSatom/mH2SO4mol & |
---|
[2690] | 172 | & *evap_rate*(paprs(ilon,ilev)-paprs(ilon,ilev+1))/RG |
---|
[3094] | 173 | ! compute vertically integrated flux due to the net effect of nucleation and condensation/evaporation |
---|
| 174 | budg_h2so4_to_part(ilon)=budg_h2so4_to_part(ilon)+(H2SO4_init-tr_seri(ilon,ilev,id_H2SO4_strat)) & |
---|
| 175 | & *mSatom/mH2SO4mol*(paprs(ilon,ilev)-paprs(ilon,ilev+1))/RG/pdtphys |
---|
[2690] | 176 | ENDIF |
---|
| 177 | ENDDO |
---|
| 178 | ENDDO |
---|
| 179 | |
---|
[2695] | 180 | IF (MINVAL(tr_seri).LT.0.0) THEN |
---|
[2690] | 181 | DO ilon=1, klon |
---|
| 182 | DO ilev=1, klev |
---|
[3098] | 183 | DO it=1, nbtr |
---|
| 184 | IF (tr_seri(ilon,ilev,it).LT.0.0) THEN |
---|
[3526] | 185 | WRITE(lunout,*) 'micphy_tstep: negative concentration', tr_seri(ilon,ilev,it), ilon, ilev, it |
---|
[2690] | 186 | ENDIF |
---|
| 187 | ENDDO |
---|
| 188 | ENDDO |
---|
| 189 | ENDDO |
---|
| 190 | ENDIF |
---|
| 191 | |
---|
| 192 | END SUBROUTINE micphy_tstep |
---|