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