m7_equimix.F90 9.1 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231
  1. #include "tm5.inc"
  2. SUBROUTINE m7_equimix(kproma, kbdim, klev, &
  3. papp1, pttn, ptp1, &
  4. prelhum, pm6rp, pm6dry, &
  5. prhop, pww, paernl )
  6. !
  7. ! *m7_equimix* calculates the ambient radii of the particles with
  8. ! sulphate, b/o carbon and dust.
  9. !
  10. ! Authors:
  11. ! --------
  12. ! J. Wilson and E. Vignati, JRC (original source) 05/2000
  13. ! P. Stier, MPI (f90-version, changes, comments) 2001
  14. !
  15. ! Purpose:
  16. ! --------
  17. ! This routine calculates the ambient radii for mixed particles without
  18. ! sea salt with mass of ttn molecules, converts them to count mean radii and
  19. ! stores them in the array with address pm6rp.
  20. ! It additionally calculates the ambient particle density.
  21. !
  22. ! Method:
  23. ! -------
  24. ! The calculations of the ambient particle properties are based on
  25. ! parameterisations of the mass of sulfate and density derived
  26. ! by Julian Wilson from a regression analysis of results of solving
  27. ! the generalised Kelvin equation using (F. J. Zeleznik, J. Phys. Chem.
  28. ! Ref. Data 20, 1157, 1991), for an H2SO4-H2O mixture, in the
  29. ! following parameter ranges:
  30. ! 1e2 < pttn < 1E11 [molecules]
  31. ! 0.2 < prelhum < 0.9 [1]
  32. ! 240 < ptp1 < 330 [K]
  33. ! 10000 < papp1 < 100000 [Pa]
  34. !
  35. ! Due to the limitations of the parametrisation, the ambient temperature
  36. ! is restricted to a minimum of 240 K within this subroutine.
  37. !
  38. ! For this application to mixed aerosols with an insoluble core we
  39. ! assume the H2O uptake by the particle to be that of a pure
  40. ! H2SO4 / H2O particle containing the H2SO4 mass of the mixed aerosol.
  41. !
  42. ! Interface:
  43. ! ----------
  44. ! *m7_equimix* is called from *m7*
  45. !
  46. ! Externals:
  47. ! ----------
  48. ! none
  49. !
  50. USE mo_aero_m7, ONLY: naermod, nmod, nsol, &
  51. ibcks, iocks, issas, ibcas, &
  52. iocas, iduas, isscs, ibccs, &
  53. ioccs, iducs, &
  54. wvb, gmb, avo, wh2so4,&
  55. pi, ram2cmr, &
  56. dbc, doc, ddust, dh2so4,&
  57. dh2o
  58. IMPLICIT NONE
  59. !
  60. ! pttn = average mass for single compound in each mode
  61. ! [in molec. for sulphate and in ug for bc, oc, ss, and dust]
  62. ! pm6rp = count mean radius under ambient conditions
  63. ! pm6dry = count mean radius under dry conditions
  64. ! paernl = aerosol number for each mode [cm-3]
  65. ! pww = aerosol water content for each mode [kg(water) m-3(air)]
  66. ! zwso4 = percentage by mass of sulfate in a H2O-H2SO4 particle
  67. ! containing pttn molecules of sulfate under ambient conditions
  68. ! zvso4 = volume of pttn molecules of sulfate [cm3]
  69. ! zmso4 = mass of pttn molecules of sulfate [g]
  70. ! zdso4h2o = density of sulfate-h2o fraction of a particle with average
  71. ! mass [g.cm-3]
  72. ! zmso4h2o = mass of sulfate-h2o fraction of a particle with average mass [g]
  73. ! zvso4h2o = volume of sulfate-h2o fraction of a particle with average
  74. ! mass [cm3]
  75. ! zinsvol = total volume of insoluble compounds in a single particle of
  76. ! average mass [cm3]
  77. ! zinsmass = total mass of insoluble compounds in a single
  78. ! particle of average mass [cm3]
  79. INTEGER :: kproma, kbdim, klev
  80. REAL :: papp1(kbdim,klev), ptp1(kbdim,klev), &
  81. prelhum(kbdim,klev)
  82. REAL :: pttn(kbdim,klev,naermod), prhop(kbdim,klev,nmod), &
  83. pm6dry(kbdim,klev,nsol), pm6rp(kbdim,klev,nmod), &
  84. pww(kbdim,klev,nmod), paernl(kbdim,klev,nmod)
  85. !
  86. ! Local variables:
  87. !
  88. INTEGER :: jk, jl, jmod
  89. REAL :: zseasalt, zinsvol, zinsmas, &
  90. zwso4, zvso4, zmso4, &
  91. zvso4h2o, zmso4h2o, zdso4h2o, &
  92. zapp1, zrh, ztk
  93. REAL :: zlnm2, zln3, zln32, ztk2, &
  94. zlnm, zss2
  95. !
  96. !
  97. !CDIR unroll=5
  98. DO 100 jmod=2,nsol
  99. DO 90 jk=1,klev
  100. DO 80 jl=1,kproma
  101. !--- 1) Split particle quantities into soluble (sea salt) and --------------
  102. ! non soluble (organic carbon + black carbon + dust) parts:
  103. ! (N.B. densities are assumed independent of temperature & pressure)
  104. SELECT CASE (jmod)
  105. CASE (2)
  106. zseasalt=0.
  107. zinsvol=1.e-6*(pttn(jl,jk,ibcks)/dbc+pttn(jl,jk,iocks)/doc)
  108. zinsmas=1.e-6*(pttn(jl,jk,ibcks)+pttn(jl,jk,iocks))
  109. CASE (3)
  110. zseasalt=pttn(jl,jk,issas)
  111. zinsvol=1.e-6*(pttn(jl,jk,ibcas)/dbc+pttn(jl,jk,iocas)/doc+ &
  112. pttn(jl,jk,iduas)/ddust)
  113. zinsmas=1.e-6*(pttn(jl,jk,ibcas)+pttn(jl,jk,iocas)+ &
  114. pttn(jl,jk,iduas))
  115. CASE (4)
  116. zseasalt=pttn(jl,jk,isscs)
  117. zinsvol=1.e-6*(pttn(jl,jk,ibccs)/dbc+pttn(jl,jk,ioccs)/doc+ &
  118. pttn(jl,jk,iducs)/ddust)
  119. zinsmas=1.e-6*(pttn(jl,jk,ibccs)+pttn(jl,jk,ioccs)+ &
  120. pttn(jl,jk,iducs))
  121. END SELECT
  122. !--- 2) Calculation of the particle properties in the absense of sea salt: --
  123. !
  124. IF (pttn(jl,jk,jmod) > 0.0 .AND. zinsvol > 0.0 .AND. zseasalt < 1.E-15 ) THEN
  125. !--- 2.1) Calculation of the ambient particle properties: ----------------
  126. !
  127. !--- Constrain ambient temperature and relative humidity to
  128. ! conditions for which the parametrisation of the liquid
  129. ! water content works:
  130. !
  131. ! Temperature:
  132. ztk = ptp1(jl,jk)
  133. ztk = MAX(ztk , 240.)
  134. ! Relative Humidity:
  135. zrh = prelhum(jl,jk)
  136. zrh = MAX(zrh , 0.05)
  137. zrh = MIN(zrh , 0.90)
  138. !--- Assign auxiliary variables:
  139. zapp1=papp1(jl,jk)
  140. zlnm = LOG(pttn(jl,jk,jmod))
  141. zlnm2 = zlnm*zlnm
  142. zss2 = zrh**2
  143. ztk2 = ztk*ztk
  144. zln3 = zlnm/3.0
  145. zln32 = zln3*zln3
  146. !--- Percentage by weight of sulfate in the particle [%]:
  147. ! (Here we ignore any insoluble mass.)
  148. zwso4 = wvb(1) + wvb(2)*zlnm + wvb(3)*zrh*zlnm + wvb(4)*ztk*zlnm + &
  149. wvb(5)*zrh/ztk + wvb(6)*zlnm2*zrh + wvb(7)*zlnm2*ztk + &
  150. wvb(8)*zlnm*zss2 + wvb(9)*zlnm*ztk2 + wvb(10)*zlnm2*zss2 + &
  151. wvb(11)*zlnm2*ztk2 + wvb(12)*zss2/ztk2 + wvb(13)*zlnm2 + &
  152. wvb(14)*zlnm2*zlnm + wvb(15)*zlnm2*zlnm2 + &
  153. wvb(16)*zss2*zrh/(ztk2*ztk) + wvb(17)*LOG(zrh*ztk/zapp1)
  154. !--- Dry mass of sulfate in an average particle [g]:
  155. zmso4 = pttn(jl,jk,jmod)*wh2so4/avo
  156. !--- Dry volume of sulfate in an average particle [cm3]:
  157. ! Any temperature or pressure dependency of the
  158. ! sulfate density is ingored.
  159. zvso4 = zmso4/dh2so4
  160. !--- Mass of sulfate + water in an average particle [g]:
  161. zmso4h2o = zmso4/(zwso4/100.0)
  162. !--- Density of the sulfate-water fraction of an average particle [g cm-3]:
  163. !@@@ Check: changed zwvso4 into zwso4 (now the mass!)
  164. zdso4h2o = gmb(1) + gmb(2)*zwso4 + gmb(3)*zln3 + gmb(4)*zrh + &
  165. gmb(5)*ztk + gmb(6)*zln32 + gmb(7)*zln3/zrh + &
  166. gmb(8)*zln3/ztk + gmb(9)*ztk2
  167. !--- Limits for zdso4h2o: H2O(0.99) and pure H2SO4 (1.841):
  168. !
  169. zdso4h2o=MAX(zdso4h2o,dh2o)
  170. zdso4h2o=MIN(zdso4h2o,dh2so4)
  171. !--- Volume of sulfate-water fraction of an average particle [cm3]:
  172. zvso4h2o = zmso4h2o/zdso4h2o
  173. !--- 2.2) Calculatiion of the particle radii: ----------------------------
  174. !--- 2.2.1) Dry count mean radius [cm]:
  175. pm6dry(jl,jk,jmod)=((zvso4+zinsvol)*0.75/pi)**(1./3.)*ram2cmr(jmod)
  176. !--- 2.2.2) Equilibrium wet count mean radius [cm]:
  177. pm6rp(jl,jk,jmod) =((zvso4h2o+zinsvol)*0.75/pi)**(1./3.)*ram2cmr(jmod)
  178. !--- 2.3) Calculation of the particle density [g cm-3]:-------------------
  179. prhop(jl,jk,jmod)=(zmso4h2o+zinsmas)/ &
  180. (zvso4h2o+zinsvol)
  181. !--- 2.4) Store aerosol water for each mode [kg(water) m-3(air)]:
  182. pww(jl,jk,jmod)=(zmso4h2o-zmso4)*paernl(jl,jk,jmod)*1.E3
  183. END IF
  184. 80 END DO
  185. 90 END DO
  186. 100 END DO
  187. END SUBROUTINE m7_equimix