m7_nuck.F90 8.8 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248
  1. #include "tm5.inc"
  2. SUBROUTINE m7_nuck(kproma, kbdim, klev, pso4g, &
  3. ptp1, prelhum, panew, pa4delt, &
  4. ptime )
  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) Kulmala et al. (1998):
  37. !
  38. ! For the Kulmala et al. (1998) scheme the formula for binary
  39. ! nucleation is rewritten to take the form
  40. ! znucrate = exp[zalpha+ln(pso4g)*beta].
  41. ! Equation numbers are taken from Kulmala et al. (1998).
  42. ! After the calculation of the nucleation rate znucrate, it is
  43. ! integrated in 2) analytically over one timestep, i.e.:
  44. !
  45. ! Integration of:
  46. !
  47. ! znucrate=d(critn*znav)/dt=exp[zalpha + zbeta*ln(znav)]
  48. !
  49. ! gives znav(t0+dt, znav(t0)) where znav(t0) is pso4g.
  50. ! znav is temporarily stored in zso4g_new and confined between
  51. ! 0 and pso4g.
  52. ! The number of nucleated particles is then calculated by
  53. ! assuming a fixed critical mass critn of newly nucleated
  54. ! particles and dividing the total mass of nucleated sulfate
  55. ! by this critical mass of one nucleated particle.
  56. !
  57. !
  58. ! 2) Vehkamaeki et al. (2002):
  59. !
  60. ! An analytical integration of the nucleation equation is not
  61. ! possible, therefor the nucleation rate is simply multiplied
  62. ! by dt, implying a fixed gas-phase H2SO4 concentration over
  63. ! the timestep.
  64. !@@@ The dependency of the results on the used timestep
  65. !@@@ should be checked carefully in a sensitivity study!
  66. ! The number of nucleated particles is then calculated by
  67. ! taking the calculated critical mass critn of newly nucleated
  68. ! particles and dividing the total mass of nucleated sulfate
  69. ! by this critical mass of one nucleated particle.
  70. !
  71. ! Externals:
  72. ! ----------
  73. ! nucl_kulmala
  74. ! nucl_vehkamaeki
  75. !
  76. ! References:
  77. ! -----------
  78. ! Vehkamaeki et al. (2002), An improved parameterization for sulfuric
  79. ! acid/water nucleation rates for tropospheric and stratospheric
  80. ! conditions, J. Geophys. Res, 107, D22, 4622
  81. ! Kulmala et al. (1998), Parameterizations for sulfuric acid/water
  82. ! nucleation rates. J. Geophys. Res., 103, No D7, 8301-8307
  83. ! Vignatti, E. (1999), Modelling Interactions between Aerosols and
  84. ! Gaseous Compounds in the Polluted Marine Atmosphere. PhD-Thesis,
  85. ! RISO National Laborartory Copenhagen, Riso-R-1163(EN)
  86. USE mo_time_control, ONLY: delta_time
  87. USE mo_control, ONLY: nrow
  88. USE mo_kind, ONLY: wp
  89. USE mo_aero_m7, ONLY: critn, naermod, nnucl, avo
  90. ! USE mo_aero_mem, ONLY: d_nuc_so4
  91. USE mo_aero_nucl, ONLY: nucl_kulmala, nucl_vehkamaeki
  92. IMPLICIT NONE
  93. !--- Parameters:
  94. !
  95. ! pso4g = mass of gas phase sulfate [molec. cm-3]
  96. ! ptp1 = atmospheric temperature at time t+1 [K]
  97. ! prelhum = atmospheric relative humidity [%]
  98. ! pa4delt(:,:,1) = mass of H2SO4 added to the nucleation mode due
  99. ! to nucleation of H2SO4 over ztmst.
  100. ! Equilvalent to the integral of H2SO4 gas loss
  101. ! due to nucleation over timestep ztmst. [molec. cm-3]
  102. ! panew = number of nucleated particles over timestep ztmst
  103. ! panew=pa4delt/critn i.e. mass of formed sulfate
  104. ! divided by an assumed mass of a nucleus. [cm-3]
  105. !
  106. !--- Local variables:
  107. !
  108. ! zso4g_new = temporay storage of gas phase sulfate [molec. cm-3]
  109. ! zncrit = number of molecules in the critical cluster [1]
  110. !
  111. ! See comments!
  112. INTEGER :: kproma, kbdim, klev
  113. REAL :: ptime, time_step_len
  114. REAL :: pso4g(kbdim,klev), ptp1(kbdim,klev), &
  115. prelhum(kbdim,klev), panew(kbdim,klev)
  116. REAL :: pa4delt(kbdim,klev,naermod)
  117. ! Local variables:
  118. INTEGER :: jk, jl, jrow
  119. REAL :: ztmst, zqtmst, zf1, zeps
  120. REAL :: znucrate(kbdim,klev), & ! nucleation rate [m-3 s-1] !@@@ Make consistent with Kulmala
  121. zso4g_new(kbdim,klev), & ! new gas phase sulfate concentration [molec. cm-3]
  122. zalpha(kbdim,klev), & ! auxiliary coefficient for the analytical integration of Kulmala
  123. zbeta(kbdim,klev), & ! auxiliary coefficient for the analytical integration of Kulmala
  124. zncrit(kbdim,klev) ! number of molecules in the critical cluster [1]
  125. !--- 0) Initialisations: ------------------------------------------------------
  126. jrow=nrow(2)
  127. time_step_len = ptime
  128. ztmst=time_step_len
  129. zqtmst=1/ztmst
  130. zeps=EPSILON(1.0_wp)
  131. !--- 1) Calculate nucleation rate:
  132. IF(nnucl==1) THEN
  133. CALL nucl_vehkamaeki(kproma, kbdim, klev, & ! ECHAM5 dimensions
  134. ptp1, prelhum, pso4g, & ! ECHAM5 temperature, relative humidity
  135. znucrate, zncrit )
  136. !--- Calculate updated gas phase concentration:
  137. !
  138. ! N(t) = N(0) - znucrate * zncrit * dt
  139. ! [cm-3] = [cm-3] - [cm-3 s-1] * [1] * [s]
  140. DO jk=1, klev
  141. DO jl=1, kproma
  142. zso4g_new(jl,jk)=pso4g(jl,jk)-(znucrate(jl,jk)*zncrit(jl,jk)*ztmst)
  143. END DO
  144. END DO
  145. ELSE IF (nnucl==2) THEN
  146. zncrit(:,:)=critn
  147. CALL nucl_kulmala(kproma, kbdim, klev, &
  148. pso4g, ptp1, prelhum, &
  149. znucrate, zalpha, zbeta )
  150. !--- 2) Analytical integration of the nucleation rate (Eq. 19) ----------------
  151. ! over timestep ztmst assuming no new H2SO4(g) production:
  152. !
  153. ! d(N_av/critn)/dt=exp(alpha + beta*ln(N_av)) => ... =>
  154. !
  155. ! N_av(t0+dt)=
  156. ! [N_av(t0)**(1-beta) + critn*(1-beta)exp(alpha)*dt]**(1/(1-beta)
  157. !
  158. DO jk=1, klev
  159. DO jl=1, kproma
  160. IF (znucrate(jl,jk) .GT. 1e-10) THEN
  161. zf1 = pso4g(jl,jk)**(1.0-zbeta(jl,jk))-critn*EXP(zalpha(jl,jk))*(1.0-zbeta(jl,jk))*ztmst
  162. zso4g_new(jl,jk) = EXP(LOG(zf1)/(1.0 - zbeta(jl,jk)))
  163. ELSE
  164. zso4g_new(jl,jk) = pso4g(jl,jk)
  165. END IF
  166. END DO
  167. END DO
  168. END IF
  169. !--- 3) Calculate changes in gas-phase and aerosol mass and aerosol numbers: --
  170. DO jk=1, klev
  171. DO jl=1, kproma
  172. IF( znucrate(jl,jk) > zeps ) THEN
  173. !--- 3.1) Security check:
  174. zso4g_new(jl,jk) = MAX(zso4g_new(jl,jk), 0.0)
  175. zso4g_new(jl,jk) = MIN(zso4g_new(jl,jk), pso4g(jl,jk))
  176. !--- 3.2) Calculate mass of nucleated H2SO4 (equals the net
  177. ! gas phase H2SO4 loss):
  178. !
  179. ! pa4delt(jl,jk,1) = (pso4g(jl,jk)-zso4g_new(jl,jk))
  180. ! JadB: A problem occurs. We calculate gas_new, wich is gas_old - nucleation,
  181. ! and then calculate the nucleation again with gas_old - gas_new.
  182. ! Huge errors when the time step is small.
  183. ! That's why we take the nucleation as fresh as possible (from znucrate) and apply the limiters.
  184. pa4delt(jl,jk,1) = (znucrate(jl,jk)*zncrit(jl,jk)*ztmst)
  185. pa4delt(jl,jk,1) = Max(pa4delt(jl,jk,1),0.0)
  186. pa4delt(jl,jk,1) = Min(pa4delt(jl,jk,1),pso4g(jl,jk))
  187. !
  188. !--- 3.3) Calculate the number of nucleated particles (nucleated mass
  189. ! divided by the assumed mass of a critical cluster critn):
  190. panew(jl,jk)=pa4delt(jl,jk,1)/zncrit(jl,jk)
  191. !
  192. !--- 3.4) Calculate changes in gas phase H2SO4 due to nucleation:
  193. !
  194. pso4g(jl,jk)=pso4g(jl,jk)-pa4delt(jl,jk,1)
  195. !--- 4) Vertically integrate mass of nucleated sulfate for diagnostics
  196. ! Convert [molec. cm-3] to [kg(S) m-2]:
  197. END IF
  198. END DO
  199. END DO
  200. ! write(*,*) 'nuck', 'nucl part= ',panew(2100,1), 'so4gn', pso4g(2100,1), 'deltag', pa4delt(2100,1,1)
  201. END SUBROUTINE m7_nuck