m7_dnum.F90 14 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373
  1. #include "tm5.inc"
  2. #ifdef with_budgets
  3. SUBROUTINE m7_dnum(kproma, kbdim, klev, &
  4. pso4g, pelvoc, paerml, paernl, ptp1, &
  5. papp1, prelhum, pm6rp, prhop, &
  6. pso4_5, pso4_6, pso4_7, ptime, &
  7. pprocess)
  8. #else
  9. SUBROUTINE m7_dnum(kproma, kbdim, klev, &
  10. pso4g, pelvoc, paerml, paernl, ptp1, &
  11. papp1, prelhum, pm6rp, prhop, &
  12. pso4_5, pso4_6, pso4_7, ptime )
  13. #endif
  14. !
  15. ! *m7_dnum* changes gas phase sulfate, aerosol numbers and masses
  16. ! due to nucleation and coagulation
  17. !
  18. ! Authors:
  19. ! ---------
  20. ! J. Wilson and E. Vignati, JRC/EI (original source) 09/2000
  21. ! P. Stier, MPI (f90-version, changes, comments) 2001
  22. !
  23. ! Version:
  24. ! ---------
  25. ! This version is equivalent to the version dnum2 of the m7 boxmodel.
  26. !
  27. ! Purpose
  28. ! ---------
  29. ! This routine calculates new gas phase sulfate and aerosol
  30. ! numbers and masses after timestep ztmst.
  31. !
  32. ! Interface
  33. ! -----------
  34. ! *m7_dnum* is called from *m7*
  35. !
  36. ! Externals
  37. ! -----------
  38. ! *m7_coaset* calculates the coagulation kernels
  39. ! *m7_nuck* calculates the integral mass nucleated sulfate and
  40. ! the number of nucleated partcles over one timestep
  41. ! *m7_delcoa* integrates equations for the changes in aerosol numbers
  42. ! dn/dt=c -an2 -bn over one timestep and calculates the
  43. ! corresponding changes in aerosol masses
  44. ! *m7_concoag* calculates particle numbers and mass moved from the
  45. ! insoluble to the mixed modes due to coagulation with
  46. ! smaller mixed particles and condensation of H2SO4.
  47. !
  48. ! Warning:
  49. ! --------
  50. ! For optimization purposes currently only "physically reasonable" elements of the
  51. ! coagulation kernel zcom are calculated in m7_concoag. These elements are specified
  52. ! in the matrix locoagmask in mo_aero_m7. Check carefully and adapt locoagmask
  53. ! accordingly before changes in the code below.
  54. USE mo_aero_m7, ONLY: naermod, nmod, lsnucl, lscoag, isoans
  55. #ifdef with_budgets
  56. Use M7_Data, Only: nm7procs
  57. #endif
  58. IMPLICIT NONE
  59. !--- Parameters:
  60. !
  61. ! pso4g = mass of gas phase sulfate [molec. cm-3]
  62. ! pelvoc = mass of gas phase elvoc [molec cm-3]
  63. ! paerml = total aerosol mass for each compound
  64. ! [molec. cm-3 for sulphate and ug m-3 for bc, oc, ss, and dust]
  65. ! paernl = aerosol number for each mode [cm-3]
  66. ! ptp1 = atmospheric temperature at time t+1 [K]
  67. ! papp1 = atmospheric pressure at time t+1 [Pa]
  68. ! prelhum = atmospheric relative humidity [%]
  69. ! pm6rp = mean mode actual radius (wet radius for soluble modes
  70. ! and dry radius for insoluble modes) [cm]
  71. ! prhop = mean mode particle density [g cm-3]
  72. ! pso4_x = mass of sulphate condensed on insoluble mode x []
  73. ! ptime = TM5 time step
  74. !
  75. !
  76. !--- Local variables:
  77. !
  78. ! zcom = general coagulation coefficient []
  79. ! (calculated in m7_coaset)
  80. ! za = effectively used coagulation coefficient for
  81. ! unimodal coagulation []
  82. ! zb = effectively used coagulation coefficient for
  83. ! inter-modal coagulation []
  84. ! zbfractx(:,:,y) = fraction of the total number of particles removed by
  85. ! coagulation from mode x (finally calculated in m7_delcoa)
  86. ! that is moved to mode y / y+1 (modes 5,6,7 and mode 1,2 resp.) [1]
  87. ! !@@@ Careful! Inconsistent usage!!!
  88. ! za4delt(:,:,:) = change in H2SO4 mass of the respective mode over one timstep
  89. ! due to:
  90. ! - nucleation of H2SO4 (calculated in m7_nuck)
  91. ! - coagulation (calculated in m7_concoag)
  92. ! zanew = number of nucleated particles
  93. ! zanew=za4delt/critn i.e. mass of formed sulfate
  94. ! divided by an assumed mass of a nucleus. []
  95. ! (calculated in m7_nuck)
  96. ! zxxavy = average mass of species xx in mode y []
  97. ! where xx is ss, du, bc, oc, or a4 for sulfate
  98. ! [molecules for sulfate and ug for others]
  99. !
  100. !@@@ to be continued!
  101. !--- Parameters:
  102. INTEGER :: kproma, kbdim, klev
  103. REAL :: ptime
  104. REAL :: pso4g(kbdim,klev), ptp1(kbdim,klev), &
  105. papp1(kbdim,klev), prelhum(kbdim,klev), &
  106. pso4_5(kbdim,klev), pso4_6(kbdim,klev), &
  107. pso4_7(kbdim,klev), pelvoc(kbdim,klev)
  108. REAL :: paerml(kbdim,klev,naermod), paernl(kbdim,klev,nmod), &
  109. pm6rp(kbdim,klev,nmod), prhop(kbdim,klev,nmod)
  110. #ifdef with_budgets
  111. Real :: pprocess(kbdim,klev,nm7procs)
  112. #endif
  113. ! Local Variables:
  114. INTEGER :: jl, jk
  115. REAL :: zanew(kbdim,klev)
  116. REAL :: za(kbdim,klev,nmod), zb(kbdim,klev,nmod), &
  117. za4delt(kbdim,klev,naermod)
  118. REAL :: zbfract1(kbdim,klev,nmod-1),zbfract2(kbdim,klev,nmod-1), &
  119. zbfract5(kbdim,klev,3), zbfract6(kbdim,klev,2), &
  120. zbfract7(kbdim,klev,2)
  121. REAL :: zcom(kbdim,klev,nmod,nmod)
  122. !--- 0) Initialisations: ----------------------------------------------
  123. za4delt(:,:,:) = 0. ! Mode 1 changed by m7_nuck if lsnucl=TRUE .
  124. ! Has to be initialized for the other modes.
  125. zanew(:,:) = 0. ! Changed by m7_nuck if lsnucl=TRUE .
  126. !--- 1) Calculate coagulation coefficients: --------------------------
  127. !
  128. IF (lscoag) CALL m7_coaset(kproma, kbdim, klev, paernl, ptp1, &
  129. papp1, pm6rp, prhop, zcom )
  130. !
  131. !--- 2) Calculate nucleation rate, number of nucleated particles ------
  132. ! and changes in gas phase sulfate mass.
  133. !
  134. IF (lsnucl) CALL m7_nuck(kproma, kbdim, klev, pso4g, pelvoc, &
  135. ptp1, prelhum, papp1, zanew, za4delt, &
  136. ptime , paernl, pm6rp )
  137. #ifdef with_budgets
  138. pprocess(:,:,1) = zanew ! Nucleations
  139. pprocess(:,:,2) = za4delt(:,:,1) ! Sulfate involved in nucleation
  140. pprocess(:,:,88) = za4delt(:,:,isoans) ! Organics involved in nucleation
  141. #endif
  142. !
  143. !--- 3) Assign coagulation coefficients (unimodal coagulation)---------
  144. ! and the normalised fraction of particle numbers moved
  145. ! between the modes (inter-modal coagulation):
  146. !
  147. ! The general equation for dn/dt for each mode is:
  148. !
  149. ! dn/dt=-za*n^2 - zb*n + zc
  150. !
  151. ! where za=unimodal coagulation coefficient (zcom(mod))
  152. ! zb=inter-modal coagulation with higher modes
  153. ! (zcom(mod) * n(jmod+1))
  154. ! zc=particle formation rate
  155. ! (=zanew/ztmst if jmod=1, zero for higher modes)
  156. !
  157. ! zb is zero when n(jmod+1)=zero, or jmod=naermod
  158. !
  159. IF (lscoag) THEN
  160. DO jk=1,klev
  161. DO jl=1,kproma
  162. !--- 3.1) Unimodal coagulation coefficients:
  163. !@@@Coag:
  164. za(jl,jk,1)=zcom(jl,jk,1,1)/2. ! Unimodal coagulation
  165. za(jl,jk,2)=zcom(jl,jk,2,2)/2. ! only allowed for modes
  166. za(jl,jk,3)=zcom(jl,jk,3,3)/2. ! 1,2,3 and 5.
  167. za(jl,jk,4)=0.
  168. za(jl,jk,5)=zcom(jl,jk,5,5)/2.
  169. za(jl,jk,6)=0.
  170. za(jl,jk,7)=0.
  171. !
  172. !--- 3.2) Inter-modal coagulation - soluble modes
  173. !
  174. !--- Sum all higher mode coagulation terms for
  175. ! soluble modes 1,2,3,4:
  176. !
  177. !--- 3.2.1) Mode 1:
  178. !--- Number of particles (zbfract1(:,:,x)) that are moved
  179. ! from mode 1 to the mode x+1 :
  180. ! !@@@ Clumsy! Change to x - also in concoag!!!
  181. zbfract1(jl,jk,1)=zcom(jl,jk,2,1)*paernl(jl,jk,2)
  182. zbfract1(jl,jk,2)=zcom(jl,jk,3,1)*paernl(jl,jk,3)
  183. zbfract1(jl,jk,3)=zcom(jl,jk,4,1)*paernl(jl,jk,4)
  184. zbfract1(jl,jk,4)=zcom(jl,jk,5,1)*paernl(jl,jk,5)
  185. zbfract1(jl,jk,5)=zcom(jl,jk,6,1)*paernl(jl,jk,6)
  186. zbfract1(jl,jk,6)=zcom(jl,jk,7,1)*paernl(jl,jk,7)
  187. !
  188. !--- Sum of all particles that are moved from mode 1:
  189. !
  190. zb(jl,jk,1)=zbfract1(jl,jk,1)+zbfract1(jl,jk,2)+ &
  191. zbfract1(jl,jk,3)+zbfract1(jl,jk,4)+ &
  192. zbfract1(jl,jk,5)+zbfract1(jl,jk,6)
  193. !
  194. !--- Normalize number of particles by the total number of
  195. ! particles moved from mode 1:
  196. !
  197. IF (zb(jl,jk,1).GT. EPSILON(zb(jl,jk,1))) THEN
  198. zbfract1(jl,jk,1)=zbfract1(jl,jk,1)/zb(jl,jk,1)
  199. zbfract1(jl,jk,2)=zbfract1(jl,jk,2)/zb(jl,jk,1)
  200. zbfract1(jl,jk,3)=zbfract1(jl,jk,3)/zb(jl,jk,1)
  201. zbfract1(jl,jk,4)=zbfract1(jl,jk,4)/zb(jl,jk,1)
  202. zbfract1(jl,jk,5)=zbfract1(jl,jk,5)/zb(jl,jk,1)
  203. zbfract1(jl,jk,6)=zbfract1(jl,jk,6)/zb(jl,jk,1)
  204. END IF
  205. !
  206. !--- 3.2.2) Mode 2:
  207. !
  208. !--- Number of particles (zbfract1(:,:,x)) that are moved
  209. ! from mode 2 to the mode x+1 :
  210. !
  211. zbfract2(jl,jk,2)=zcom(jl,jk,3,2)*paernl(jl,jk,3)
  212. zbfract2(jl,jk,3)=zcom(jl,jk,4,2)*paernl(jl,jk,4)
  213. !zbfract2(jl,jk,4)=zcom(jl,jk,5,2)*paernl(jl,jk,5)
  214. zbfract2(jl,jk,4)=0.
  215. zbfract2(jl,jk,5)=zcom(jl,jk,6,2)*paernl(jl,jk,6)
  216. zbfract2(jl,jk,6)=zcom(jl,jk,7,2)*paernl(jl,jk,7)
  217. !--- Sum of all particles that are moved from mode 2:
  218. zb(jl,jk,2)=zbfract2(jl,jk,2)+zbfract2(jl,jk,3)+ &
  219. zbfract2(jl,jk,4)+zbfract2(jl,jk,5)+ &
  220. zbfract2(jl,jk,6)
  221. !--- Normalize particle numbers by the total number of
  222. ! particles moved from mode 2:
  223. IF (zb(jl,jk,2).GT. EPSILON(zb(jl,jk,2))) THEN
  224. zbfract2(jl,jk,2)=zbfract2(jl,jk,2)/zb(jl,jk,2)
  225. zbfract2(jl,jk,3)=zbfract2(jl,jk,3)/zb(jl,jk,2)
  226. zbfract2(jl,jk,4)=zbfract2(jl,jk,4)/zb(jl,jk,2)
  227. zbfract2(jl,jk,5)=zbfract2(jl,jk,5)/zb(jl,jk,2)
  228. zbfract2(jl,jk,6)=zbfract2(jl,jk,6)/zb(jl,jk,2)
  229. END IF
  230. !--- 3.2.3) Mode 3 and Mode 4 - considered ineffective:
  231. zb(jl,jk,3)=0.0
  232. zb(jl,jk,4)=0.0
  233. !
  234. !--- 3.3) Inter-modal coagulation - insoluble modes
  235. !
  236. ! For the insoluble modes coagulation with soluble modes
  237. ! is a sink as they are transfered to the corresponding
  238. ! mixed/solublemode. Therefore, terms with a lower mode
  239. ! number or the same mode number are included.
  240. ! (!@@@ There are still some switches for testing.)
  241. !
  242. !--- 3.3.1) Mode 5:
  243. !
  244. !--- Number of particles (zbfract5(:,:,x)) that are moved
  245. ! from mode 5 to the mode x:
  246. !@@@ zbfract5(jl,jk,1)= zcom(jl,jk,1,5)*paernl(jl,jk,1)
  247. zbfract5(jl,jk,1)=0.
  248. zbfract5(jl,jk,2)=zcom(jl,jk,2,5)*paernl(jl,jk,2)
  249. zbfract5(jl,jk,3)=zcom(jl,jk,3,5)*paernl(jl,jk,3)
  250. !--- Sum of all particles that are moved from mode 5:
  251. zb(jl,jk,5)=zbfract5(jl,jk,1)+zbfract5(jl,jk,2)+zbfract5(jl,jk,3)
  252. !--- Normalize number of particles by the total number of
  253. ! particles moved from mode 5:
  254. IF (zb(jl,jk,5).GT. EPSILON(zb(jl,jk,5))) THEN
  255. zbfract5(jl,jk,1)=zbfract5(jl,jk,1)/zb(jl,jk,5)
  256. zbfract5(jl,jk,2)=zbfract5(jl,jk,2)/zb(jl,jk,5)
  257. zbfract5(jl,jk,3)=zbfract5(jl,jk,3)/zb(jl,jk,5)
  258. END IF
  259. !--- 3.3.2) Mode 6:
  260. !--- Number of particles (zbfract6(:,:,x)) that are moved
  261. ! from mode 6 to the mode x:
  262. !@@@zbfract6(jl,jk,1)=zcom(jl,jk,1,6)*paernl(jl,jk,1)
  263. !@@@zbfract6(jl,jk,2)=zcom(jl,jk,2,6)*paernl(jl,jk,2)
  264. zbfract6(jl,jk,1)=0.
  265. zbfract6(jl,jk,2)=0.
  266. !--- Sum of all particles that are moved from mode 6:
  267. zb(jl,jk,6)=zbfract6(jl,jk,1)+zbfract6(jl,jk,2)
  268. !--- Normalize number of particles by the total number of
  269. ! particles moved from mode 6:
  270. IF (zb(jl,jk,6).GT. EPSILON(zb(jl,jk,6))) THEN
  271. zbfract6(jl,jk,1)=zbfract6(jl,jk,1)/zb(jl,jk,6)
  272. zbfract6(jl,jk,2)=zbfract6(jl,jk,2)/zb(jl,jk,6)
  273. END IF
  274. !--- 3.3.3) Mode 7:
  275. !--- Number of particles (zbfract7(:,:,x)) that are moved
  276. ! from mode 7 to the mode x:
  277. !@@@ zbfract7(jl,jk,1)=zcom(jl,jk,1,7)*paernl(jl,jk,1)
  278. !@@@ zbfract7(jl,jk,2)=zcom(jl,jk,2,7)*paernl(jl,jk,2)
  279. zbfract7(jl,jk,1)=0.
  280. zbfract7(jl,jk,2)=0.
  281. !--- Sum of all particles that are moved from mode 7:
  282. zb(jl,jk,7)=zbfract7(jl,jk,1)+zbfract7(jl,jk,2)
  283. !--- Normalize number of particles by the total number of
  284. ! particles moved from mode 7:
  285. IF (zb(jl,jk,7).GT. EPSILON(zb(jl,jk,7))) THEN
  286. zbfract7(jl,jk,1)=zbfract7(jl,jk,1)/zb(jl,jk,7)
  287. zbfract7(jl,jk,2)=zbfract7(jl,jk,2)/zb(jl,jk,7)
  288. END IF
  289. END DO
  290. END DO
  291. !
  292. ELSE
  293. za(:,:,:) = 0.
  294. zb(:,:,:) = 0.
  295. zbfract1(:,:,:) = 0.
  296. zbfract2(:,:,:) = 0.
  297. zbfract5(:,:,:) = 0.
  298. zbfract6(:,:,:) = 0.
  299. zbfract7(:,:,:) = 0.
  300. END IF !(lscoag)
  301. !
  302. !
  303. #ifdef with_budgets
  304. CALL m7_delcoa(kproma, kbdim, klev, paerml, &
  305. paernl, pm6rp, za4delt, zanew, &
  306. za, zb, zbfract1, zbfract2, &
  307. zbfract5, pso4_5, pso4_6, pso4_7, ptime,pprocess )
  308. #else
  309. CALL m7_delcoa(kproma, kbdim, klev, paerml, &
  310. paernl, pm6rp, za4delt, zanew, &
  311. za, zb, zbfract1, zbfract2, &
  312. zbfract5, pso4_5, pso4_6, pso4_7, ptime )
  313. #endif
  314. END SUBROUTINE m7_dnum