m7_nuck.F90 13 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345
  1. #include "tm5.inc"
  2. SUBROUTINE m7_nuck(kproma, kbdim, klev, pso4g, pelvoc, &
  3. ptp1, prelhum, papp1, panew, pa4delt, &
  4. ptime, paernl, pm6rp )
  5. !
  6. ! Authors:
  7. ! --------
  8. ! J. Wilson, E. Vignati, JRC/EI, original source 09/2000
  9. ! P. Stier, MPI f90-version,
  10. ! changes,
  11. ! comments,
  12. ! modularisation and
  13. ! implementation of
  14. ! Vehkamaeki (2002) 2001-2003
  15. !
  16. ! Purpose:
  17. ! --------
  18. ! This routine calls the routines for the computation of the
  19. ! nucleation rate znucrate [molec. cm-3 s-1] and, for
  20. ! Vehkamaeki (2002), of the number of molecules in the critical
  21. ! cluster from a given gas phase H2SO4 concentration
  22. ! pso4g [molec. cm-3]. It also calculates the integrated change of
  23. ! H2SO4 gas phase mass over one timestep due to nucleation
  24. ! pa4delt(:,:,1) [molec. cm-3] as well as the number of nucleated
  25. ! particles panew [1] during the timestep. Whilst this is done
  26. ! analytically for the old Kulmala (1998) parameterization, it has
  27. ! to be done numerically for the new Vehkamaeki (2002) scheme.
  28. !
  29. ! Interface:
  30. ! ----------
  31. ! *m7_nuck* is called from *m7_dnum*
  32. !
  33. ! Method:
  34. ! -------
  35. !
  36. ! 1) Vehkamaeki et al. (2002):
  37. !
  38. ! An analytical integration of the nucleation equation is not
  39. ! possible, therefor the nucleation rate is simply multiplied
  40. ! by dt, implying a fixed gas-phase H2SO4 concentration over
  41. ! the timestep.
  42. !@@@ The dependency of the results on the used timestep
  43. !@@@ should be checked carefully in a sensitivity study!
  44. ! The number of nucleated particles is then calculated by
  45. ! taking the calculated critical mass critn of newly nucleated
  46. ! particles and dividing the total mass of nucleated sulfate
  47. ! by this critical mass of one nucleated particle.
  48. !
  49. ! 2) Kulmala et al. (1998):
  50. !
  51. ! For the Kulmala et al. (1998) scheme the formula for binary
  52. ! nucleation is rewritten to take the form
  53. ! znucrate = exp[zalpha+ln(pso4g)*beta].
  54. ! Equation numbers are taken from Kulmala et al. (1998).
  55. ! After the calculation of the nucleation rate znucrate, it is
  56. ! integrated in 2) analytically over one timestep, i.e.:
  57. !
  58. ! Integration of:
  59. !
  60. ! znucrate=d(critn*znav)/dt=exp[zalpha + zbeta*ln(znav)]
  61. !
  62. ! gives znav(t0+dt, znav(t0)) where znav(t0) is pso4g.
  63. ! znav is temporarily stored in zso4g_new and confined between
  64. ! 0 and pso4g.
  65. ! The number of nucleated particles is then calculated by
  66. ! assuming a fixed critical mass critn of newly nucleated
  67. ! particles and dividing the total mass of nucleated sulfate
  68. ! by this critical mass of one nucleated particle.
  69. !
  70. !
  71. ! 3) Paasonen et al. (2010):
  72. ! A semi-empirical parameterization for new particle formation
  73. ! mechanism involving low-volatility organic vapors. We use the
  74. ! mechanism from Eq. 15, which presumes homogeneous heteromolecular
  75. ! nucleation between sulfuric acid and organic molecules, or that
  76. ! one of the vapors activate the clusters the clusters of other
  77. ! compound parameterised as J=K[H2SO4][Org]. Diameter of produced particle
  78. ! is assumed to be 2 nm.
  79. !
  80. ! Externals:
  81. ! ----------
  82. ! nucl_kulmala
  83. ! nucl_vehkamaeki
  84. ! nucl_bl
  85. !
  86. ! References:
  87. ! -----------
  88. ! Paasonen et al. (2010), On the roles of sulphuric acid and low-volatility
  89. ! organic vapours in the initial steps of atmospheric new particle
  90. ! formation, Atmos. Chem. Phys., 10, 11223-11242, 2010
  91. ! Vehkamaeki et al. (2002), An improved parameterization for sulfuric
  92. ! acid/water nucleation rates for tropospheric and stratospheric
  93. ! conditions, J. Geophys. Res, 107, D22, 4622
  94. ! Kulmala et al. (1998), Parameterizations for sulfuric acid/water
  95. ! nucleation rates. J. Geophys. Res., 103, No D7, 8301-8307
  96. ! Vignatti, E. (1999), Modelling Interactions between Aerosols and
  97. ! Gaseous Compounds in the Polluted Marine Atmosphere. PhD-Thesis,
  98. ! RISO National Laborartory Copenhagen, Riso-R-1163(EN)
  99. use GO, only : gol, goErr, goPr, goBug
  100. USE mo_time_control, ONLY: delta_time
  101. USE mo_control, ONLY: nrow
  102. USE mo_kind, ONLY: wp
  103. USE mo_aero_m7, ONLY: critn, naermod, nnucl, avo, nmod, isoans
  104. ! USE mo_aero_mem, ONLY: d_nuc_so4
  105. USE mo_aero_nucl, ONLY: nucl_kulmala, nucl_vehkamaeki, nucl_bl
  106. USE chem_param, ONLY: xmelvoc
  107. USE mo_aero, ONLY: nsoa
  108. IMPLICIT NONE
  109. !--- Parameters:
  110. !
  111. ! pso4g = mass of gas phase sulfate [molec. cm-3]
  112. ! pelvoc = mass of gas phase elvoc [molec cm-3]
  113. ! ptp1 = atmospheric temperature at time t+1 [K]
  114. ! prelhum = atmospheric relative humidity [%]
  115. ! pa4delt(:,:,1) = mass of H2SO4 added to the nucleation mode due
  116. ! to nucleation of H2SO4 over ztmst.
  117. ! Equilvalent to the integral of H2SO4 gas loss
  118. ! due to nucleation over timestep ztmst. [molec. cm-3]
  119. ! panew = number of nucleated particles over timestep ztmst
  120. ! panew=pa4delt/critn i.e. mass of formed sulfate
  121. ! divided by an assumed mass of a nucleus. [cm-3]
  122. ! ptime = TM5 timestep
  123. !
  124. !--- Local variables:
  125. !
  126. ! zso4g_new = temporay storage of gas phase sulfate [molec. cm-3]
  127. ! zncrit = number of molecules in the critical cluster [1]
  128. !
  129. ! See comments!
  130. INTEGER :: kproma, kbdim, klev
  131. REAL :: ptime, time_step_len
  132. REAL :: pso4g(kbdim,klev), ptp1(kbdim,klev), &
  133. prelhum(kbdim,klev), panew(kbdim,klev), papp1(kbdim,klev), pelvoc(kbdim,klev)
  134. REAL :: pa4delt(kbdim,klev,naermod)
  135. REAL :: paernl(kbdim,klev,nmod), &
  136. pm6rp(kbdim,klev,nmod)
  137. ! Local variables:
  138. INTEGER :: jk, jl, jrow
  139. REAL :: ztmst, zqtmst, zf1, zeps
  140. REAL :: znucrate(kbdim,klev), & ! nucleation rate [m-3 s-1] !@@@ Make consistent with Kulmala
  141. zso4g_new(kbdim,klev), & ! new gas phase sulfate concentration [molec. cm-3]
  142. zalpha(kbdim,klev), & ! auxiliary coefficient for the analytical integration of Kulmala
  143. zbeta(kbdim,klev), & ! auxiliary coefficient for the analytical integration of Kulmala
  144. zncrit(kbdim,klev), & ! number of molecules in the critical cluster [1]
  145. zdiam(kbdim,klev) ! diameter of the critical cluster [nm]
  146. REAL :: bl_ppfr(kbdim,klev), bl_pns_sa(kbdim,klev), bl_pns_org(kbdim,klev), pmolecELVOC(kbdim,klev)
  147. !--- 0) Initialisations: ------------------------------------------------------
  148. jrow=nrow(2)
  149. time_step_len = ptime
  150. ztmst=time_step_len
  151. zqtmst=1/ztmst
  152. zeps=EPSILON(1.0_wp)
  153. znucrate=0.
  154. zncrit=0.
  155. bl_ppfr=0.
  156. ! Convert ELVOC from ug/m3 to molec/cm3
  157. !1e-12/xmbc*Avog
  158. DO jk=1, klev
  159. DO jl=1, kproma
  160. pmolecELVOC(jl,jk)=(pelvoc(jl,jk)*1.e-12*avo)/(xmelvoc)
  161. END DO
  162. END DO
  163. IF(nnucl==1) THEN
  164. CALL nucl_vehkamaeki(kproma, kbdim, klev, & ! ECHAM5 dimensions
  165. ptp1, prelhum, pso4g, & ! ECHAM5 temperature, relative humidity
  166. znucrate, zncrit, zdiam )
  167. !--- Calculate updated gas phase concentration:
  168. !
  169. ! N(t) = N(0) - znucrate * zncrit * dt
  170. ! [cm-3] = [cm-3] - [cm-3 s-1] * [1] * [s]
  171. DO jk=1, klev
  172. DO jl=1, kproma
  173. zso4g_new(jl,jk)=pso4g(jl,jk)-(znucrate(jl,jk)*zncrit(jl,jk)*ztmst)
  174. END DO
  175. END DO
  176. ELSE IF (nnucl==2) THEN
  177. zncrit(:,:)=critn
  178. CALL nucl_kulmala(kproma, kbdim, klev, &
  179. pso4g, ptp1, prelhum, &
  180. znucrate, zalpha, zbeta )
  181. !--- 2) Analytical integration of the nucleation rate (Eq. 19) ----------------
  182. ! over timestep ztmst assuming no new H2SO4(g) production:
  183. !
  184. ! d(N_av/critn)/dt=exp(alpha + beta*ln(N_av)) => ... =>
  185. !
  186. ! N_av(t0+dt)=
  187. ! [N_av(t0)**(1-beta) + critn*(1-beta)exp(alpha)*dt]**(1/(1-beta)
  188. !
  189. DO jk=1, klev
  190. DO jl=1, kproma
  191. IF (znucrate(jl,jk) .GT. 1e-10) THEN
  192. zf1 = pso4g(jl,jk)**(1.0-zbeta(jl,jk))-critn*EXP(zalpha(jl,jk))*(1.0-zbeta(jl,jk))*ztmst
  193. zso4g_new(jl,jk) = EXP(LOG(zf1)/(1.0 - zbeta(jl,jk)))
  194. ELSE
  195. zso4g_new(jl,jk) = pso4g(jl,jk)
  196. END IF
  197. END DO
  198. END DO
  199. ELSE IF (nsoa==2 .and. nnucl==3) THEN
  200. CALL nucl_vehkamaeki(kproma, kbdim, klev, & ! ECHAM5 dimensions
  201. ptp1, prelhum, pso4g, & ! ECHAM5 temperature, relative humidity
  202. znucrate, zncrit, zdiam )
  203. CALL nucl_bl(kproma, kbdim, klev, & ! Dimensions
  204. pso4g, pmolecELVOC, ptp1, papp1, prelhum, & ! H2SO4 concentration, ELVOC concentration
  205. paernl, pm6rp, znucrate, zdiam, & !
  206. bl_ppfr, bl_pns_sa, bl_pns_org, ztmst) ! Formation rate, number of H2SO4 molecules in cluster
  207. ELSE IF (nsoa==2 .and. nnucl==4) THEN
  208. CALL nucl_vehkamaeki(kproma, kbdim, klev, & ! ECHAM5 dimensions
  209. ptp1, prelhum, pso4g, & ! ECHAM5 temperature, relative humidity
  210. znucrate, zncrit, zdiam )
  211. CALL nucl_bl(kproma, kbdim, klev, & ! Dimensions
  212. pso4g, pmolecELVOC, ptp1, papp1, prelhum, & ! H2SO4 concentration, ELVOC concentration
  213. paernl, pm6rp, znucrate, zdiam, & !
  214. bl_ppfr, bl_pns_sa, bl_pns_org, ztmst) ! Formation rate, number of H2SO4 molecules in cluster
  215. ELSE
  216. write(gol,*) 'M7_nuck: Choice of nucleation scheme is not supported, nsoa=',nsoa,' nnucl= ',nnucl
  217. call goPr
  218. return
  219. END IF
  220. !--- 3) Calculate changes in gas-phase and aerosol mass and aerosol numbers: --
  221. DO jk=1, klev
  222. DO jl=1, kproma
  223. IF( znucrate(jl,jk) > zeps .OR. bl_ppfr(jl,jk) > zeps ) THEN
  224. !--- 3.1) If BL nucleation is active, apply only BL nucleation:
  225. IF(nsoa==2 .and. (nnucl==3 .OR. nnucl==4)) THEN
  226. pa4delt(jl,jk,1) = bl_ppfr(jl,jk)*bl_pns_sa(jl,jk)*ztmst
  227. pa4delt(jl,jk,isoans) = bl_ppfr(jl,jk)*bl_pns_org(jl,jk)*ztmst*xmelvoc/(1.e-12*avo)
  228. pa4delt(jl,jk,1) = MAX(MIN(pso4g(jl,jk), pa4delt(jl,jk,1)),0.0)
  229. pa4delt(jl,jk,isoans) = MAX(MIN(pelvoc(jl,jk),pa4delt(jl,jk,isoans)),0.0)
  230. panew(jl,jk)=bl_ppfr(jl,jk)*ztmst
  231. !RM
  232. !IF(jk==klev .AND. jl==230) THEN
  233. ! WRITE(*,*) 'nuck, delt:',pa4delt(jl,jk,1),pa4delt(jl,jk,isoans),bl_ppfr(jl,jk)
  234. ! WRITE(*,*) 'nuck, orig :',pso4g(jl,jk),pelvoc(jl,jk),pmolecELVOC(jl,jk)
  235. !END IF
  236. !
  237. !--- 3.4) Calculate changes in gas phase due to nucleation:
  238. !
  239. pso4g(jl,jk)=pso4g(jl,jk)-pa4delt(jl,jk,1)
  240. pelvoc(jl,jk)=pelvoc(jl,jk)-pa4delt(jl,jk,isoans)
  241. !--- 4) Vertically integrate mass of nucleated sulfate for diagnostics
  242. ! Convert [molec. cm-3] to [kg(S) m-2]:
  243. ELSE ! BL nucleation not active
  244. !--- 3.2) Calculate mass of nucleated H2SO4 (equals the net
  245. ! gas phase H2SO4 loss):
  246. !
  247. ! pa4delt(jl,jk,1) = (pso4g(jl,jk)-zso4g_new(jl,jk))
  248. ! JadB: A problem occurs. We calculate gas_new, wich is gas_old - nucleation,
  249. ! and then calculate the nucleation again with gas_old - gas_new.
  250. ! Huge errors when the time step is small.
  251. ! That's why we take the nucleation as fresh as possible (from znucrate) and apply the limiters.
  252. !pa4delt(jl,jk,1) = (znucrate(jl,jk)*zncrit(jl,jk)*ztmst)
  253. pa4delt(jl,jk,1) = (znucrate(jl,jk)*zncrit(jl,jk)*ztmst)
  254. pa4delt(jl,jk,1) = Max(pa4delt(jl,jk,1),0.0)
  255. pa4delt(jl,jk,1) = Min(pa4delt(jl,jk,1),pso4g(jl,jk))
  256. !
  257. !--- 3.3) Calculate the number of nucleated particles (nucleated mass
  258. ! divided by the assumed mass of a critical cluster critn):
  259. panew(jl,jk)=pa4delt(jl,jk,1)/zncrit(jl,jk)
  260. !
  261. !--- 3.4) Calculate changes in gas phase H2SO4 due to nucleation:
  262. !
  263. pso4g(jl,jk)=pso4g(jl,jk)-pa4delt(jl,jk,1)
  264. !--- 4) Vertically integrate mass of nucleated sulfate for diagnostics
  265. ! Convert [molec. cm-3] to [kg(S) m-2]:
  266. END IF
  267. END IF
  268. END DO
  269. END DO
  270. END SUBROUTINE m7_nuck