mo_aero.F90 25 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516
  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. !
  59. nsoa = 2 ! SOA formation scheme:
  60. !
  61. ! nsoa = 0 POM mass emission into both Aitken modes (standard TM5)
  62. ! 1 POM mass emission + distribution according to volatility assumptions to 5 modes
  63. ! 2 atmospheric formation from precursors + distribution according to volatility assumptions to 5 modes
  64. LOGICAL :: lodiag = .FALSE. ! Extended diagnostics
  65. LOGICAL :: laero_rad = .FALSE. ! Radiation calculation
  66. LOGICAL :: lorad(nmod) = .FALSE. ! switch for each mode
  67. LOGICAL :: lodiagrad = .FALSE. ! Extended radiation diagnostics
  68. INTEGER :: nwv = 0 ! nwv: number of additional wavelengths
  69. ! for the radiation calculations
  70. ! (max currently set to 10)
  71. REAL :: cwv(10) = 0. ! cwv: array of additional wavelengths
  72. ! for the radiation calculations [m]
  73. LOGICAL :: lomassfix = .TRUE. ! Mass fixer in convective scheme
  74. !--- 1.2) Technical:
  75. !!$ INTEGER :: NFILETYPE = GRIB ! Output stream filetypes
  76. !--- 2) Parameters:
  77. !-- 2.1) Number of aerosol compounds: (needs to be harmonized with nmode in mo_aero_m7)
  78. INTEGER, PARAMETER :: ntype=6
  79. !--- 2.2) Mode names:
  80. CHARACTER(LEN=2), PARAMETER :: cmode(nmod)=(/'NS','KS','AS','CS','KI','AI','CI'/)
  81. !--- 2.3) Compound names:
  82. CHARACTER(LEN=3), PARAMETER :: ctype(ntype)=(/'SO4','BC ','OC ','SS ','DU ','WAT'/)
  83. !--- 2.4) Index field of tracer indices for the aerosol numbers in each mode:
  84. INTEGER :: nindex(nmod)
  85. !--- 2.5) Emissions:
  86. !--- Carbon Emissions
  87. ! REAL, PARAMETER :: zbb_wsoc_perc = 0.65, & ! Biom. Burn. Percentage of Water Soluble OC (WSOC) [1]
  88. ! (M.O. Andreae; Talk: Smoke and Climate)
  89. REAL, PARAMETER :: zbb_wsoc_perc = 0.95, & ! TB:
  90. ! To reduce the AOD over china and outflow region of
  91. ! Africa the water soluble fraction was increasde to 95%
  92. ! in preparation for CMIP6.
  93. !
  94. ! Some basis for the choice can be found here:
  95. ! e (e.g. Janhall et al., 2010;
  96. ! https://doi.org/10.5194/acp-10-1427-2010 ; Winijkul et al., 2015;
  97. ! https://doi.org/10.1016/j.atmosenv.2015.02.037; Li et al., 2009;
  98. ! https://pubs.acs.org/doi/abs/10.1021/es803330j).
  99. zbge_wsoc_perc = 0.65, & ! Assume same Percentage of WSOC for biogenic OC
  100. !>>> TvN
  101. ! The value of 1.4 for the POM to OC mass ratio is an outdated estimate.
  102. ! In the current code we can apply different ratios
  103. ! for emissions from different sources.
  104. ! For further details, see comment in emission_data.F90.
  105. ! The use of a single constant value, on the other hand,
  106. ! would have the advantage that the simulated POM concentrations
  107. ! can easily be converted to OC.
  108. ! An average value of 1.8 seems reasonable.
  109. ! Assuming that there are no substantial contributions from
  110. ! elements other than H and O, a value of 1.8 can be obtained
  111. ! with an H:C atomic ratio of 1.6 and and O:C ratio of 0.5,
  112. ! which are well within the range of oxidation states
  113. ! presented by Heald et al. (GRL, 2010).
  114. ! According to the model of Kuwata et al. (Environ. Sci. Technol., 2012),
  115. ! the resulting particle density would be close to the value
  116. ! assumed in the model (doc = 1.3 g/cm3 in mo_aero_m7.F90).
  117. !zom2oc = 1.4, & ! Mass ratio organic species to organic carbon
  118. ! (Seinfeld and Pandis, 1998, p709;
  119. ! Ferek et al., JGR, 1998)
  120. !
  121. ! The emission radii for carbonaceous aerosols of the original code below
  122. ! correspond to the values recommended by AeroCom (Dentener et al., ACP, 2006),
  123. ! but adapted to sigma = 1.59 as used in M7 (Stier et al., ACP, 2005).
  124. cmr_ff = 0.03E-6, & ! Fossil fuel emissions:
  125. ! assumed number median radius of the emitted
  126. ! particles with the standard deviation given
  127. ! in mo_aero_m7 [m]. Has to lie within the
  128. ! Aitken mode for the current setup!
  129. cmr_bb = 0.075E-6, & ! Biomass burning emissions:
  130. ! Assumed number median radius of the emitted
  131. ! particles with the standard deviation given
  132. ! in mo_aero_m7 [m]. Has to lie within the
  133. ! Accumulation mode for the current setup!
  134. cmr_bg = 0.03E-6, &! Biogenic secondary particle formation:
  135. ! Assumed number median radius of the emitted
  136. ! particles with the standard deviation given
  137. ! in mo_aero_m7 [m]. Has to lie within the
  138. ! Aitken mode for the current setup!
  139. cmr_sk = 0.03E-6, &! SO4 primary emission ---> aitken mode
  140. ! Assumed number median radius of the emitted
  141. ! particles with the standard deviation given
  142. ! in mo_aero_m7 [m]. Has to lie within the
  143. ! Aitken mode for the current setup!
  144. cmr_sa = 0.075E-6, &! SO4 primary emission ---> accumulation mode
  145. ! Assumed number median radius of the emitted
  146. ! particles with the standard deviation given
  147. ! in mo_aero_m7 [m]. Has to lie within the
  148. ! Accumulation mode for the current setup!
  149. cmr_sc = 0.75E-6, &! SO4 primary emission ---> coarse mode
  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. ! Coarse mode for the current setup!
  154. facso2 = 0.975, &! factor to scale primary SO4 emissions
  155. ! AEROCOM assumption 2.5 % of the SO2 emissions
  156. ! in the from of SO4
  157. so2ts = 1./1.998 ! conversion factor SO2 to S
  158. REAL, PUBLIC :: zm2n_bcki_ff, zm2n_bcki_bb, &
  159. zm2n_bcks_bb, zm2n_ocki_ff, &
  160. zm2n_ocki_bb, zm2n_ocki_bg, &
  161. zm2n_ocks_bb, zm2n_ocks_bg, &
  162. zm2n_s4ks_sk, zm2n_s4as_sa, &
  163. zm2n_s4cs_sc
  164. !!$CONTAINS
  165. !!$
  166. !!$
  167. !!$ SUBROUTINE aero_initialize
  168. !!$
  169. !!$ ! Purpose:
  170. !!$ ! ---------
  171. !!$ ! Initializes constants and parameters
  172. !!$ ! used in the HAM aerosol model.
  173. !!$ ! Performs consistency checks.
  174. !!$ !
  175. !!$ ! Author:
  176. !!$ ! ---------
  177. !!$ ! Philip Stier, MPI 03/2003
  178. !!$ !
  179. !!$ ! Interface:
  180. !!$ ! ---------
  181. !!$ ! *aero_initialize* is called from *call_init_submodels* in *call_submodels*
  182. !!$ ! needs to be called after initialization of the
  183. !!$ ! submodel as it makes use of parameters in mo_aero_m7
  184. !!$ !
  185. !!$
  186. !!$ USE mo_tracer, ONLY: flag, ntrac, trlist, AEROSOLNUMBER
  187. !!$ USE mo_constants, ONLY: api
  188. !!$ USE mo_radiation, ONLY: iaero
  189. !!$ USE mo_mpi, ONLY: p_parallel_io
  190. !!$ USE mo_doctor, ONLY: nout
  191. !!$ USE mo_exception, ONLY: finish
  192. !!$ USE mo_aero_m7, ONLY: cmr2ram
  193. !!$ USE mo_aero_trac, ONLY: idt_mbcki, idt_mbcks, &
  194. !!$ idt_mocki, idt_mocks, &
  195. !!$ idt_ms4ks, idt_ms4as, &
  196. !!$ idt_ms4cs
  197. !!$ USE mo_aero_m7, ONLY: iaiti, iaits, iaccs, icoas
  198. !!$
  199. !!$ IMPLICIT NONE
  200. !!$
  201. !!$ INTEGER :: jwv, jmod, jt
  202. !!$
  203. !!$ !--- 1) Consistency checks:
  204. !!$
  205. !!$ !--- 1.1) Radiation:
  206. !!$
  207. !!$ IF (nwv > 10 ) &
  208. !!$ CALL finish('aero_initialize','maximal number of additional wavelengths exceeded')
  209. !!$
  210. !!$ IF (iaero==4 .AND. ANY(lorad(:))) THEN
  211. !!$ laero_rad=.TRUE.
  212. !!$ ELSE IF (iaero/=4 .AND. ANY(lorad(:))) THEN
  213. !!$ CALL finish('aero_initialize','inconsistent setting of iaero in radctl')
  214. !!$ ELSE IF (iaero==4 .AND. .NOT.ANY(lorad(:))) THEN
  215. !!$ CALL finish('aero_initialize','inconsistent setting of iaero and lorad')
  216. !!$ END IF
  217. !!$
  218. !!$ !--- 1.2) Output type:
  219. !!$
  220. !!$ IF(nfiletype/=GRIB .AND. nfiletype/=NETCDF) THEN
  221. !!$ CALL finish('aero_initialize','selected output filetype not supported')
  222. !!$ END IF
  223. !!$
  224. !!$ !--- 2) Consistency checks and display of information:
  225. !!$
  226. !!$ IF (p_parallel_io) THEN
  227. !!$ WRITE(nout,*) ''
  228. !!$ WRITE(nout,*) ''
  229. !!$ WRITE(nout,*) '----------------------------------------------------------'
  230. !!$ WRITE(nout,*) '----------------------------------------------------------'
  231. !!$ WRITE(nout,*) '--- Initialization of the ECHAM/HAM aerosol model ---'
  232. !!$ WRITE(nout,*) '---'
  233. !!$ WRITE(nout,*) '--- Default values of aeroctl modified by setaero:'
  234. !!$ WRITE(nout,*) '---'
  235. !!$ WRITE(nout,*) '--- New settings: lm7 = ', lm7
  236. !!$ WRITE(nout,*) '--- ncdnc = ', ncdnc
  237. !!$ IF (ncdnc==0) THEN
  238. !!$ WRITE(nout,*) '--- => no aerosol-CDNC coupling'
  239. !!$ ELSE IF (ncdnc==1) THEN
  240. !!$ WRITE(nout,*) '--- => Lohmann et al. (1999) +'
  241. !!$ WRITE(nout,*) '--- Lin and Leaitch (1997)'
  242. !!$ ELSE IF (ncdnc==2) THEN
  243. !!$ WRITE(nout,*) '--- => Lohmann et al. (1999) +'
  244. !!$ WRITE(nout,*) '--- Abdul-Razzak and Ghan (2000)'
  245. !!$ END IF
  246. !!$ WRITE(nout,*) '--- nicnc = ', nicnc
  247. !!$ IF (nicnc==0) THEN
  248. !!$ WRITE(nout,*) '--- => no aerosol-ICNC coupling'
  249. !!$ ELSE IF (ncdnc>0 .AND. nicnc==1) THEN
  250. !!$ WRITE(nout,*) '--- => Kaercher and Lohmann (2002)'
  251. !!$ ELSE IF (ncdnc==0 .AND. nicnc>0) THEN
  252. !!$ WRITE(nout,*) '--- => ICNC scheme requires CDNC scheme!'
  253. !!$ CALL finish('aero_initialize','inconsistent combination of ncdnc and nicnc')
  254. !!$ END IF
  255. !!$ WRITE(nout,*) '--- nauto = ', nauto
  256. !!$ WRITE(nout,*) '--- => Autoconversion scheme:'
  257. !!$ IF (nauto==1) THEN
  258. !!$ WRITE(nout,*) '--- Beheng (1994) - ECHAM5 Standard'
  259. !!$ ELSE IF (nauto==2 .AND. ncdnc>0) THEN
  260. !!$ WRITE(nout,*) '--- Khairoutdinov and Kogan (2000)'
  261. !!$ ELSE IF (nauto==2 .AND. ncdnc==0) THEN
  262. !!$ WRITE(nout,*) '--- Khairoutdinov and Kogan (2000)'
  263. !!$ WRITE(nout,*) '--- scheme requires CDNC scheme!'
  264. !!$ CALL finish('aero_initialize','inconsistent combination of nauto and ncdnc')
  265. !!$ ELSE
  266. !!$ CALL finish('aero_initialize','invalid setting for nauto')
  267. !!$ END IF
  268. !!$ WRITE(nout,*) '--- ndust = ', ndust
  269. !!$ IF (ndust==1) THEN
  270. !!$ WRITE(nout,*) '--- => Balkanski et al. (2002)'
  271. !!$ ELSE IF (ndust==2) THEN
  272. !!$ WRITE(nout,*) '--- => Tegen et al. (2002)'
  273. !!$ IF (lcolumn) THEN
  274. !!$ WRITE(nout,*) '--- WARNING:'
  275. !!$ WRITE(nout,*) '--- This dust emission scheme '
  276. !!$ WRITE(nout,*) '--- does not work in SCM mode!'
  277. !!$ WRITE(nout,*) '--- Dust emissions deactivated!'
  278. !!$ ndust=0
  279. !!$ WRITE(nout,*) '--- => ndust = ', ndust
  280. !!$ END IF !lcolumn
  281. !!$ ELSE IF (ndust==0) THEN
  282. !!$ WRITE(nout,*) '--- => DUST EMISSIONS DEACTIVATED!'
  283. !!$ END IF
  284. !!$ WRITE(nout,*) '--- nseasalt = ', nseasalt
  285. !!$ IF (nseasalt==1) THEN
  286. !!$ WRITE(nout,*) '--- => Monahan (1986)'
  287. !!$ ELSE IF (nseasalt==2) THEN
  288. !!$ WRITE(nout,*) '--- => Schulz et al. (2002)'
  289. !!$ ELSE IF (nseasalt==0) THEN
  290. !!$ WRITE(nout,*) '--- => SEASALT EMISSIONS DEACTIVATED!'
  291. !!$ END IF
  292. !!$ WRITE(nout,*) '--- npist = ', npist
  293. !!$ IF (npist==1) THEN
  294. !!$ WRITE(nout,*) '--- => Air-sea exchange:'
  295. !!$ WRITE(nout,*) '--- Liss & Merlivat (1986)'
  296. !!$ ELSE IF (npist==2) THEN
  297. !!$ WRITE(nout,*) '--- => Air-sea exchange:'
  298. !!$ WRITE(nout,*) '--- Wanninkhof (1992)'
  299. !!$ ELSE IF (npist==3) THEN
  300. !!$ WRITE(nout,*) '--- => Air-sea exchange:'
  301. !!$ WRITE(nout,*) '--- Nightingale (2000)'
  302. !!$ END IF
  303. !!$ WRITE(nout,*) '--- nemiss = ', nemiss
  304. !!$ IF (nemiss==1) THEN
  305. !!$ WRITE(nout,*) '--- => 1985 emission data'
  306. !!$ ELSE IF (nemiss==2) THEN
  307. !!$ WRITE(nout,*) '--- => AEROCOM emissions 2000'
  308. !!$ END IF
  309. !!$ IF (lodiag) THEN
  310. !!$ WRITE(nout,*) '--- lodiag = ', lodiag
  311. !!$ WRITE(nout,*) '--- => Aerosol diagnostics activated'
  312. !!$ ELSE
  313. !!$ WRITE(nout,*) '--- lodiag = ', lodiag
  314. !!$ WRITE(nout,*) '--- => Aerosol diagnostics deactivated'
  315. !!$ END IF
  316. !!$ IF (laero_rad) THEN
  317. !!$ WRITE(nout,*) '--- lorad = ', lorad
  318. !!$ WRITE(nout,*) '--- => Radiation calculation for:'
  319. !!$ WRITE(nout,*) '---'
  320. !!$ DO jmod=1, nmod
  321. !!$ IF (lorad(jmod)) THEN
  322. !!$ WRITE(nout,*) '--- Mode ', jmod
  323. !!$ END IF
  324. !!$ END DO
  325. !!$ WRITE(nout,*) '---'
  326. !!$ IF (nwv>0) THEN
  327. !!$ WRITE(nout,*) '--- nwv = ', nwv
  328. !!$ WRITE(nout,*) '--- => Additional wavelengs requested:'
  329. !!$ WRITE(nout,*) '---'
  330. !!$ DO jwv=1, nwv
  331. !!$ WRITE(nout,fmt="(A,E8.2,A)") '--- ',cwv(jwv), ' [m]'
  332. !!$ END DO
  333. !!$ END IF
  334. !!$ ELSE
  335. !!$ WRITE(nout,*) '--- Radiation calculations deactivated!'
  336. !!$ END IF
  337. !!$ IF (lodiagrad) THEN
  338. !!$ WRITE(nout,*) '--- lodiagrad = ', lodiagrad
  339. !!$ WRITE(nout,*) '--- => Extended radiation diagnostics!'
  340. !!$ END IF
  341. !!$ WRITE(nout,*) '---'
  342. !!$ IF(lomassfix) THEN
  343. !!$ WRITE(nout,*) '--- Mass fixer in convection activated!'
  344. !!$ ELSE
  345. !!$ WRITE(nout,*) '--- Mass fixer in convection deactivated!'
  346. !!$ END IF
  347. !!$ WRITE(nout,*) '---'
  348. !!$ IF(nfiletype==GRIB) THEN
  349. !!$ WRITE(nout,*) '--- Output filetype set to GRIB'
  350. !!$ ELSE IF(nfiletype==NETCDF) THEN
  351. !!$ WRITE(nout,*) '--- Output filetype set to NetCDF'
  352. !!$ END IF
  353. !!$ END IF
  354. !!$
  355. !!$ !--- 2) Initialize constants and parameters:
  356. !!$
  357. !!$ !--- 2.1) Emissions
  358. !!$ ! Calculate factors to convert mass flux in number flux for
  359. !!$ ! given number median radii (cmr) and standard deviation
  360. !!$ ! (implicitly by the conversion factor cmr2ram) of the modes
  361. !!$ !
  362. !!$ ! N = M/m = M/(4/3 * pi * dens * R(averageMass)**3)
  363. !!$ ! = M * (3/(4*pi*dens*R(averageMass)))
  364. !!$ ! !
  365. !!$ ! = M * zm2n_xx
  366. !!$
  367. !!$ zm2n_bcki_ff=3./(4.*api*flag('density',idt_mbcki)*(cmr_ff*cmr2ram(iaiti))**3.)
  368. !!$ zm2n_bcki_bb=3./(4.*api*flag('density',idt_mbcki)*(cmr_bb*cmr2ram(iaiti))**3.)
  369. !!$
  370. !!$ zm2n_bcks_bb=3./(4.*api*flag('density',idt_mbcks)*(cmr_bb*cmr2ram(iaits))**3.)
  371. !!$
  372. !!$ zm2n_ocki_ff=3./(4.*api*flag('density',idt_mocki)*(cmr_ff*cmr2ram(iaiti))**3.)
  373. !!$ zm2n_ocki_bb=3./(4.*api*flag('density',idt_mocki)*(cmr_bb*cmr2ram(iaiti))**3.)
  374. !!$ zm2n_ocki_bg=3./(4.*api*flag('density',idt_mocki)*(cmr_bg*cmr2ram(iaiti))**3.)
  375. !!$
  376. !!$ zm2n_ocks_bb=3./(4.*api*flag('density',idt_mocks)*(cmr_bb*cmr2ram(iaits))**3.)
  377. !!$ zm2n_ocks_bg=3./(4.*api*flag('density',idt_mocks)*(cmr_bg*cmr2ram(iaits))**3.)
  378. !!$
  379. !!$ !??????????????
  380. !!$ zm2n_s4ks_sk=3./(4.*api*flag('density',idt_ms4ks)*(cmr_sk*cmr2ram(iaits))**3.)
  381. !!$ zm2n_s4as_sa=3./(4.*api*flag('density',idt_ms4as)*(cmr_sa*cmr2ram(iaccs))**3.)
  382. !!$ zm2n_s4cs_sc=3./(4.*api*flag('density',idt_ms4cs)*(cmr_sc*cmr2ram(icoas))**3.)
  383. !!$ !????????????
  384. !!$
  385. !!$ !--- 3) Set up index matrices for access of tracer by compound and mode:
  386. !!$
  387. !!$ IF (p_parallel_io) THEN
  388. !!$ WRITE(nout,*) '---'
  389. !!$ WRITE(nout,*) '--- Mapping of ECHAM tracers HAM mode-indices:'
  390. !!$ WRITE(nout,*) '---'
  391. !!$ END IF
  392. !!$
  393. !!$ DO jmod=1, nmod
  394. !!$ DO jt=1, ntrac
  395. !!$ IF(trlist%ti(jt)%nphase==AEROSOLNUMBER .AND. trlist%ti(jt)%mode==jmod) THEN
  396. !!$ nindex(jmod)=jt
  397. !!$ IF (p_parallel_io) THEN
  398. !!$ WRITE(nout,*) '--- ', TRIM(trlist%ti(jt)%fullname),': ', jmod
  399. !!$ END IF
  400. !!$ CYCLE
  401. !!$ END IF
  402. !!$ END DO
  403. !!$ END DO
  404. !!$
  405. !!$ !--- 4) Finish:
  406. !!$
  407. !!$ IF (p_parallel_io) THEN
  408. !!$ WRITE(nout,*) '---'
  409. !!$ WRITE(nout,*) '--- Parameters for ECHAM5-HAM initialized ---'
  410. !!$ WRITE(nout,*) '----------------------------------------------------------'
  411. !!$ WRITE(nout,*) '----------------------------------------------------------'
  412. !!$ WRITE(nout,*) ''
  413. !!$ WRITE(nout,*) ''
  414. !!$ END IF
  415. !!$ END SUBROUTINE aero_initialize
  416. !!$
  417. !!$
  418. !!$ SUBROUTINE setaero
  419. !!$
  420. !!$ ! *setaero* modifies pre-set switches of the aeroctl
  421. !!$ ! namelist for the configuration of the
  422. !!$ ! ECHAM/HAM aerosol model
  423. !!$ !
  424. !!$ ! Authors:
  425. !!$ ! --------
  426. !!$ ! Philip Stier, MPI-MET 12/2002
  427. !!$ !
  428. !!$ ! *setaero* is called from *call_init_submodels* in *call_submodels*
  429. !!$ !
  430. !!$
  431. !!$ USE mo_mpi, ONLY: p_parallel, p_parallel_io, p_bcast, p_io
  432. !!$ USE mo_namelist, ONLY: position_nml, nnml, POSITIONED
  433. !!$
  434. !!$ IMPLICIT NONE
  435. !!$
  436. !!$ INCLUDE 'aeroctl.inc'
  437. !!$
  438. !!$ !--- Local variables:
  439. !!$
  440. !!$ INTEGER :: ierr
  441. !!$
  442. !!$ !--- 1) Read namelist:
  443. !!$
  444. !!$ IF (p_parallel_io) THEN
  445. !!$ CALL position_nml ('AEROCTL', status=ierr)
  446. !!$ SELECT CASE (ierr)
  447. !!$ CASE (POSITIONED)
  448. !!$ READ (nnml, aeroctl)
  449. !!$ END SELECT
  450. !!$ ENDIF
  451. !!$
  452. !!$ !--- 2) Broadcast over processors:
  453. !!$
  454. !!$ IF (p_parallel) THEN
  455. !!$ CALL p_bcast (lm7, p_io)
  456. !!$ CALL p_bcast (ncdnc, p_io)
  457. !!$ CALL p_bcast (nicnc, p_io)
  458. !!$ CALL p_bcast (nauto, p_io)
  459. !!$ CALL p_bcast (ndust, p_io)
  460. !!$ CALL p_bcast (nseasalt, p_io)
  461. !!$ CALL p_bcast (npist, p_io)
  462. !!$ CALL p_bcast (nemiss, p_io)
  463. !!$ CALL p_bcast (lodiag, p_io)
  464. !!$ CALL p_bcast (nfiletype, p_io)
  465. !!$ CALL p_bcast (lorad, p_io)
  466. !!$ CALL p_bcast (lodiagrad, p_io)
  467. !!$ CALL p_bcast (nwv, p_io)
  468. !!$ CALL p_bcast (cwv, p_io)
  469. !!$ CALL p_bcast (lomassfix, p_io)
  470. !!$ END IF
  471. !!$
  472. !!$ END SUBROUTINE setaero
  473. END MODULE mo_aero