mo_aero_m7.F90 24 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579
  1. #include "tm5.inc"
  2. MODULE mo_aero_m7
  3. ! *mo_aero_m7* Contains parameters, switches and initialization
  4. ! routines for the m7 aerosol scheme.
  5. !
  6. ! Authors:
  7. ! --------
  8. ! E. Vignati (JRC/IES) 2005
  9. ! P. Stier (MPI) 2001/2002
  10. ! E. Vignati and J. Wilson (JRC / EI) 2000
  11. IMPLICIT NONE
  12. SAVE
  13. !--- 1) Define and pre-set switches for the processes of M7: -----------------------
  14. !--- Physical:
  15. LOGICAL :: lsnucl = .TRUE., & ! nucleation
  16. lscoag = .TRUE., & ! coagulation
  17. lscond = .TRUE. ! condensation of H2SO4
  18. INTEGER :: nnucl = 1 ! Choice of the nucleation scheme:
  19. !
  20. ! nnucl = 1 Vehkamaeki (2002)
  21. ! = 2 Kulmala (1998) -NOT RECOMMENDED-
  22. !--- Technical:
  23. LOGICAL :: lmass_diag = .FALSE. ! mass balance check in m7_interface
  24. !--- 2) Numbers of compounds and modes of m7: --------------------------------------
  25. INTEGER, PARAMETER :: naermod=23, & !number of all compounds
  26. nmod=7, & !number of modes
  27. nss=2, & !number of sea salt compounds
  28. nsol=4, & !number of soluble compounds
  29. ngas=3, & !number of gaseous compounds
  30. nsulf=4,& !number of sulfate compounds
  31. ncomp=5 !number of compounds
  32. !--- 3) List of indexes corresponding to the compound masses and mode numbers:------
  33. !--- 3.1) Mass index (in array aerml and ttn):
  34. !
  35. ! Attention:
  36. ! The mass of sulfate compounds is always given in [molec. cm-3]
  37. ! whilst the mass of other compounds is given in [ug cm-3].
  38. !
  39. ! Compounds:
  40. !
  41. ! so4 = sulphate
  42. ! bc = black carbon
  43. ! oc = organic carbon,
  44. ! ss = sea salt
  45. ! du = dust
  46. !
  47. ! Modes:
  48. !
  49. ! n = nucleation mode
  50. ! k = aitken mode
  51. ! a = accumulation mode
  52. ! c = coarse mode
  53. !
  54. ! Type:
  55. !
  56. ! s = soluble mode
  57. ! i = insoluble mode
  58. ! COMPOUND:
  59. INTEGER, PARAMETER :: &
  60. iso4ns=1, iso4ks=2, iso4as=3, iso4cs=4, & !- Sulfate
  61. ibcks =5, ibcas =6, ibccs =7, ibcki =8, & !- Black Carbon
  62. iocks =9, iocas=10, ioccs=11, iocki=12, & !- Organic Carbon
  63. issas=13, isscs=14, & !- Sea Salt
  64. iduas=15, iducs=16, iduai=17, iduci=18,& !- Dust
  65. isoans=19,isoaks=20,isoaas=21,isoacs=22,isoaki=23 !- SOA
  66. ! MODE: | | | | |
  67. ! nucl. | aitk. | acc. | coar. | aitk. | acc. | coar. |
  68. ! soluble | soluble | soluble | soluble | insol. | insol. | insol. |
  69. !--- 3.2) Number index (in array aernl):
  70. !
  71. INTEGER, PARAMETER :: &
  72. inucs=1, iaits=2, iaccs=3, icoas=4, iaiti=5, iacci=6, icoai=7
  73. ! MODE: | | | | |
  74. ! nucl. | aitk. | acc. | coar. | aitk. | acc. | coar. |
  75. ! soluble | soluble | soluble | soluble | insol. | insol. | insol. |
  76. !--- 4) Definition of the modes of M7: ------------------------------------------------------
  77. !--- 4.1) Threshold radii between the different modes [cm]:
  78. ! Used for the repartititioning in m7_dconc.
  79. ! crdiv(jmod) is the lower bound and crdiv(jmod+1) is
  80. ! the upper bound of the respective geometric mode
  81. ! Default value for nucleation mode is modified by the
  82. ! choice of the nuclation scheme.
  83. REAL :: crdiv(4)=(/ 0.0005E-4, 0.005E-4, 0.05E-4, 0.5E-4 /)
  84. ! | | |
  85. ! | | |
  86. ! nucleation -- aitken - accum -- coarse mode
  87. !--- 4.2) Standard deviation for the modes:
  88. REAL, PARAMETER :: sigma(nmod)=(/ 1.59, 1.59, 1.59, 2.00, 1.59, 1.59, 2.00 /)
  89. !--- Natural logarithm of the standard deviation of each mode:
  90. ! Calulated in m7_initialize.
  91. REAL :: sigmaln(nmod)
  92. !--- 5) Conversion factors for lognormal particle size distributions: -------------
  93. ! Calulated in m7_initialize.
  94. REAL :: cmr2ras(nmod) ! Conversion factor: count median radius to radius of average surface
  95. REAL :: cmr2mmr(nmod) ! Conversion factor: count median radius to mass mean radius
  96. REAL :: cmedr2mmedr(nmod) ! Conversion factor: count median radius to mass median radius
  97. REAL :: cmr2ram(nmod) ! Conversion factor: count median radius to radius of average mass
  98. REAL :: ram2cmr(nmod) ! Conversion factor: radius of average mass to count median radius
  99. !--- 6) Assumed thresholds for occurence of specific quantities: -------------
  100. !@@@ To be done!
  101. ! REAL, PARAMETER :: cmin_aerml = 1.E-15 , ! Aerosol mass
  102. ! cmin_aernl = 1.E-10 , ! Aerosol number
  103. !
  104. !--- 7) Chemical constants: ----------------------------------------------------
  105. !
  106. !--- Accomodation coefficient of H2SO4 on aerosols:
  107. ! (reduced for insoluble modes)
  108. REAL, PARAMETER :: caccso4(nmod) = (/ 1.0, 1.0, 1.0, 1.0, 0.3, 0.3, 0.3 /)
  109. !--- Critical relative humidity:
  110. REAL, PARAMETER :: crh = 0.45 ! Assumed relative humidity for the
  111. ! Na2SO4 / NaCl system below which
  112. ! crystalization occurs.
  113. ! (estimated from Tang, I.N.; JGR 102, D2 1883-1893)
  114. !--- 8) Physical constants: ----------------------------------------------------
  115. !
  116. !--- 8.1) General physical constants:
  117. REAL, PARAMETER :: bk = 1.38e-16, & ! Bolzman constant []
  118. avo = 6.02217E+23,& ! Avogadro number [mol-1]
  119. rerg = 8.314E+7, & ! Ideal gas constant [erg.K-1.mole-1]
  120. r_kcal = 1.986E-3 ! Ideal gas constant [kcal K-1.mole-1]
  121. !--- 8.2) Type specific physical constants:
  122. !
  123. REAL, PARAMETER :: dh2so4 = 1.841, & ! Density H2SO4 [g cm-3]
  124. ddust = 2.650, & ! Density du [g cm-3]
  125. !>>> TvN
  126. ! The density of BC is in the range 1.7 to 1.9 g/cm3.
  127. ! (Bond and Bergstrom, Aerosol Sci. Technol., 2006).
  128. ! We therefore adopt a value of 1.8 g/cm3.
  129. ! Details can be found in Bond et al. (JGR, 2013),
  130. ! and references therein:
  131. ! Park et al. (J. Nanoparticle Research, 2004) measured
  132. ! 1.77 +- 0.07 g/cm3 for the non-volatile components of diesel soot,
  133. ! and give a range 1.7-1.8 g/cm3 in their conclusions.
  134. ! Kondo et al. (Aerosol Sci. Techn., 2011) measured
  135. ! 1.718 +- 0.004 g/cm3 for fullerene soot.
  136. ! Schmid et al. (Environ. Sci. Technol., 2009)
  137. ! derive a value 1.8 +- 0.2 g/cm3
  138. ! for elemental carbon from biomass burning.
  139. ! For comparison, in GLOMAP a value of 1.5 g/cm3 is used.
  140. ! Note that these density estimates measure the mass per volume
  141. ! occupied by the spherules, as should be the case:
  142. ! "If the radiative forcing of BC particles is to be
  143. ! calculated from their mass concentrations,
  144. ! as it is usually the case, density should represent
  145. ! the material density of the spherules, and not that
  146. ! of their ramiform (branched) or aciniform (packed) aggregates."
  147. ! (A. Gelencser, Carbonaceous Aerosol, Springer, 2004, p. 228).
  148. ! This is explained in more detail by Bond and Bergstrom
  149. ! (Aerosol Sci. Technol., 2005).
  150. !
  151. !dbc = 2., & ! Density bc [g cm-3]
  152. dbc = 1.8, & ! Density bc [g cm-3]
  153. ! The density of OA is highly variable,
  154. ! but in any case substantially lower than 2 g/cm3.
  155. ! We adopt an average value of 1.3 g/cm3,
  156. ! based on a number of studies:
  157. ! Turpin and Lim (Aerosol Sci. Technol., 2001)
  158. ! suggest that 1.2 g/cm3 is a reasonable estimate.
  159. ! Lee et al. (ACP, 2010) measured 1.26 +- 0.24 g/cm3
  160. ! at during FAME-2009 at Finokalia after evaporation
  161. ! Cross et al. (Aerosol Sci. Technol., 2007) assume an
  162. ! average bulk density of 1.27 g/cm3
  163. ! Nakao et al. (Atmos. Environ., 2013) measure average densities
  164. ! for SOA between 1.22 and 1.42 g/cm3, depending of species.
  165. ! This is in line with predictions from the OA density model
  166. ! by Kuwata et al. (Environ. Sci. Technol., 2012),
  167. ! who find a range between 1.23 and 1.46 g/cm3 for SOA.
  168. ! This model can be used to estimate OA density
  169. ! as function of O:C and H:C elemental ratios,
  170. ! with an accuracy of 12% or more.
  171. ! As a further simplication, it is often assumed that
  172. ! H:C = 2 - O:C (e.g. Murphy et al., ACP, 2011).
  173. ! The model, however, is restricted to particle components
  174. ! having negligible quantities of additional elements,
  175. ! most notably nitrogen.
  176. ! Schmid et al. (Environ. Sci. Technol., 2009)
  177. ! derive a value of 1.39 +- 0.13 for OA from biomass burning.
  178. !
  179. !doc = 2., & ! Density oc [g cm-3]
  180. doc = 1.3, & ! Density POM [g cm-3]
  181. !<<< TvN
  182. dnacl = 2.165, & ! Density NaCl [g cm-3]
  183. dna2so4 = 2.68, & ! Density Na2SO4 [g cm-3]
  184. dnahso4 = 2.435, & ! Density NaHSO4 [g cm-3]
  185. dh2o = 1.0, & ! Density H2O [g cm-3]
  186. wh2so4 = 98.0734, & ! Molecular weight H2SO4 [g mol-1]
  187. wh2o = 18.0, & ! Molecular weight H2O [g mol-1]
  188. wso4 = 96.0576, & ! Molecular weight SO4 [g mol-1]
  189. wso2 = 64.0, & ! Molecular weight SO2 [g mol-1]
  190. wna = 22.99, & ! Atomic weight Na [g mol-1]
  191. wcl = 35.453, & ! Atomic weight Cl [g mol-1]
  192. wnacl = 58.443, & ! Molecular weight NaCl [g mol-1]
  193. wna2so4 = 142.0376, & ! Molecular weight Na2SO4 [g mol-1]
  194. wnahso4 = 120.0555 ! Molecular weight NaHSO4 [g mol-1]
  195. !--- 9) Assumed parameters: ------------------------------------------------------
  196. REAL, PARAMETER :: critn=100., & ! Assumed mass of an nucleated sulfate
  197. ! particle for the Kulmala scheme [molecules]
  198. fmax=0.95, & ! Factor that limits the condensation
  199. ! of sulfate to fmax times the available
  200. ! sulfate in the gas phase [1].
  201. ! (m7_dgas)
  202. cLayerThickness = 1.0 ! Assumed required layer thickness of
  203. ! sulfate to transfer an insoluble
  204. ! particle to a soluble mode. It is
  205. ! given in units of layers of
  206. ! monomolecular sulfate. Determines the
  207. ! transfer rate from insoluble to
  208. ! soluble modes.
  209. !--- 10) Computational constants: ------------------------------------------------
  210. REAL, PARAMETER :: sqrt2=1.4142136, &
  211. pi=3.141592654
  212. !--- 11) Data used for the calculation of the aerosol properties -----------------
  213. ! under ambient conditions:
  214. ! (Included the conversion from Pa to hPa in the first parameter.)
  215. REAL, PARAMETER :: wvb(17)= &
  216. (/ 95.80188, -28.5257, -1.082153, 0.1466501, &
  217. -20627.51, 0.0461242, -0.003935, -3.36115, &
  218. -0.00024137, 0.067938345, 0.00000649899, 8616124.373, &
  219. 1.168155578, -0.021317481, 0.000270358, -1353332314.0, &
  220. -0.002403805 /)
  221. REAL, PARAMETER :: gmb(9)= &
  222. (/ 1.036391467, 0.00728531, -0.011013887, -0.068887407, &
  223. 0.001047842, 0.001049607, 0.000740534, -1.081202685, &
  224. -0.0000029113 /)
  225. !--- 4) Logical mask for coagulation kernel: -------------------------------------
  226. ! (The coagulation kernel mask is symmetric and not all
  227. ! values are used for physical considerations. As its
  228. ! calculation is very expensive, a mask is used to
  229. ! calculate only the necessarey elements.)
  230. LOGICAL :: locoagmask(nmod,nmod)
  231. DATA locoagmask(1:nmod,1) / .TRUE., .TRUE., .TRUE., .TRUE., .TRUE., .TRUE., .TRUE. /
  232. DATA locoagmask(1:nmod,2) / .FALSE., .TRUE., .TRUE., .TRUE., .TRUE., .TRUE., .TRUE. /
  233. DATA locoagmask(1:nmod,3) / .FALSE., .FALSE., .TRUE., .FALSE., .TRUE., .FALSE., .FALSE. /
  234. DATA locoagmask(1:nmod,4) / .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE. /
  235. DATA locoagmask(1:nmod,5) / .FALSE., .FALSE., .FALSE., .FALSE., .TRUE., .FALSE., .FALSE. /
  236. DATA locoagmask(1:nmod,6) / .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE. /
  237. DATA locoagmask(1:nmod,7) / .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE. /
  238. !--- 12) Service routines for initialization and auxiliary computations ----------
  239. CONTAINS
  240. SUBROUTINE m7_initialize
  241. ! Purpose:
  242. ! ---------
  243. ! Initializes constants and parameters
  244. ! used in the m7 aerosol model.
  245. !
  246. ! Author:
  247. ! ---------
  248. ! Philip Stier, MPI may 2001
  249. !
  250. ! Interface:
  251. ! ---------
  252. ! *m7_initialize* is called from *call_init_submodels* in *call_submodels*
  253. !
  254. IMPLICIT NONE
  255. INTEGER :: jmod
  256. DO jmod=1, nmod
  257. !--- 1) Calculate conversion factors for lognormal distributions:----
  258. ! Radius of average mass (ram) to count median radius (cmr) and
  259. ! vice versa. Count median radius to radius of average
  260. ! mass (ram).
  261. ! These factors depend on the standard deviation (sigma)
  262. ! of the lognormal distribution.
  263. ! (Based on the Hatch-Choate Conversins Equations;
  264. ! see Hinds, Chapter 4.5, 4.6 for more details.
  265. ! In particular equation 4.53.)
  266. !--- Count Median Radius to Mass Median Radius:
  267. cmedr2mmedr(jmod) = EXP(3.0*(LOG(sigma(jmod)))**2)
  268. !--- Count Median Radius to Mass Mean Radius:
  269. cmr2mmr(jmod) = EXP(3.5*(LOG(sigma(jmod)))**2)
  270. !--- Count Median Radius to Radius of Average Mass:
  271. cmr2ram(jmod) = EXP(1.5*(LOG(sigma(jmod)))**2)
  272. !--- Radius of Average Mass to Count Median Radius:
  273. ram2cmr(jmod) = 1. / cmr2ram(jmod)
  274. !--- Count Median Radius to Radius of Average Surface:
  275. cmr2ras(jmod) = EXP(1.0*(LOG(sigma(jmod)))**2)
  276. !--- 2) Calculate the natural logarithm of the standard deviation:
  277. sigmaln(jmod) = LOG(sigma(jmod))
  278. END DO
  279. !--- 3) Set the lower mode boundary for the nucleation mode:
  280. ! (Depends on the choice of the nucleation scheme.)
  281. SELECT CASE (nnucl)
  282. CASE(1)
  283. crdiv(1)=0.0005E-4
  284. CASE(2)
  285. crdiv(1)=( critn * wh2so4/avo/dh2so4*0.75/pi )**(1./3.)
  286. END SELECT
  287. !--------------------------------------------------------------------
  288. END SUBROUTINE m7_initialize
  289. SUBROUTINE m7_coat(pm6rp_lon_lev, pcrtcst)
  290. ! Purpose:
  291. ! ---------
  292. ! *m7_coat* calculates the number of sulfate
  293. ! molecules required to coat a particle
  294. ! with cLayerThickness of sulfate
  295. !
  296. ! Author:
  297. ! ---------
  298. ! Philip Stier, MPI 2001
  299. !
  300. ! Interface:
  301. ! ---------
  302. ! *m7_coat* is called from *m7_concoag*
  303. !
  304. IMPLICIT NONE
  305. INTEGER :: jmod
  306. REAL :: pm6rp_lon_lev(nmod) ! Ambient radii for current
  307. ! longitude and level [cm]
  308. REAL :: pcrtcst(nmod) ! Critical constant, i.e. number of
  309. ! sulfate to cover an average particle
  310. ! of the mode with a layer of the
  311. ! thickness determined by cLayerThickness.
  312. REAL :: zras(nmod) ! Radius of average surface
  313. ! for a single particle [cm]
  314. REAL :: zas(nmod) ! Average surface
  315. ! for single particle [cm+2]
  316. REAL, PARAMETER :: csurf_molec = 2.39E-15 ! Average cross-section
  317. ! of a single H2SO4 molecule [cm+2]
  318. !--- 1) Calculate the radii of average surface for modes 5-7:
  319. zras(5) = pm6rp_lon_lev(5) * cmr2ras(5)
  320. zras(6) = pm6rp_lon_lev(6) * cmr2ras(6)
  321. zras(7) = pm6rp_lon_lev(7) * cmr2ras(7)
  322. DO jmod=5, 7
  323. !--- 2) Calculate the average surface of an particle for modes 5-7:
  324. zas(jmod) = 4 * zras(jmod)**2 * pi
  325. !--- 3) Determine the number of sulfate molecules needed to form
  326. ! a cLayerThickness thick layer of sulfate on the particles
  327. ! in modes 5-7:
  328. pcrtcst(jmod) = (zas(jmod) / csurf_molec) * cLayerThickness
  329. END DO
  330. END SUBROUTINE m7_coat
  331. SUBROUTINE condensation_sink(NMODE,N,MEAN_IN,LAMBDA_IN,OUTPUT)
  332. !this is very approximative tool to calculate the division factors for organic condensation
  333. ! Assumes sigma = 1.5 (will underestimate condensation to coarse mode by factor of ~1-5)
  334. ! AA (2006)
  335. USE mo_kind,ONLY: dp
  336. INTEGER,INTENT(IN) :: NMODE !number of modes considered
  337. REAL(dp), DIMENSION(NMODE),INTENT(OUT) :: OUTPUT !output coefficients
  338. REAL(dp), DIMENSION(NMODE),INTENT(IN) :: N !number concentrations [arbitrary]
  339. REAL(dp), DIMENSION(NMODE),INTENT(IN) :: MEAN_IN !current geom median diameters of the modes [m]
  340. REAL(dp), INTENT(IN) :: LAMBDA_IN
  341. REAL(dp), DIMENSION(NMODE) :: MEAN
  342. REAL(dp) :: LAMBDA
  343. !local variables.
  344. REAL(dp), DIMENSION(3) :: COEF !the actual fit of CS to log10("mean")
  345. !fit of fit parameters in respect to log10(lambda)
  346. REAL(dp), DIMENSION(3), PARAMETER :: C1=(/ 0.0292 , 0.4376 , 1.5011/) !2nd order
  347. REAL(dp), DIMENSION(3), PARAMETER :: C2=(/0.4289 , 6.6937 , 25.4629/) !1st order
  348. REAL(dp), DIMENSION(3), PARAMETER :: C3=(/1.4346 , 23.0498 , 87.5852/) !0th order
  349. !REAL, DIMENSION(3) :: COEF_COARSE = (/
  350. !Note : CS is without the standard non-size dependent
  351. !factor of Diff*2*pi, which cancels out
  352. REAL(dp), DIMENSION(NMODE) :: CS,LMEAN
  353. REAL(dp) :: LLAM
  354. CONTINUE
  355. LAMBDA = LAMBDA_IN
  356. MEAN = MEAN_IN
  357. !Check parameter validity
  358. IF (LAMBDA>7.1220e-07) LAMBDA =7.1220e-07
  359. IF (LAMBDA<6.5100e-08) LAMBDA =6.5100e-08
  360. WHERE (MEAN<1e-10) MEAN = 1E-10
  361. WHERE (MEAN>10E-6) MEAN = 10E-6
  362. !logs
  363. LMEAN = LOG10(MEAN)
  364. LLAM = LOG10(LAMBDA)
  365. !coefficents
  366. COEF(1) = LLAM*(LLAM*C1(1) + C1(2)) + C1(3)
  367. COEF(2) = LLAM*(LLAM*C2(1) + C2(2)) + C2(3)
  368. COEF(3) = LLAM*(LLAM*C3(1) + C3(2)) + C3(3)
  369. !Cond-sink
  370. CS= 10**(LMEAN*(LMEAN*COEF(1)+COEF(2))+COEF(3))
  371. IF (SUM(N*CS) .GT. 1E-20) THEN
  372. OUTPUT = N*CS/SUM(N*CS)
  373. ELSE
  374. OUTPUT = 1./NMODE
  375. END IF
  376. END SUBROUTINE condensation_sink
  377. !!$ SUBROUTINE setaeroM7
  378. !!$
  379. !!$ ! *setaeroM7* modifies pre-set switches of the aeroM7ctl
  380. !!$ ! namelist for the configuration of the
  381. !!$ ! M7 component of the ECHAM/HAM aerosol model
  382. !!$ !
  383. !!$ ! Authors:
  384. !!$ ! --------
  385. !!$ ! Philip Stier, MPI-MET 12/2002
  386. !!$ !
  387. !!$ ! *setaeroM7* is called from *call_init_submodels* in *call_submodels*
  388. !!$ !
  389. !!$
  390. !!$ USE mo_mpi, ONLY: p_parallel, p_parallel_io, p_bcast, p_io
  391. !!$ USE mo_namelist, ONLY: position_nml, nnml, POSITIONED
  392. !!$ USE mo_doctor, ONLY: nout
  393. !!$ USE mo_exception, ONLY: finish
  394. !!$
  395. !!$ IMPLICIT NONE
  396. !!$
  397. !!$ INCLUDE 'aerom7ctl.inc'
  398. !!$
  399. !!$ !--- Local variables:
  400. !!$
  401. !!$ INTEGER :: ierr
  402. !!$
  403. !!$ !--- 1) Read namelist:
  404. !!$
  405. !!$ IF (p_parallel_io) THEN
  406. !!$ CALL position_nml ('AEROM7CTL', status=ierr)
  407. !!$ SELECT CASE (ierr)
  408. !!$ CASE (POSITIONED)
  409. !!$ READ (nnml, aerom7ctl)
  410. !!$ END SELECT
  411. !!$ ENDIF
  412. !!$
  413. !!$ !--- 2) Broadcast over processors:
  414. !!$
  415. !!$ IF (p_parallel) THEN
  416. !!$ CALL p_bcast (lsnucl, p_io)
  417. !!$ CALL p_bcast (lscoag, p_io)
  418. !!$ CALL p_bcast (lscond, p_io)
  419. !!$ CALL p_bcast (nnucl, p_io)
  420. !!$ CALL p_bcast (lmass_diag, p_io)
  421. !!$ END IF
  422. !!$
  423. !!$ IF (.NOT. p_parallel) THEN
  424. !!$ WRITE(nout,*) ''
  425. !!$ WRITE(nout,*) ''
  426. !!$ WRITE(nout,*) '----------------------------------------------------------'
  427. !!$ WRITE(nout,*) '----------------------------------------------------------'
  428. !!$ WRITE(nout,*) '--- Initialization of settings for aerosol module M7 ---'
  429. !!$ WRITE(nout,*) '---'
  430. !!$ WRITE(nout,*) '--- Default values of aeroctl modified by setaero:'
  431. !!$ WRITE(nout,*) '---'
  432. !!$ WRITE(nout,*) '--- New settings: lsnucl = ', lsnucl
  433. !!$ WRITE(nout,*) '--- lscoag = ', lscoag
  434. !!$ WRITE(nout,*) '--- lscond = ', lscond
  435. !!$ IF (nnucl==1) THEN
  436. !!$ WRITE(nout,*) '--- nnucl = ', nnucl
  437. !!$ WRITE(nout,*) '--- => Vehkamaeki et al., 2002'
  438. !!$ ELSE IF (nnucl==2) THEN
  439. !!$ WRITE(nout,*) '--- nnucl = ', nnucl
  440. !!$ WRITE(nout,*) '--- => Kulmala et al., 1998'
  441. !!$ ELSE IF (lsnucl .AND. (nnucl/=1 .OR. nnucl/=2)) THEN
  442. !!$ WRITE(nout,*) '--- Error:'
  443. !!$ CALL finish('setaerom7', 'nucleation requested but no scheme selected')
  444. !!$ END IF
  445. !!$ WRITE(nout,*) '---'
  446. !!$ IF (lmass_diag) THEN
  447. !!$ WRITE(nout,*) '--- Mass balance check in m7_interface activated'
  448. !!$ ELSE
  449. !!$ WRITE(nout,*) '--- Mass balance check in m7_interface deactivated'
  450. !!$ END IF
  451. !!$ WRITE(nout,*) '---'
  452. !!$ WRITE(nout,*) '----------------------------------------------------------'
  453. !!$ WRITE(nout,*) '----------------------------------------------------------'
  454. !!$ WRITE(nout,*) ''
  455. !!$ WRITE(nout,*) ''
  456. !!$ END IF
  457. !!$
  458. !!$ END SUBROUTINE setaeroM7
  459. END MODULE mo_aero_m7