mo_aero.F90 26 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537
  1. #include "tm5.inc"
  2. MODULE mo_aero
  3. ! *mo_aero* contains phyiscal switches and parameters
  4. ! for the ECHAM/HAM aerosol model.
  5. !
  6. ! Author:
  7. ! -------
  8. ! Philip Stier, MPI-MET 12/2002
  9. !
  10. !!$ USE mo_linked_list, ONLY: NETCDF, GRIB
  11. USE mo_aero_m7, ONLY: nmod
  12. !!$ USE mo_control, ONLY: lcolumn
  13. IMPLICIT NONE
  14. !--- 0) Submodel ID:
  15. INTEGER :: id_ham
  16. !--- 1) Switches:
  17. !--- 1.1) Physical:
  18. !--- Define control variables and pre-set with default values:
  19. LOGICAL :: lm7 = .TRUE. ! Aerosol dynamics and thermodynamics scheme M7
  20. INTEGER :: ncdnc = 0, & ! CDNC activation scheme:
  21. !
  22. ! ncdnc = 0 OFF => standard ECHAM5
  23. !
  24. ! = 1 Lohmann et al. (1999) + Lin and Leaitch (1997)
  25. ! = 2 Lohmann et al. (1999) + Abdul-Razzak and Ghan (2000)
  26. ! = 3 Lohmann et al. (1999) + ( Nenes et al. (2003) )
  27. !
  28. nicnc = 0, & ! ICNC scheme:
  29. !
  30. ! ncdnc = 0 OFF
  31. ! = 1 Kaercher and Lohmann (2002)
  32. !
  33. nauto = 1, & ! Autoconversion scheme:
  34. !
  35. ! nauto = 1 Beheng (1994) - ECHAM5 Standard
  36. ! = 2 Khairoutdinov and Kogan (2000)
  37. !
  38. ndust = 2, & ! Dust emission scheme:
  39. !
  40. ! ndust = 1 Balkanski et al. (2002)
  41. ! = 2 Tegen et al. (2002)
  42. !
  43. nseasalt = 2, & ! Sea Salt emission scheme:
  44. !
  45. ! nseasalt = 1 Monahan (1986)
  46. ! = 2 Schulz et al. (2002)
  47. !
  48. npist = 3, & ! DMS emission scheme:
  49. !
  50. ! npist = 1 Liss & Merlivat (1986)
  51. ! = 2 Wanninkhof (1992)
  52. ! = 3 Nightingale (2000)
  53. !
  54. nemiss = 1 ! Emission inventory
  55. !
  56. ! nemiss =1 old version
  57. ! nemiss =2 AEROCOM emissions 2000
  58. LOGICAL :: lodiag = .FALSE. ! Extended diagnostics
  59. LOGICAL :: laero_rad = .FALSE. ! Radiation calculation
  60. LOGICAL :: lorad(nmod) = .FALSE. ! switch for each mode
  61. LOGICAL :: lodiagrad = .FALSE. ! Extended radiation diagnostics
  62. INTEGER :: nwv = 0 ! nwv: number of additional wavelengths
  63. ! for the radiation calculations
  64. ! (max currently set to 10)
  65. REAL :: cwv(10) = 0. ! cwv: array of additional wavelengths
  66. ! for the radiation calculations [m]
  67. LOGICAL :: lomassfix = .TRUE. ! Mass fixer in convective scheme
  68. !--- 1.2) Technical:
  69. !!$ INTEGER :: NFILETYPE = GRIB ! Output stream filetypes
  70. !--- 2) Parameters:
  71. !-- 2.1) Number of aerosol compounds: (needs to be harmonized with nmode in mo_aero_m7)
  72. INTEGER, PARAMETER :: ntype=6
  73. !--- 2.2) Mode names:
  74. CHARACTER(LEN=2), PARAMETER :: cmode(nmod)=(/'NS','KS','AS','CS','KI','AI','CI'/)
  75. !--- 2.3) Compound names:
  76. CHARACTER(LEN=3), PARAMETER :: ctype(ntype)=(/'SO4','BC ','OC ','SS ','DU ','WAT'/)
  77. !--- 2.4) Index field of tracer indices for the aerosol numbers in each mode:
  78. INTEGER :: nindex(nmod)
  79. !--- 2.5) Emissions:
  80. !--- Carbon Emissions
  81. REAL, PARAMETER :: zbb_wsoc_perc = 0.65, & ! Biom. Burn. Percentage of Water Soluble OC (WSOC) [1]
  82. ! (M.O. Andreae; Talk: Smoke and Climate)
  83. zbge_wsoc_perc = 0.65, & ! Assume same Percentage of WSOC for biogenic OC
  84. !>>> TvN
  85. ! The value of 1.4 for the POM to OC mass ratio is an outdated estimate.
  86. ! In the current code we apply different ratios
  87. ! for emissions from vegetation fires and other emissions.
  88. ! For further details, see comment in emission_data.F90.
  89. ! The use of a single constant value, on the other hand,
  90. ! would have the advantage that the simulated POM concentrations
  91. ! can easily be converted to OC.
  92. ! An average value of 1.8 seems reasonable.
  93. ! Assuming that there are no substantial contributions from
  94. ! elements other than H and O, a value of 1.8 can be obtained
  95. ! with an H:C atomic ratio of 1.6 and and O:C ratio of 0.5,
  96. ! which are well within the range of oxidation states
  97. ! presented by Heald et al. (GRL, 2010).
  98. ! According to the model of Kuwata et al. (Environ. Sci. Technol., 2012),
  99. ! the resulting particle density would be close to the value
  100. ! assumed in the model (doc = 1.3 g/cm3 in mo_aero_m7.F90).
  101. !zom2oc = 1.4, & ! Mass ratio organic species to organic carbon
  102. ! (Seinfeld and Pandis, 1998, p709;
  103. ! Ferek et al., JGR, 1998)
  104. !
  105. ! The emission radii for carbonaceous aerosols of the original code below
  106. ! correspond to the values recommended by AeroCom (Dentener et al., ACP, 2006),
  107. ! but adapted to sigma = 1.59 as used in M7 (Stier et al., ACP, 2005).
  108. ! See also Figure C2 from Dentener et al. for a linear relation
  109. ! between emission radius and sigma.
  110. !
  111. ! For comparison, Bond et al. (JGR, 2013) give number median radii
  112. ! between 25 and 40 nm for fresh BC in the urban areas
  113. ! of Tokyo, Nagoya, and Seoul,
  114. ! of 60 nm in plumes associated with wildfires,
  115. ! and about 15 nm from aircraft jet engines.
  116. ! These values are volume-equivalent radii (see their Fig. 4).
  117. !
  118. ! According to the original paper by Schwarz et al. (GRL, 2008)
  119. ! the corresponding geometric standard deviation
  120. ! is sigma = 1.71 for the urban BC
  121. ! and 1.43 for the biomass burning aerosol.
  122. !
  123. ! For BC in biomass burning plumes,
  124. ! Kondo et al (JGR, 2011) estimated
  125. ! number median radii in the range 68-70.5 nm (+- 6-8 nm)
  126. ! and geometric standard deviation between 1.32 and 1.36 (+- 0.01-0.04),
  127. ! for particles thickly coated by organics.
  128. !
  129. ! Janhaell et al. (ACP, 2010) have compiled measurements of
  130. ! particle size in fresh biomass burning smoke from vegetation fires.
  131. ! They mention that particles from biomass burning are dominated
  132. ! by an accumulation mode.
  133. ! They also present a relation between the geometric mean diameter Dg
  134. ! and geometric standard deviation sigma for fresh smoke:
  135. ! Dg (um) = (584 +- 5) - (269 +-1) sigma
  136. ! This gives a geometric mean radius of 78 um for sigma = 1.59,
  137. ! in close agreement with the value used by Stier et al.
  138. ! Particles emitted by grass and savannah fires are generally
  139. ! somewhat smaller than those from wood burning.
  140. ! Janhaell et al. estimate that the mean emission radii
  141. ! for grass and savannah fires, resp., are 12.5 and 10 nm smaller.
  142. ! These differences is not accounted for in the model.
  143. !
  144. ! In a later version of ECHAM-HAM particles the emission radius
  145. ! for biomass burning was reduced to the value for fossil fuel
  146. ! (Zhang et al., ACP, 2012).
  147. ! However, such as a small value seems inconsistent with measurements.
  148. !
  149. cmr_ff = 0.03E-6, & ! Fossil fuel emissions:
  150. ! assumed number median radius of the emitted
  151. ! particles with the standard deviation given
  152. ! in mo_aero_m7 [m]. Has to lie within the
  153. ! Aitken mode for the current setup!
  154. cmr_bb = 0.075E-6, & ! Biomass burning emissions:
  155. ! Assumed number median radius of the emitted
  156. ! particles with the standard deviation given
  157. ! in mo_aero_m7 [m]. Has to lie within the
  158. ! Accumulation mode for the current setup!
  159. cmr_bg = 0.03E-6, &! Biogenic secondary particle formation:
  160. ! Assumed number median radius of the emitted
  161. ! particles with the standard deviation given
  162. ! in mo_aero_m7 [m]. Has to lie within the
  163. ! Aitken mode for the current setup!
  164. cmr_sk = 0.03E-6, &! SO4 primary emission ---> aitken mode
  165. ! Assumed number median radius of the emitted
  166. ! particles with the standard deviation given
  167. ! in mo_aero_m7 [m]. Has to lie within the
  168. ! Aitken mode for the current setup!
  169. cmr_sa = 0.075E-6, &! SO4 primary emission ---> accumulation mode
  170. ! Assumed number median radius of the emitted
  171. ! particles with the standard deviation given
  172. ! in mo_aero_m7 [m]. Has to lie within the
  173. ! Accumulation mode for the current setup!
  174. cmr_sc = 0.75E-6, &! SO4 primary emission ---> coarse mode
  175. ! Assumed number median radius of the emitted
  176. ! particles with the standard deviation given
  177. ! in mo_aero_m7 [m]. Has to lie within the
  178. ! Coarse mode for the current setup!
  179. facso2 = 0.975, &! factor to scale primary SO4 emissions
  180. ! AEROCOM assumption 2.5 % of the SO2 emissions
  181. ! in the from of SO4
  182. so2ts = 1./1.998 ! conversion factor SO2 to S
  183. REAL, PUBLIC :: zm2n_bcki_ff, zm2n_bcki_bb, &
  184. zm2n_bcks_bb, zm2n_ocki_ff, &
  185. zm2n_ocki_bb, zm2n_ocki_bg, &
  186. zm2n_ocks_bb, zm2n_ocks_bg, &
  187. zm2n_s4ks_sk, zm2n_s4as_sa, &
  188. zm2n_s4cs_sc
  189. !!$CONTAINS
  190. !!$
  191. !!$
  192. !!$ SUBROUTINE aero_initialize
  193. !!$
  194. !!$ ! Purpose:
  195. !!$ ! ---------
  196. !!$ ! Initializes constants and parameters
  197. !!$ ! used in the HAM aerosol model.
  198. !!$ ! Performs consistency checks.
  199. !!$ !
  200. !!$ ! Author:
  201. !!$ ! ---------
  202. !!$ ! Philip Stier, MPI 03/2003
  203. !!$ !
  204. !!$ ! Interface:
  205. !!$ ! ---------
  206. !!$ ! *aero_initialize* is called from *call_init_submodels* in *call_submodels*
  207. !!$ ! needs to be called after initialization of the
  208. !!$ ! submodel as it makes use of parameters in mo_aero_m7
  209. !!$ !
  210. !!$
  211. !!$ USE mo_tracer, ONLY: flag, ntrac, trlist, AEROSOLNUMBER
  212. !!$ USE mo_constants, ONLY: api
  213. !!$ USE mo_radiation, ONLY: iaero
  214. !!$ USE mo_mpi, ONLY: p_parallel_io
  215. !!$ USE mo_doctor, ONLY: nout
  216. !!$ USE mo_exception, ONLY: finish
  217. !!$ USE mo_aero_m7, ONLY: cmr2ram
  218. !!$ USE mo_aero_trac, ONLY: idt_mbcki, idt_mbcks, &
  219. !!$ idt_mocki, idt_mocks, &
  220. !!$ idt_ms4ks, idt_ms4as, &
  221. !!$ idt_ms4cs
  222. !!$ USE mo_aero_m7, ONLY: iaiti, iaits, iaccs, icoas
  223. !!$
  224. !!$ IMPLICIT NONE
  225. !!$
  226. !!$ INTEGER :: jwv, jmod, jt
  227. !!$
  228. !!$ !--- 1) Consistency checks:
  229. !!$
  230. !!$ !--- 1.1) Radiation:
  231. !!$
  232. !!$ IF (nwv > 10 ) &
  233. !!$ CALL finish('aero_initialize','maximal number of additional wavelengths exceeded')
  234. !!$
  235. !!$ IF (iaero==4 .AND. ANY(lorad(:))) THEN
  236. !!$ laero_rad=.TRUE.
  237. !!$ ELSE IF (iaero/=4 .AND. ANY(lorad(:))) THEN
  238. !!$ CALL finish('aero_initialize','inconsistent setting of iaero in radctl')
  239. !!$ ELSE IF (iaero==4 .AND. .NOT.ANY(lorad(:))) THEN
  240. !!$ CALL finish('aero_initialize','inconsistent setting of iaero and lorad')
  241. !!$ END IF
  242. !!$
  243. !!$ !--- 1.2) Output type:
  244. !!$
  245. !!$ IF(nfiletype/=GRIB .AND. nfiletype/=NETCDF) THEN
  246. !!$ CALL finish('aero_initialize','selected output filetype not supported')
  247. !!$ END IF
  248. !!$
  249. !!$ !--- 2) Consistency checks and display of information:
  250. !!$
  251. !!$ IF (p_parallel_io) THEN
  252. !!$ WRITE(nout,*) ''
  253. !!$ WRITE(nout,*) ''
  254. !!$ WRITE(nout,*) '----------------------------------------------------------'
  255. !!$ WRITE(nout,*) '----------------------------------------------------------'
  256. !!$ WRITE(nout,*) '--- Initialization of the ECHAM/HAM aerosol model ---'
  257. !!$ WRITE(nout,*) '---'
  258. !!$ WRITE(nout,*) '--- Default values of aeroctl modified by setaero:'
  259. !!$ WRITE(nout,*) '---'
  260. !!$ WRITE(nout,*) '--- New settings: lm7 = ', lm7
  261. !!$ WRITE(nout,*) '--- ncdnc = ', ncdnc
  262. !!$ IF (ncdnc==0) THEN
  263. !!$ WRITE(nout,*) '--- => no aerosol-CDNC coupling'
  264. !!$ ELSE IF (ncdnc==1) THEN
  265. !!$ WRITE(nout,*) '--- => Lohmann et al. (1999) +'
  266. !!$ WRITE(nout,*) '--- Lin and Leaitch (1997)'
  267. !!$ ELSE IF (ncdnc==2) THEN
  268. !!$ WRITE(nout,*) '--- => Lohmann et al. (1999) +'
  269. !!$ WRITE(nout,*) '--- Abdul-Razzak and Ghan (2000)'
  270. !!$ END IF
  271. !!$ WRITE(nout,*) '--- nicnc = ', nicnc
  272. !!$ IF (nicnc==0) THEN
  273. !!$ WRITE(nout,*) '--- => no aerosol-ICNC coupling'
  274. !!$ ELSE IF (ncdnc>0 .AND. nicnc==1) THEN
  275. !!$ WRITE(nout,*) '--- => Kaercher and Lohmann (2002)'
  276. !!$ ELSE IF (ncdnc==0 .AND. nicnc>0) THEN
  277. !!$ WRITE(nout,*) '--- => ICNC scheme requires CDNC scheme!'
  278. !!$ CALL finish('aero_initialize','inconsistent combination of ncdnc and nicnc')
  279. !!$ END IF
  280. !!$ WRITE(nout,*) '--- nauto = ', nauto
  281. !!$ WRITE(nout,*) '--- => Autoconversion scheme:'
  282. !!$ IF (nauto==1) THEN
  283. !!$ WRITE(nout,*) '--- Beheng (1994) - ECHAM5 Standard'
  284. !!$ ELSE IF (nauto==2 .AND. ncdnc>0) THEN
  285. !!$ WRITE(nout,*) '--- Khairoutdinov and Kogan (2000)'
  286. !!$ ELSE IF (nauto==2 .AND. ncdnc==0) THEN
  287. !!$ WRITE(nout,*) '--- Khairoutdinov and Kogan (2000)'
  288. !!$ WRITE(nout,*) '--- scheme requires CDNC scheme!'
  289. !!$ CALL finish('aero_initialize','inconsistent combination of nauto and ncdnc')
  290. !!$ ELSE
  291. !!$ CALL finish('aero_initialize','invalid setting for nauto')
  292. !!$ END IF
  293. !!$ WRITE(nout,*) '--- ndust = ', ndust
  294. !!$ IF (ndust==1) THEN
  295. !!$ WRITE(nout,*) '--- => Balkanski et al. (2002)'
  296. !!$ ELSE IF (ndust==2) THEN
  297. !!$ WRITE(nout,*) '--- => Tegen et al. (2002)'
  298. !!$ IF (lcolumn) THEN
  299. !!$ WRITE(nout,*) '--- WARNING:'
  300. !!$ WRITE(nout,*) '--- This dust emission scheme '
  301. !!$ WRITE(nout,*) '--- does not work in SCM mode!'
  302. !!$ WRITE(nout,*) '--- Dust emissions deactivated!'
  303. !!$ ndust=0
  304. !!$ WRITE(nout,*) '--- => ndust = ', ndust
  305. !!$ END IF !lcolumn
  306. !!$ ELSE IF (ndust==0) THEN
  307. !!$ WRITE(nout,*) '--- => DUST EMISSIONS DEACTIVATED!'
  308. !!$ END IF
  309. !!$ WRITE(nout,*) '--- nseasalt = ', nseasalt
  310. !!$ IF (nseasalt==1) THEN
  311. !!$ WRITE(nout,*) '--- => Monahan (1986)'
  312. !!$ ELSE IF (nseasalt==2) THEN
  313. !!$ WRITE(nout,*) '--- => Schulz et al. (2002)'
  314. !!$ ELSE IF (nseasalt==0) THEN
  315. !!$ WRITE(nout,*) '--- => SEASALT EMISSIONS DEACTIVATED!'
  316. !!$ END IF
  317. !!$ WRITE(nout,*) '--- npist = ', npist
  318. !!$ IF (npist==1) THEN
  319. !!$ WRITE(nout,*) '--- => Air-sea exchange:'
  320. !!$ WRITE(nout,*) '--- Liss & Merlivat (1986)'
  321. !!$ ELSE IF (npist==2) THEN
  322. !!$ WRITE(nout,*) '--- => Air-sea exchange:'
  323. !!$ WRITE(nout,*) '--- Wanninkhof (1992)'
  324. !!$ ELSE IF (npist==3) THEN
  325. !!$ WRITE(nout,*) '--- => Air-sea exchange:'
  326. !!$ WRITE(nout,*) '--- Nightingale (2000)'
  327. !!$ END IF
  328. !!$ WRITE(nout,*) '--- nemiss = ', nemiss
  329. !!$ IF (nemiss==1) THEN
  330. !!$ WRITE(nout,*) '--- => 1985 emission data'
  331. !!$ ELSE IF (nemiss==2) THEN
  332. !!$ WRITE(nout,*) '--- => AEROCOM emissions 2000'
  333. !!$ END IF
  334. !!$ IF (lodiag) THEN
  335. !!$ WRITE(nout,*) '--- lodiag = ', lodiag
  336. !!$ WRITE(nout,*) '--- => Aerosol diagnostics activated'
  337. !!$ ELSE
  338. !!$ WRITE(nout,*) '--- lodiag = ', lodiag
  339. !!$ WRITE(nout,*) '--- => Aerosol diagnostics deactivated'
  340. !!$ END IF
  341. !!$ IF (laero_rad) THEN
  342. !!$ WRITE(nout,*) '--- lorad = ', lorad
  343. !!$ WRITE(nout,*) '--- => Radiation calculation for:'
  344. !!$ WRITE(nout,*) '---'
  345. !!$ DO jmod=1, nmod
  346. !!$ IF (lorad(jmod)) THEN
  347. !!$ WRITE(nout,*) '--- Mode ', jmod
  348. !!$ END IF
  349. !!$ END DO
  350. !!$ WRITE(nout,*) '---'
  351. !!$ IF (nwv>0) THEN
  352. !!$ WRITE(nout,*) '--- nwv = ', nwv
  353. !!$ WRITE(nout,*) '--- => Additional wavelengs requested:'
  354. !!$ WRITE(nout,*) '---'
  355. !!$ DO jwv=1, nwv
  356. !!$ WRITE(nout,fmt="(A,E8.2,A)") '--- ',cwv(jwv), ' [m]'
  357. !!$ END DO
  358. !!$ END IF
  359. !!$ ELSE
  360. !!$ WRITE(nout,*) '--- Radiation calculations deactivated!'
  361. !!$ END IF
  362. !!$ IF (lodiagrad) THEN
  363. !!$ WRITE(nout,*) '--- lodiagrad = ', lodiagrad
  364. !!$ WRITE(nout,*) '--- => Extended radiation diagnostics!'
  365. !!$ END IF
  366. !!$ WRITE(nout,*) '---'
  367. !!$ IF(lomassfix) THEN
  368. !!$ WRITE(nout,*) '--- Mass fixer in convection activated!'
  369. !!$ ELSE
  370. !!$ WRITE(nout,*) '--- Mass fixer in convection deactivated!'
  371. !!$ END IF
  372. !!$ WRITE(nout,*) '---'
  373. !!$ IF(nfiletype==GRIB) THEN
  374. !!$ WRITE(nout,*) '--- Output filetype set to GRIB'
  375. !!$ ELSE IF(nfiletype==NETCDF) THEN
  376. !!$ WRITE(nout,*) '--- Output filetype set to NetCDF'
  377. !!$ END IF
  378. !!$ END IF
  379. !!$
  380. !!$ !--- 2) Initialize constants and parameters:
  381. !!$
  382. !!$ !--- 2.1) Emissions
  383. !!$ ! Calculate factors to convert mass flux in number flux for
  384. !!$ ! given number median radii (cmr) and standard deviation
  385. !!$ ! (implicitly by the conversion factor cmr2ram) of the modes
  386. !!$ !
  387. !!$ ! N = M/m = M/(4/3 * pi * dens * R(averageMass)**3)
  388. !!$ ! = M * (3/(4*pi*dens*R(averageMass)))
  389. !!$ ! !
  390. !!$ ! = M * zm2n_xx
  391. !!$
  392. !!$ zm2n_bcki_ff=3./(4.*api*flag('density',idt_mbcki)*(cmr_ff*cmr2ram(iaiti))**3.)
  393. !!$ zm2n_bcki_bb=3./(4.*api*flag('density',idt_mbcki)*(cmr_bb*cmr2ram(iaiti))**3.)
  394. !!$
  395. !!$ zm2n_bcks_bb=3./(4.*api*flag('density',idt_mbcks)*(cmr_bb*cmr2ram(iaits))**3.)
  396. !!$
  397. !!$ zm2n_ocki_ff=3./(4.*api*flag('density',idt_mocki)*(cmr_ff*cmr2ram(iaiti))**3.)
  398. !!$ zm2n_ocki_bb=3./(4.*api*flag('density',idt_mocki)*(cmr_bb*cmr2ram(iaiti))**3.)
  399. !!$ zm2n_ocki_bg=3./(4.*api*flag('density',idt_mocki)*(cmr_bg*cmr2ram(iaiti))**3.)
  400. !!$
  401. !!$ zm2n_ocks_bb=3./(4.*api*flag('density',idt_mocks)*(cmr_bb*cmr2ram(iaits))**3.)
  402. !!$ zm2n_ocks_bg=3./(4.*api*flag('density',idt_mocks)*(cmr_bg*cmr2ram(iaits))**3.)
  403. !!$
  404. !!$ !??????????????
  405. !!$ zm2n_s4ks_sk=3./(4.*api*flag('density',idt_ms4ks)*(cmr_sk*cmr2ram(iaits))**3.)
  406. !!$ zm2n_s4as_sa=3./(4.*api*flag('density',idt_ms4as)*(cmr_sa*cmr2ram(iaccs))**3.)
  407. !!$ zm2n_s4cs_sc=3./(4.*api*flag('density',idt_ms4cs)*(cmr_sc*cmr2ram(icoas))**3.)
  408. !!$ !????????????
  409. !!$
  410. !!$ !--- 3) Set up index matrices for access of tracer by compound and mode:
  411. !!$
  412. !!$ IF (p_parallel_io) THEN
  413. !!$ WRITE(nout,*) '---'
  414. !!$ WRITE(nout,*) '--- Mapping of ECHAM tracers HAM mode-indices:'
  415. !!$ WRITE(nout,*) '---'
  416. !!$ END IF
  417. !!$
  418. !!$ DO jmod=1, nmod
  419. !!$ DO jt=1, ntrac
  420. !!$ IF(trlist%ti(jt)%nphase==AEROSOLNUMBER .AND. trlist%ti(jt)%mode==jmod) THEN
  421. !!$ nindex(jmod)=jt
  422. !!$ IF (p_parallel_io) THEN
  423. !!$ WRITE(nout,*) '--- ', TRIM(trlist%ti(jt)%fullname),': ', jmod
  424. !!$ END IF
  425. !!$ CYCLE
  426. !!$ END IF
  427. !!$ END DO
  428. !!$ END DO
  429. !!$
  430. !!$ !--- 4) Finish:
  431. !!$
  432. !!$ IF (p_parallel_io) THEN
  433. !!$ WRITE(nout,*) '---'
  434. !!$ WRITE(nout,*) '--- Parameters for ECHAM5-HAM initialized ---'
  435. !!$ WRITE(nout,*) '----------------------------------------------------------'
  436. !!$ WRITE(nout,*) '----------------------------------------------------------'
  437. !!$ WRITE(nout,*) ''
  438. !!$ WRITE(nout,*) ''
  439. !!$ END IF
  440. !!$ END SUBROUTINE aero_initialize
  441. !!$
  442. !!$
  443. !!$ SUBROUTINE setaero
  444. !!$
  445. !!$ ! *setaero* modifies pre-set switches of the aeroctl
  446. !!$ ! namelist for the configuration of the
  447. !!$ ! ECHAM/HAM aerosol model
  448. !!$ !
  449. !!$ ! Authors:
  450. !!$ ! --------
  451. !!$ ! Philip Stier, MPI-MET 12/2002
  452. !!$ !
  453. !!$ ! *setaero* is called from *call_init_submodels* in *call_submodels*
  454. !!$ !
  455. !!$
  456. !!$ USE mo_mpi, ONLY: p_parallel, p_parallel_io, p_bcast, p_io
  457. !!$ USE mo_namelist, ONLY: position_nml, nnml, POSITIONED
  458. !!$
  459. !!$ IMPLICIT NONE
  460. !!$
  461. !!$ INCLUDE 'aeroctl.inc'
  462. !!$
  463. !!$ !--- Local variables:
  464. !!$
  465. !!$ INTEGER :: ierr
  466. !!$
  467. !!$ !--- 1) Read namelist:
  468. !!$
  469. !!$ IF (p_parallel_io) THEN
  470. !!$ CALL position_nml ('AEROCTL', status=ierr)
  471. !!$ SELECT CASE (ierr)
  472. !!$ CASE (POSITIONED)
  473. !!$ READ (nnml, aeroctl)
  474. !!$ END SELECT
  475. !!$ ENDIF
  476. !!$
  477. !!$ !--- 2) Broadcast over processors:
  478. !!$
  479. !!$ IF (p_parallel) THEN
  480. !!$ CALL p_bcast (lm7, p_io)
  481. !!$ CALL p_bcast (ncdnc, p_io)
  482. !!$ CALL p_bcast (nicnc, p_io)
  483. !!$ CALL p_bcast (nauto, p_io)
  484. !!$ CALL p_bcast (ndust, p_io)
  485. !!$ CALL p_bcast (nseasalt, p_io)
  486. !!$ CALL p_bcast (npist, p_io)
  487. !!$ CALL p_bcast (nemiss, p_io)
  488. !!$ CALL p_bcast (lodiag, p_io)
  489. !!$ CALL p_bcast (nfiletype, p_io)
  490. !!$ CALL p_bcast (lorad, p_io)
  491. !!$ CALL p_bcast (lodiagrad, p_io)
  492. !!$ CALL p_bcast (nwv, p_io)
  493. !!$ CALL p_bcast (cwv, p_io)
  494. !!$ CALL p_bcast (lomassfix, p_io)
  495. !!$ END IF
  496. !!$
  497. !!$ END SUBROUTINE setaero
  498. END MODULE mo_aero