ebischeme.F90 68 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665
  1. #define TRACEBACK write (gol,'("in ",a," (",a,i6,")")') rname, __FILE__, __LINE__ ; call goErr
  2. #define IF_NOTOK_RETURN(action) if (status/=0) then; TRACEBACK; action; return; end if
  3. #define IF_ERROR_RETURN(action) if (status> 0) then; TRACEBACK; action; return; end if
  4. !
  5. #include "tm5.inc"
  6. !
  7. !-----------------------------------------------------------------------------
  8. ! TM5 !
  9. !-----------------------------------------------------------------------------
  10. !BOP
  11. !
  12. ! !MODULE: EBISCHEME
  13. !
  14. ! !DESCRIPTION: Eulerian Backward Iteration (EBI) is a chemistry solver for
  15. ! the CBM4 scheme.
  16. !\\
  17. !\\
  18. ! !INTERFACE:
  19. !
  20. module EBISCHEME
  21. !
  22. ! !USES:
  23. !
  24. use GO, only : gol, goPr, goErr
  25. use dims, only : nregions
  26. use tm5_distgrid, only : dgrid, Get_DistGrid
  27. use chem_param
  28. #ifdef with_budgets
  29. use budget_global, only : nbudg, nbud_vg
  30. use reaction_data, only : nreac, nreacw
  31. use photolysis_data, only : nj
  32. #endif
  33. implicit none
  34. private
  35. !
  36. ! !PUBLIC MEMBER FUNCTIONS:
  37. !
  38. public :: EBI
  39. !
  40. ! !PUBLIC DATA MEMBERS:
  41. !
  42. #ifdef with_budgets
  43. real, dimension(nregions), public :: sum_wetchem
  44. real, dimension(nregions), public :: sum_chemistry
  45. real, dimension(nregions), public :: sum_deposition
  46. type, public :: buddep_data
  47. real, dimension(:,:,:), pointer :: dry ! i,j,ntrace
  48. end type buddep_data
  49. type(buddep_data), dimension(nregions), public :: buddep_dat
  50. real, dimension(nbudg, nbud_vg, nreac ), public :: budrrg
  51. real, dimension(nbudg, nbud_vg, nj ), public :: budrjg
  52. real, dimension(nbudg, nbud_vg, nreacw), public :: budrwg
  53. real, dimension(nbudg, nbud_vg, nmark ), public :: budmarkg
  54. #endif
  55. character(len=*), parameter :: mname = 'ebischeme'
  56. !
  57. ! !REVISION HISTORY:
  58. !
  59. ! Feb 2007 - Elisabetta Vignati - changed for inclusion of cloud chemistry on modes
  60. ! 22 Mar 2012 - Philippe Le Sager - adapted for lon-lat MPI domain decomposition
  61. !
  62. ! !REMARKS:
  63. ! (1) initializations are made in chemistry/chemistry_init
  64. !
  65. ! !TODO : FIXME check sum_chemistry and sum_deposition
  66. !
  67. !EOP
  68. !------------------------------------------------------------------------
  69. contains
  70. !--------------------------------------------------------------------------
  71. ! TM5 !
  72. !--------------------------------------------------------------------------
  73. !BOP
  74. !
  75. ! !IROUTINE: EBI
  76. !
  77. ! !DESCRIPTION: perform Eulerian backwards chemistry at one model layer
  78. ! level in one region
  79. !\\
  80. !\\
  81. ! !INTERFACE:
  82. !
  83. subroutine EBI( region, level, is, js, rj, rr, y, ye, status)
  84. !
  85. ! !USES:
  86. !
  87. use dims, only : im, jm, nchem, tref, okdebug
  88. use Dims, only : CheckShape
  89. use global_data, only : region_dat
  90. #ifndef without_dry_deposition
  91. use dry_deposition, only : vd
  92. #endif
  93. !
  94. ! !INPUT PARAMETERS:
  95. !
  96. integer, intent(in) :: region, level, is, js
  97. real, intent(in) :: rr(is:,js:,:) ! array of reaction rates
  98. real, intent(in) :: rj(is:,js:,:) ! array of photolysis rates
  99. !
  100. ! !INPUT/OUTPUT PARAMETERS:
  101. !
  102. real, intent(inout) :: y(is:,js:,:) ! array of concentration
  103. real, intent(inout) :: ye(is:,js:,:)
  104. !
  105. ! !OUTPUT PARAMETERS:
  106. !
  107. integer, intent(out) :: status
  108. !
  109. ! !REVISION HISTORY:
  110. ! 22 Mar 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  111. !
  112. !EOP
  113. !------------------------------------------------------------------------
  114. !BOC
  115. character(len=*), parameter :: rname = mname//'/ebi'
  116. #ifdef with_zoom
  117. integer, dimension(:,:), pointer :: zoomed
  118. #endif
  119. #ifdef with_budgets
  120. real, dimension(:,:,:), allocatable :: cr2, cr3, cr4 ! reaction budgets
  121. #endif
  122. real, dimension(:,:,:), allocatable :: y0
  123. real :: dtime, dt, dt2, fnoy
  124. integer :: iterebi, i, j, ib, maxit
  125. integer :: io, sfstart, sfend
  126. ! For vectorization/blocking ....
  127. ! npts can be varied to optimize cache memory management.
  128. integer, parameter :: npts=15
  129. integer, dimension(npts) :: ipts, jpts
  130. real, dimension(npts, nreac ) :: rrv
  131. real, dimension(npts, nj ) :: rjv
  132. real, dimension(npts, ntrace) :: vdv ! deposition velocities
  133. real, dimension(npts) :: emino
  134. real, dimension(npts, maxtrace) :: yv, y0v
  135. integer :: iv, itrace, ivt, n
  136. integer :: i1, j1, i2, j2
  137. ! --- BEGIN --------------------------------
  138. call Get_DistGrid( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  139. ! check arguments ...
  140. call CheckShape( (/i2-i1+1, j2-j1+1, nreac /), shape(rr), status )
  141. IF_NOTOK_RETURN(status=1)
  142. call CheckShape( (/i2-i1+1, j2-j1+1, nj /), shape(rj), status )
  143. IF_NOTOK_RETURN(status=1)
  144. call CheckShape( (/i2-i1+1, j2-j1+1, maxtrace/), shape(y ), status )
  145. IF_NOTOK_RETURN(status=1)
  146. call CheckShape( (/i2-i1+1, j2-j1+1, n_extra /), shape(ye), status )
  147. IF_NOTOK_RETURN(status=1)
  148. #ifdef with_zoom
  149. zoomed => region_dat(region)%zoomed
  150. #endif
  151. dtime=nchem/(2*tref(region))
  152. !CMK iterebi=max(1,nint(dtime/2400)) !needed if nchem <2400
  153. iterebi=max(1,nint(dtime/1350)) !needed if nchem <2400
  154. dt=dtime/iterebi
  155. allocate( y0 (i1:i2, j1:j2, maxtrace))
  156. #ifdef with_budgets
  157. allocate( cr2(i1:i2, j1:j2, nj ))
  158. allocate( cr3(i1:i2, j1:j2, nreac ))
  159. allocate( cr4(i1:i2, j1:j2, nreacw ))
  160. #endif
  161. !*** SCALING OF NOx, which has changed due to transport/deposition
  162. ! This does not yet work. TODO: Make this working. (FIXME : ask VH what's this is about???)
  163. do j = j1, j2
  164. do i = i1, i2
  165. #ifdef with_zoom
  166. if(zoomed(i,j)/=region) cycle
  167. #endif
  168. y(i,j,ino) =max(1e-3,y(i,j,ino))
  169. y(i,j,ino2) =max(1e-3,y(i,j,ino2))
  170. y(i,j,ino3) =max(1e-3,y(i,j,ino3))
  171. y(i,j,in2o5)=max(1e-3,y(i,j,in2o5))
  172. y(i,j,ihno4)=max(1e-3,y(i,j,ihno4))
  173. fnoy=y(i,j,ino)+y(i,j,ino2)+y(i,j,ino3)+2.*y(i,j,in2o5)+y(i,j,ihno4)
  174. fnoy=y(i,j,inox)/fnoy
  175. y(i,j,ino) =fnoy*y(i,j,ino)
  176. y(i,j,ino2) =fnoy*y(i,j,ino2)
  177. y(i,j,ino3) =fnoy*y(i,j,ino3)
  178. y(i,j,in2o5)=fnoy*y(i,j,in2o5)
  179. y(i,j,ihno4)=fnoy*y(i,j,ihno4)
  180. end do
  181. end do
  182. !
  183. ! set budget accumulators to zero
  184. !
  185. #ifdef with_budgets
  186. cr2 = 0.0
  187. cr3 = 0.0
  188. cr4 = 0.0
  189. #endif
  190. !===========================================================
  191. ! ** Start iterating over CHEMISTRY
  192. !===========================================================
  193. do ib=1,iterebi
  194. maxit=8 !CMKTEMP
  195. if(level<=3) maxit = maxit*2 ! lowest layers more iterations
  196. y0 = y
  197. !-------------------------------
  198. ! wet sulphur/ammonia chemistry
  199. !------------------------------
  200. #ifdef with_budgets
  201. call wetS(region, level, i1, j1, y0, dt, y, ye, cr4, status)
  202. #else
  203. call wetS(region, level, i1, j1, y0, dt, y, ye, status)
  204. #endif
  205. !-------------------------------------
  206. ! gasphase chemistry using EBI solver
  207. !-------------------------------------
  208. y0 = y ! reset initial concentrations
  209. ! ______do EBI solver_______
  210. dt2 = dt*dt
  211. ! block the input for EBI for efficiency:
  212. ! copy values with faster running index in inside loop
  213. iv = 0
  214. do j = j1, j2
  215. do i = i1, i2
  216. iv = iv+1
  217. ipts(iv) = i
  218. jpts(iv) = j
  219. if(iv==npts) then
  220. ! copy reaction rates...
  221. do itrace=1,nreac
  222. do ivt=1,npts
  223. rrv(ivt,itrace) = rr(ipts(ivt),jpts(ivt),itrace)
  224. end do
  225. end do
  226. ! copy photolysis rates....
  227. do itrace=1,nj
  228. do ivt=1,npts
  229. rjv(ivt,itrace) = rj(ipts(ivt),jpts(ivt),itrace)
  230. end do
  231. end do
  232. ! copy tracer concentrations ....
  233. do itrace=1,maxtrace
  234. do ivt=1,npts
  235. yv(ivt,itrace) = y(ipts(ivt),jpts(ivt),itrace)
  236. y0v(ivt,itrace) = y0(ipts(ivt),jpts(ivt),itrace)
  237. end do
  238. end do
  239. ! deposition ....
  240. #ifndef without_dry_deposition
  241. if(level == 1) then
  242. do itrace=1,ntrace
  243. do ivt=1,npts
  244. vdv(ivt,itrace) = &
  245. vd(region,itrace)%surf(ipts(ivt),jpts(ivt)) &
  246. / ye(ipts(ivt),jpts(ivt),idz) !1/s
  247. end do
  248. end do
  249. else
  250. vdv(:,:) = 0.0
  251. end if
  252. #endif
  253. ! copy nox emissions....
  254. do ivt=1,npts
  255. emino(ivt) = ye(ipts(ivt),jpts(ivt),ieno)
  256. end do
  257. ! do ebi solver....
  258. call DO_EBI(iv, npts, maxit, dt, dt2, rrv, rjv, vdv, emino, yv, y0v)
  259. do itrace=1,maxtrace
  260. do ivt=1,npts
  261. y(ipts(ivt),jpts(ivt),itrace)=yv(ivt,itrace)
  262. end do
  263. end do
  264. iv=0
  265. end if
  266. end do
  267. end do
  268. ! do the 'remaining' points...
  269. if(iv > 0) then
  270. do itrace=1,nreac
  271. do ivt=1,iv
  272. rrv(ivt,itrace) = rr(ipts(ivt),jpts(ivt),itrace)
  273. end do
  274. end do
  275. do itrace=1,nj
  276. do ivt=1,iv
  277. rjv(ivt,itrace) = rj(ipts(ivt),jpts(ivt),itrace)
  278. end do
  279. end do
  280. do itrace=1,maxtrace
  281. do ivt=1,iv
  282. yv(ivt,itrace) = y(ipts(ivt),jpts(ivt),itrace)
  283. y0v(ivt,itrace) = y0(ipts(ivt),jpts(ivt),itrace)
  284. end do
  285. end do
  286. ! deposition ....
  287. #ifndef without_dry_deposition
  288. if(level == 1) then
  289. do itrace=1,ntrace
  290. do ivt=1,iv
  291. vdv(ivt,itrace) = &
  292. vd(region,itrace)%surf(ipts(ivt),jpts(ivt)) &
  293. / ye(ipts(ivt),jpts(ivt),idz) !1/s
  294. end do
  295. end do
  296. else
  297. vdv(:,:) = 0.0
  298. end if
  299. #endif
  300. do ivt=1,iv
  301. emino(ivt) = ye(ipts(ivt),jpts(ivt),ieno)
  302. end do
  303. !the actual EBI solver on remaining cells
  304. call DO_EBI(iv, npts, maxit, dt, dt2, rrv, rjv, vdv, emino, yv, y0v)
  305. do itrace=1,maxtrace
  306. do ivt=1,iv
  307. y(ipts(ivt),jpts(ivt),itrace)=yv(ivt,itrace)
  308. end do
  309. end do
  310. end if
  311. call NOYmass
  312. !-------------------------------------
  313. ! marked tracers
  314. ! apply after correction of nitrogen components
  315. !----------------------------------------------
  316. call MARK_TRAC(region, level, is, js, y, rr, rj, dt, ye)
  317. !------------------------------------------------------------
  318. ! increase budget accumulators cr2 and cr3 (cr4 is done in wetS)
  319. !------------------------------------------------------------
  320. #ifdef with_budgets
  321. call incc2c3
  322. #endif
  323. !===========================================================
  324. ! ** END iterating over CHEMISTRY
  325. !===========================================================
  326. end do !iterebi
  327. #ifdef with_budgets
  328. call REACBUD
  329. #endif
  330. deallocate(y0)
  331. #ifdef with_budgets
  332. deallocate(cr2)
  333. deallocate(cr3)
  334. deallocate(cr4)
  335. #endif
  336. #ifdef with_zoom
  337. nullify(zoomed)
  338. #endif
  339. ! ok
  340. status = 0
  341. contains
  342. subroutine DO_EBI(lvec, npts, maxit, dt, dt2, rrv, rjv, vdv, emino, yv, y0v)
  343. ! INPUT/OUTPUT
  344. integer,intent(in) :: lvec, npts, maxit
  345. real, intent(in) :: dt, dt2, rrv(npts,nreac), rjv(npts,nj), &
  346. vdv(npts,ntrace), emino(npts), &
  347. y0v(npts,maxtrace)
  348. real, intent(out) :: yv(npts,maxtrace)
  349. ! Local
  350. integer :: ivec, iter
  351. real :: r57, r89, p1, r12, r21, xl1, p2, xl2, p3, &
  352. xl3, x1, x2, x3, c1, c2, c3, y2, xjt, r21t, &
  353. r12t, acub, bcub, ccub, cubdet, dno2, r56, &
  354. r65, r75, p5, xl5, r66, x5, p6, xl6, x6, c6, &
  355. xl7, y1, c7, r98, p8, xl8, x4, c5, xl9, &
  356. r1920, r1919, p19, xl19, r2019, xl20, xlhno3, &
  357. ph2o2, xlh2o2, pch2o, pco, phno3, xlch2o, &
  358. pch3o2, xlch3o2, pch3o2h, xlch3o2h, pald2, &
  359. xlald2, pmgly, xlmgly, pole, xleth, xlole, &
  360. xlisop, prxpar, xlrxpar, ppar, xlpar, pror, &
  361. xlror, pxo2, xlxo2, pxo2n, xlxo2n, prooh, &
  362. xlrooh, porgntr, xlorgntr, xlco, qdms, pso2, &
  363. qso2, qso2d, qnh3, pnh2, qnh2, qdms1, qdms2, &
  364. pmsa
  365. do iter=1,maxit
  366. do ivec=1,lvec
  367. ! --- Short living compounds & groups
  368. ! --- First group: NO NO2 O3
  369. P1=rjv(ivec,jbno3)*yv(ivec,ino3)+emino(ivec)
  370. R12=0.
  371. R21=rrv(ivec,kho2no)*yv(ivec,iho2)+rrv(ivec,kmo2no)*yv(ivec,ich3o2)&
  372. +rrv(ivec,kc79)*yv(ivec,ixo2)+rrv(ivec,kc46)*yv(ivec,ic2o3)
  373. XL1=rrv(ivec,knono3)*yv(ivec,ino3)+rrv(ivec,kc81)*yv(ivec,ixo2n)
  374. XL1 = XL1 + vdv(ivec,ino)
  375. P2=rjv(ivec,jhno3)*yv(ivec,ihno3)+rjv(ivec,jn2o5)*yv(ivec,in2o5)&
  376. +rrv(ivec,kn2o5)*yv(ivec,in2o5)+rjv(ivec,jano3)*yv(ivec,ino3)&
  377. +yv(ivec,ihno4)*(rjv(ivec,jhno4)+rrv(ivec,khno4m)+rrv(ivec,khno4oh)&
  378. *yv(ivec,ioh))+2.*rrv(ivec,knono3)*yv(ivec,ino3)*yv(ivec,ino)&
  379. +rrv(ivec,kc48)*yv(ivec,ipan)+rrv(ivec,kc59)*yv(ivec,iole)*yv(ivec,ino3)&
  380. +rrv(ivec,kc84)*yv(ivec,iorgntr)*yv(ivec,ioh)+rjv(ivec,jorgn)&
  381. *yv(ivec,iorgntr)+rjv(ivec,jpan)*yv(ivec,ipan)+0.1*rrv(ivec,kc78) *yv(ivec,iisop)*yv(ivec,ino3)
  382. XL2=rrv(ivec,kno2oh)*yv(ivec,ioh)+rrv(ivec,kno2no3)*yv(ivec,ino3)&
  383. +rrv(ivec,kno2ho2)*yv(ivec,iho2)+rrv(ivec,kno2o3)*yv(ivec,io3)&
  384. +rrv(ivec,kc47)*yv(ivec,ic2o3)
  385. XL2 = XL2 + vdv(ivec,ino2)
  386. P3=rjv(ivec,jano3)*yv(ivec,ino3)+rjv(ivec,jo2) ! JEW : O3P + O2 =O3
  387. XL3=rrv(ivec,ko3ho2)*yv(ivec,iho2)+rrv(ivec,ko3oh)*yv(ivec,ioh)+rrv(ivec,ko3po3)&
  388. +rrv(ivec,kno2o3)*yv(ivec,ino2)+rjv(ivec,jo3d)&
  389. +rrv(ivec,kc58)*yv(ivec,iole)&
  390. +rrv(ivec,kc62)*yv(ivec,ieth)&
  391. +rrv(ivec,kc77)*yv(ivec,iisop)
  392. XL3 = XL3 + vdv(ivec,io3)
  393. X1=y0v(ivec,ino)+P1*DT
  394. X2=y0v(ivec,ino2)+P2*DT
  395. X3=y0v(ivec,io3)+P3*DT
  396. C1=1.+XL1*DT
  397. C2=1.+XL2*DT
  398. C3=1.+XL3*DT
  399. Y1=rrv(ivec,knoo3)*DT
  400. R21T=R21*DT
  401. R12T=R12*DT
  402. XJT=rjv(ivec,jno2)*DT
  403. ! --- Solve unknown: x
  404. ACUB=-2.*Y1*(C2+R12T+C2*R21T/C1)
  405. BCUB=2.*C1*C2*C3+2.*C1*C3*(R12T+XJT)+2.*C2*C3*R21T+&
  406. 2.*Y1*(R12T*(X1-X2)+2.*C2*R21T*X1/C1+C2*(X1+X3))
  407. CCUB=2.*C1*C3*X2*(R12T+XJT)-2.*C2*C3*X1*R21T+2.*Y1*X1*&
  408. (X2*R12T-C2*X3-C2*R21T*X1/C1)
  409. CUBDET=BCUB*BCUB-4.*ACUB*CCUB
  410. DNO2=(-1.*BCUB+sqrt(CUBDET))/(2.*ACUB)
  411. dno2=min(x1,dno2)
  412. yv(ivec,ino2)=(X2+DNO2)/C2
  413. yv(ivec,ino)=(X1-DNO2)/C1
  414. yv(ivec,io3)=(X3+XJT*yv(ivec,ino2))/(C3+Y1*yv(ivec,ino))
  415. ! --- Second group: yv(ivec,iho2) yv(ivec,ioh) yv(ivec,ihno4)
  416. R57=rjv(ivec,jhno4)+rrv(ivec,khno4m)
  417. R56=rrv(ivec,kcooh)*yv(ivec,ico)+rrv(ivec,ko3oh)*yv(ivec,io3)+rrv(ivec,khpoh)&
  418. *yv(ivec,ih2o2)+rrv(ivec,kfrmoh)*yv(ivec,ich2o)+rrv(ivec,kh2oh) &
  419. +rrv(ivec,kso2oh)*yv(ivec,iso2) ! bug found by Narcisa 02/2013 SO2+OH -> SO4+HO2
  420. P5=2.*rjv(ivec,jbch2o)*yv(ivec,ich2o)+rrv(ivec,kc46)*yv(ivec,ic2o3)*yv(ivec,ino)&
  421. +rrv(ivec,kmo2no)*yv(ivec,ich3o2)*yv(ivec,ino)+0.66*rrv(ivec,kmo2mo2)&
  422. *yv(ivec,ich3o2)*yv(ivec,ich3o2)+rjv(ivec,jmepe)*yv(ivec,ich3o2h)&
  423. +2.*rrv(ivec,kc49)*yv(ivec,ic2o3)*yv(ivec,ic2o3)+2.*rjv(ivec,j45)&
  424. *yv(ivec,iald2)+rjv(ivec,j74)*yv(ivec,imgly)+0.11*rrv(ivec,kc52)*yv(ivec,ipar)&
  425. *yv(ivec,ioh)+0.94*rrv(ivec,kc53)*yv(ivec,iror)+rrv(ivec,kc54)*yv(ivec,iror)&
  426. +rrv(ivec,kc57)*yv(ivec,iole)*yv(ivec,ioh)+0.25*rrv(ivec,kc58)*yv(ivec,io3)&
  427. *yv(ivec,iole)+rrv(ivec,kc61)*yv(ivec,ieth)*yv(ivec,ioh)+0.26*rrv(ivec,kc62)&
  428. *yv(ivec,ieth)*yv(ivec,io3)+0.85*rrv(ivec,kc76)*yv(ivec,iisop)*yv(ivec,ioh)&
  429. +0.3*rrv(ivec,kc77)*yv(ivec,iisop)*yv(ivec,io3)+rrv(ivec,kc41)*yv(ivec,ich2o)&
  430. *yv(ivec,ino3)+rjv(ivec,jorgn)*yv(ivec,iorgntr)+0.9*rrv(ivec,kc78)*yv(ivec,iisop)*yv(ivec,ino3)
  431. XL5=rrv(ivec,kho2no)*yv(ivec,ino)+rrv(ivec,kno2ho2)*yv(ivec,ino2)&
  432. +rrv(ivec,ko3ho2)*yv(ivec,io3)+rrv(ivec,kmo2ho2)*yv(ivec,ich3o2)&
  433. +rrv(ivec,kho2oh)*yv(ivec,ioh)+rrv(ivec,kc82)*yv(ivec,ixo2)&
  434. +rrv(ivec,kc85)*yv(ivec,ixo2n) &
  435. +rrv(ivec,kho2_aer) &
  436. +rrv(ivec,kho2_l)
  437. R66=2.*rrv(ivec,kho2ho2)
  438. X5=y0v(ivec,iho2)+P5*DT
  439. R65=rrv(ivec,kho2no)*yv(ivec,ino)+rrv(ivec,ko3ho2)*yv(ivec,io3)
  440. P6=rjv(ivec,jhno3)*yv(ivec,ihno3)+2.*rjv(ivec,jo3d)*yv(ivec,io3)&
  441. +2.*rjv(ivec,jh2o2)*yv(ivec,ih2o2)+rjv(ivec,jmepe)*yv(ivec,ich3o2h)&
  442. +0.79*rrv(ivec,kc50)*yv(ivec,ic2o3)*yv(ivec,iho2)+0.4*rrv(ivec,kc58)&
  443. *yv(ivec,io3)*yv(ivec,iole)+0.28*rrv(ivec,kc77)*yv(ivec,iisop)*yv(ivec,io3)&
  444. +rjv(ivec,jrooh)*yv(ivec,irooh)+0.12*rrv(ivec,kc62)*yv(ivec,ieth)*yv(ivec,io3)
  445. XL6=rrv(ivec,khno4oh)*yv(ivec,ihno4)+rrv(ivec,kho2oh)*yv(ivec,iho2)&
  446. +rrv(ivec,kno2oh)*yv(ivec,ino2)+rrv(ivec,kohhno3)*yv(ivec,ihno3)&
  447. +rrv(ivec,kcooh)*yv(ivec,ico)+rrv(ivec,ko3oh)*yv(ivec,io3)+rrv(ivec,khpoh)&
  448. *yv(ivec,ih2o2)+rrv(ivec,kfrmoh)*yv(ivec,ich2o)+rrv(ivec,kch4oh)&
  449. *yv(ivec,ich4)+0.7*rrv(ivec,kohmper)*yv(ivec,ich3o2h)+rrv(ivec,kc43)&
  450. *yv(ivec,iald2)+rrv(ivec,kc73)*yv(ivec,imgly)+rrv(ivec,kc52)&
  451. *yv(ivec,ipar)+rrv(ivec,kc57)*yv(ivec,iole)+rrv(ivec,kc61)*yv(ivec,ieth)&
  452. +rrv(ivec,kc76)*yv(ivec,iisop)+0.7*rrv(ivec,kohrooh)*yv(ivec,irooh)&
  453. +rrv(ivec,kc84)*yv(ivec,iorgntr)+rrv(ivec,kh2oh)&
  454. +rrv(ivec,kso2oh)*yv(ivec,iso2) & ! bug found by Jason 01/2008
  455. +(rrv(ivec,kdmsoha)+rrv(ivec,kdmsohb)) *yv(ivec,idms) &
  456. +rrv(ivec,knh3oh)*yv(ivec,inh3) !sulfur
  457. X6=y0v(ivec,ioh)+P6*DT
  458. C6=1.+XL6*DT
  459. R75=rrv(ivec,kno2ho2)*yv(ivec,ino2)
  460. XL7=rjv(ivec,jhno4)+rrv(ivec,khno4oh)*yv(ivec,ioh)+rrv(ivec,khno4m)
  461. XL7 = XL7 + vdv(ivec,ihno4)
  462. C7=1.+XL7*DT
  463. Y1=R57/C7
  464. Y2=R56/C6
  465. ACUB=R66*DT
  466. BCUB=1.+XL5*DT-DT2*(Y1*R75+Y2*R65)
  467. CCUB=-1.*X5-DT*(Y1*y0v(ivec,ihno4)+Y2*X6)
  468. CUBDET=BCUB*BCUB-4.*ACUB*CCUB
  469. CUBDET=max(CUBDET,1.E-20)
  470. yv(ivec,iho2)=max(0.1,(-1.*BCUB+sqrt(CUBDET))/(2.*ACUB))
  471. yv(ivec,ioh)=(X6+R65*yv(ivec,iho2)*DT)/C6
  472. yv(ivec,ihno4)=(y0v(ivec,ihno4)+R75*DT*yv(ivec,iho2))/C7
  473. ! --- Third group: NO3 N2O5
  474. R89=rjv(ivec,jn2o5)+rrv(ivec,kn2o5)
  475. P8=rrv(ivec,kohhno3)*yv(ivec,ihno3)*yv(ivec,ioh)+rrv(ivec,kno2o3)*yv(ivec,ino2)*yv(ivec,io3)
  476. XL8=rjv(ivec,jbno3)+rjv(ivec,jano3)+rrv(ivec,knono3)*yv(ivec,ino)&
  477. +rrv(ivec,kno2no3)*yv(ivec,ino2)+rrv(ivec,kc44)*yv(ivec,iald2)+rrv(ivec,kc59)&
  478. ! *yv(ivec,iole)+rrv(ivec,kc78)*yv(ivec,iisop)+rrv(ivec,kc41)*yv(ivec,ich2o)+rrv(ivec,kdmsno3)*yv(ivec,idms)
  479. *yv(ivec,iole)+rrv(ivec,kc78)*yv(ivec,iisop)+rrv(ivec,kc41)*yv(ivec,ich2o)&
  480. +rrv(ivec,kdmsno3)*yv(ivec,idms)&
  481. +rrv(ivec,kno3_aer)
  482. XL8 = XL8 + vdv(ivec,ino3)
  483. X4=y0v(ivec,ino3)+P8*DT
  484. C5=1.+XL8*DT
  485. R98=rrv(ivec,kno2no3)*yv(ivec,ino2)
  486. XL9=rjv(ivec,jn2o5)+rrv(ivec,kn2o5)+rrv(ivec,kn2o5_aer)+rrv(ivec,kn2o5l)
  487. XL9 = XL9 + vdv(ivec,in2o5)
  488. C6=1.+XL9*DT
  489. C7=(C5*C6-R89*R98*DT2)
  490. yv(ivec,in2o5)=(C5*y0v(ivec,in2o5)+R98*DT*X4)/C7
  491. yv(ivec,ino3)=(C6*X4+R89*DT*y0v(ivec,in2o5))/C7
  492. ! --- Fourth group: C2O3 PAN
  493. R1920=rrv(ivec,kc48)+rjv(ivec,jpan)
  494. R1919=rrv(ivec,kc49)
  495. P19=rrv(ivec,kc43)*yv(ivec,iald2)*yv(ivec,ioh)+rrv(ivec,kc44)*yv(ivec,iald2)&
  496. *yv(ivec,ino3)+rrv(ivec,kc73)*yv(ivec,imgly)*yv(ivec,ioh)+rjv(ivec,j74)&
  497. *yv(ivec,imgly)+0.15*rrv(ivec,kc77)*yv(ivec,iisop)*yv(ivec,io3)
  498. XL19=rrv(ivec,kc46)*yv(ivec,ino)+rrv(ivec,kc50)*yv(ivec,iho2)+rrv(ivec,kc47)*yv(ivec,ino2)
  499. XL19 = XL19 + vdv(ivec,ic2o3)
  500. R2019=rrv(ivec,kc47)*yv(ivec,ino2)
  501. XL20=rrv(ivec,kc48)+rjv(ivec,jpan)
  502. XL20 = XL20 + vdv(ivec,ipan)
  503. ACUB=2*R1919*DT*(1+XL20*DT)
  504. BCUB=(1+XL20*DT)*(1+XL19*DT)-R1920*DT*R2019*DT
  505. CCUB=(1+XL20*DT)*(y0v(ivec,ic2o3)+P19*DT)+R1920*DT*y0v(ivec,ipan)
  506. CUBDET=BCUB*BCUB+4.*ACUB*CCUB
  507. yv(ivec,ic2o3)=max(1e-8,(-1.*BCUB+sqrt(CUBDET))/(2.*ACUB)) !cmk put max here....
  508. yv(ivec,ipan)=(y0v(ivec,ipan)+R2019*yv(ivec,ic2o3)*DT)/(1.+XL20*DT)
  509. ! --- CH4 chemistry (short living radicals)
  510. PCH3O2=rrv(ivec,kch4oh)*yv(ivec,ich4)*yv(ivec,ioh)+0.7*rrv(ivec,kohmper)*yv(ivec,ioh)*yv(ivec,ich3o2h)
  511. XLCH3O2=rrv(ivec,kmo2no)*yv(ivec,ino)+rrv(ivec,kmo2ho2)*yv(ivec,iho2)&
  512. +2*rrv(ivec,kmo2mo2)*yv(ivec,ich3o2)
  513. yv(ivec,ich3o2)=(y0v(ivec,ich3o2)+PCH3O2*DT)/(1.+XLCH3O2*DT)
  514. ! --- CBM4 chem.(short living compounds & operators)
  515. PRXPAR=0.11*rrv(ivec,kc52)*yv(ivec,ioh)*yv(ivec,ipar)+2.1*rrv(ivec,kc53)&
  516. *yv(ivec,iror)+rrv(ivec,kc57)*yv(ivec,iole)*yv(ivec,ioh)+0.9*rrv(ivec,kc58)&
  517. *yv(ivec,io3)*yv(ivec,iole)+rrv(ivec,kc59)*yv(ivec,iole)*yv(ivec,ino3)
  518. XLRXPAR=rrv(ivec,kc83)*yv(ivec,ipar)
  519. yv(ivec,irxpar)=(y0v(ivec,irxpar)+PRXPAR*DT)/(1.+XLRXPAR*DT)
  520. XLISOP=rrv(ivec,kc76)*yv(ivec,ioh)+rrv(ivec,kc77)*yv(ivec,io3)+rrv(ivec,kc78)*yv(ivec,ino3)
  521. yv(ivec,iisop)=y0v(ivec,iisop)/(1.+XLISOP*DT)
  522. PROR=0.76*rrv(ivec,kc52)*yv(ivec,ipar)*yv(ivec,ioh)+0.02*rrv(ivec,kc53)*yv(ivec,iror)
  523. XLROR=rrv(ivec,kc53)+rrv(ivec,kc54)
  524. yv(ivec,iror)=(y0v(ivec,iror)+PROR*DT)/(1.+XLROR*DT)
  525. PXO2=rrv(ivec,kc46)*yv(ivec,ic2o3)*yv(ivec,ino)+2.*rrv(ivec,kc49)&
  526. *yv(ivec,ic2o3)*yv(ivec,ic2o3)+rrv(ivec,kc50)*yv(ivec,ic2o3)&
  527. *yv(ivec,iho2)+rjv(ivec,j45)*yv(ivec,iald2)+rrv(ivec,kc73)&
  528. *yv(ivec,imgly)*yv(ivec,ioh)+0.87*rrv(ivec,kc52)*yv(ivec,ipar)*yv(ivec,ioh)&
  529. +0.96*rrv(ivec,kc53)*yv(ivec,iror)+rrv(ivec,kc57)*yv(ivec,iole)*yv(ivec,ioh)&
  530. +0.29*rrv(ivec,kc58)*yv(ivec,io3)*yv(ivec,iole)+0.91*rrv(ivec,kc59)&
  531. *yv(ivec,iole)*yv(ivec,ino3)+rrv(ivec,kc61)*yv(ivec,ieth)*yv(ivec,ioh)&
  532. +0.85*rrv(ivec,kc76)*yv(ivec,iisop)*yv(ivec,ioh)+0.7*rrv(ivec,kohrooh)&
  533. *yv(ivec,irooh)*yv(ivec,ioh)+rrv(ivec,kc84)*yv(ivec,ioh)*yv(ivec,iorgntr)&
  534. +0.18*rrv(ivec,kc77)*yv(ivec,iisop)*yv(ivec,io3)
  535. XLXO2=rrv(ivec,kc79)*yv(ivec,ino)+2.*rrv(ivec,kc80)*yv(ivec,ixo2)&
  536. +rrv(ivec,kc82)*yv(ivec,iho2)+rrv(ivec,kxo2xo2n)*yv(ivec,ixo2n)
  537. yv(ivec,ixo2)=(y0v(ivec,ixo2)+PXO2*DT)/(1.+XLXO2*DT)
  538. PXO2N=0.13*rrv(ivec,kc52)*yv(ivec,ipar)*yv(ivec,ioh)+0.04*rrv(ivec,kc53)&
  539. *yv(ivec,iror)+0.09*rrv(ivec,kc59)*yv(ivec,iole)*yv(ivec,ino3)+0.15*rrv(ivec,kc76)*yv(ivec,iisop)*yv(ivec,ioh)
  540. XLXO2N=rrv(ivec,kc81)*yv(ivec,ino)+rrv(ivec,kc85)*yv(ivec,iho2)+rrv(ivec,kxo2xo2n)*yv(ivec,ixo2)+rrv(ivec,kxo2n)*yv(ivec,ixo2n)
  541. yv(ivec,ixo2n)=(y0v(ivec,ixo2n)+PXO2N*DT)/(1.+XLXO2N*DT)
  542. end do !ivec
  543. if ( mod(iter,2) == 0 ) then
  544. do ivec=1,lvec
  545. ! --- Species with intermediate lifetimes
  546. ! --- Inorganic compounds (HNO3 H2O2)
  547. !
  548. PHNO3=rrv(ivec,kno2oh)*yv(ivec,ino2)*yv(ivec,ioh) &
  549. +2.*(rrv(ivec,kn2o5_aer)+rrv(ivec,kn2o5l))*yv(ivec,in2o5) &
  550. +rrv(ivec,kc44)*yv(ivec,iald2)*yv(ivec,ino3) &
  551. +rrv(ivec,kc41)*yv(ivec,ich2o)*yv(ivec,ino3) &
  552. +rrv(ivec,kno3_aer)*yv(ivec,ino3)
  553. XLHNO3=rjv(ivec,jhno3)+rrv(ivec,kohhno3)*yv(ivec,ioh)
  554. XLHNO3=XLHNO3 + vdv(ivec,ihno3)
  555. yv(ivec,ihno3)=(y0v(ivec,ihno3)+PHNO3*DT)/(1.+XLHNO3*DT)
  556. PH2O2=rrv(ivec,kho2ho2)*yv(ivec,iho2)*yv(ivec,iho2)
  557. ! VH - according to Mao et al, ACP 2013 don't include H2O2 formation
  558. ! VH & +0.5*rrv(ivec,kho2_aer)*yv(ivec,iho2)
  559. XLH2O2=rjv(ivec,jh2o2)+rrv(ivec,khpoh)*yv(ivec,ioh)
  560. XLH2O2=XLH2O2 + vdv(ivec,ih2o2)
  561. yv(ivec,ih2o2)=(y0v(ivec,ih2o2)+PH2O2*DT)/(1.+XLH2O2*DT)
  562. ! --- CH4-chemistry (methyl peroxide formaldehyde)
  563. PCH3O2H=rrv(ivec,kmo2ho2)*yv(ivec,ich3o2)*yv(ivec,iho2)
  564. XLCH3O2H=rrv(ivec,kohmper)*yv(ivec,ioh)+rjv(ivec,jmepe)
  565. XLCH3O2H=XLCH3O2H + vdv(ivec,ich3o2h)
  566. yv(ivec,ich3o2h)=(y0v(ivec,ich3o2h)+PCH3O2H*DT)/(1.+XLCH3O2H*DT)
  567. PCH2O=rrv(ivec,kc46)*yv(ivec,ic2o3)*yv(ivec,ino)+0.3*rrv(ivec,kohmper)&
  568. *yv(ivec,ich3o2h)*yv(ivec,ioh)+rrv(ivec,kmo2no)*yv(ivec,ich3o2)*yv(ivec,ino)&
  569. +1.33*rrv(ivec,kmo2mo2)*yv(ivec,ich3o2)*yv(ivec,ich3o2)+rjv(ivec,jmepe)&
  570. *yv(ivec,ich3o2h)+2.*rrv(ivec,kc49)*yv(ivec,ic2o3)*yv(ivec,ic2o3)&
  571. +rrv(ivec,kc50)*yv(ivec,ic2o3)*yv(ivec,iho2)+rjv(ivec,j45)*yv(ivec,iald2)&
  572. +rrv(ivec,kc57)*yv(ivec,iole)*yv(ivec,ioh)+0.64*rrv(ivec,kc58)*yv(ivec,iole)&
  573. *yv(ivec,io3)+rrv(ivec,kc59)*yv(ivec,iole)*yv(ivec,ino3)+1.56*rrv(ivec,kc61)&
  574. *yv(ivec,ieth)*yv(ivec,ioh)+rrv(ivec,kc62)*yv(ivec,ieth)*yv(ivec,io3)&
  575. +0.61*rrv(ivec,kc76)*yv(ivec,iisop)*yv(ivec,ioh)+0.9*rrv(ivec,kc77)&
  576. *yv(ivec,iisop)*yv(ivec,io3)+0.03*rrv(ivec,kc78)*yv(ivec,iisop)*yv(ivec,ino3)
  577. XLCH2O=rjv(ivec,jach2o)+rjv(ivec,jbch2o)+yv(ivec,ioh)*rrv(ivec,kfrmoh)+rrv(ivec,kc41)*yv(ivec,ino3)
  578. XLCH2O=XLCH2O + vdv(ivec,ich2o)
  579. yv(ivec,ich2o)=(y0v(ivec,ich2o)+PCH2O*DT)/(1.+XLCH2O*DT)
  580. ! --- CBIV-elements for higher HC-chemistry: ALD2 MGLY
  581. ! --- ETH OLE ISOP ROOH ORGNTR
  582. PALD2=0.11*rrv(ivec,kc52)*yv(ivec,ipar)*yv(ivec,ioh)+1.1*rrv(ivec,kc53)&
  583. *yv(ivec,iror)+rrv(ivec,kc57)*yv(ivec,iole)*yv(ivec,ioh)+0.44*rrv(ivec,kc58)&
  584. *yv(ivec,iole)*yv(ivec,io3)+rrv(ivec,kc59)*yv(ivec,iole)*yv(ivec,ino3)&
  585. +0.22*rrv(ivec,kc61)*yv(ivec,ieth)*yv(ivec,ioh)+0.12*rrv(ivec,kc78)*yv(ivec,iisop)*yv(ivec,ino3)
  586. XLALD2=rrv(ivec,kc43)*yv(ivec,ioh)+rrv(ivec,kc44)*yv(ivec,ino3)+rjv(ivec,j45)
  587. XLALD2=XLALD2 + vdv(ivec,iald2)
  588. yv(ivec,iald2)=(y0v(ivec,iald2)+PALD2*DT)/(1.+XLALD2*DT)
  589. PMGLY=0.03*rrv(ivec,kc76)*yv(ivec,iisop)*yv(ivec,ioh)+0.03*rrv(ivec,kc77)&
  590. *yv(ivec,iisop)*yv(ivec,io3)+0.08*rrv(ivec,kc78)*yv(ivec,iisop)*yv(ivec,ino3)
  591. XLMGLY=rrv(ivec,kc73)*yv(ivec,ioh)+rjv(ivec,j74)
  592. yv(ivec,imgly)=(y0v(ivec,imgly)+PMGLY*DT)/(1.+XLMGLY*DT)
  593. XLETH=rrv(ivec,kc61)*yv(ivec,ioh)+rrv(ivec,kc62)*yv(ivec,io3)
  594. yv(ivec,ieth)=y0v(ivec,ieth)/(1.+XLETH*DT)
  595. POLE=0.58*rrv(ivec,kc76)*yv(ivec,iisop)*yv(ivec,ioh)+0.55*rrv(ivec,kc77)&
  596. *yv(ivec,iisop)*yv(ivec,io3)+0.45*rrv(ivec,kc78)*yv(ivec,iisop) *yv(ivec,ino3)
  597. XLOLE=rrv(ivec,kc57)*yv(ivec,ioh)+rrv(ivec,kc58)*yv(ivec,io3)+rrv(ivec,kc59)*yv(ivec,ino3)
  598. yv(ivec,iole)=(y0v(ivec,iole)+POLE*DT)/(1.+XLOLE*DT)
  599. PROOH=rrv(ivec,kc82)*yv(ivec,ixo2)*yv(ivec,iho2)+0.21*rrv(ivec,kc50)&
  600. *yv(ivec,ic2o3)*yv(ivec,iho2)+rrv(ivec,kc85)*yv(ivec,iho2)*yv(ivec,ixo2n)
  601. XLROOH=rjv(ivec,jrooh)+rrv(ivec,kohrooh)*yv(ivec,ioh)
  602. XLROOH = XLROOH + vdv(ivec,irooh)
  603. yv(ivec,irooh)=(y0v(ivec,irooh)+PROOH*DT)/(1.+XLROOH*DT)
  604. PORGNTR=rrv(ivec,kc81)*yv(ivec,ino)*yv(ivec,ixo2n)+0.9*rrv(ivec,kc78)*yv(ivec,iisop)*yv(ivec,ino3)
  605. XLORGNTR=rrv(ivec,kc84)*yv(ivec,ioh)+rjv(ivec,jorgn)
  606. XLORGNTR=XLORGNTR+vdv(ivec,iorgntr)
  607. yv(ivec,iorgntr)=(y0v(ivec,iorgntr)+PORGNTR*DT)/(1.+XLORGNTR*DT)
  608. ! gas phase sulfur & ammonia
  609. qdms1=rrv(ivec,kdmsoha)*yv(ivec,ioh)+rrv(ivec,kdmsno3)*yv(ivec,ino3)
  610. qdms2=rrv(ivec,kdmsohb)*yv(ivec,ioh)
  611. qdms=qdms1+qdms2
  612. yv(ivec,idms)=y0v(ivec,idms)/(1.+qdms*DT)
  613. pso2=yv(ivec,idms)*(qdms1+0.75*qdms2)
  614. pmsa=yv(ivec,idms)*0.25*qdms2
  615. qso2=rrv(ivec,kso2oh)*yv(ivec,ioh)
  616. qso2d=qso2 + vdv(ivec,iso2)
  617. yv(ivec,iso2)=(y0v(ivec,iso2)+pso2*DT) /(1.+qso2d*DT) !qso2d includes deposition
  618. yv(ivec,imsa)=(y0v(ivec,imsa)+pmsa*DT) /(1.+vdv(ivec,imsa)*DT)
  619. #ifdef with_m7
  620. !VH: Do not apply dry deposition to H2SO4 : This deposition velocity represents aerosol deposition
  621. yv(ivec,iso4)=(y0v(ivec,iso4)+qso2*yv(ivec,iso2)*DT)
  622. #else
  623. !VH: Do apply dry deposition to SO4_A : This deposition velocity does represent aerosol deposition
  624. !VH: Use the same aerosol deposition velocity for NO3_A deposition.
  625. yv(ivec,iso4)=(y0v(ivec,iso4)+qso2*yv(ivec,iso2)*DT) /(1. + vdv(ivec,iso4)*DT) !corrected CMK qso2/qso2d
  626. yv(ivec,ino3_a)=y0v(ivec,ino3_a) /(1.+vdv(ivec,ino3_a)*DT) ! VH/FD include dry dep for no3_a? (should be copy of so4)
  627. #endif
  628. yv(ivec,inh4)=y0v(ivec,inh4)/(1.+vdv(ivec,inh4)*DT) ! This is just deposition
  629. pnh2=yv(ivec,ioh)*rrv(ivec,knh3oh)
  630. qnh3 = pnh2 + vdv(ivec,inh3)
  631. yv(ivec,inh3)=y0v(ivec,inh3)/(1.+qnh3*DT)
  632. qnh2= rrv(ivec,knh2no)*yv(ivec,ino)+rrv(ivec,knh2no2)*yv(ivec,ino2)&
  633. +rrv(ivec,knh2ho2)*yv(ivec,iho2) +rrv(ivec,knh2o2)+rrv(ivec,knh2o3)*yv(ivec,io3)
  634. yv(ivec,inh2)=(y0v(ivec,inh2)+yv(ivec,inh3)*pnh2*dt)/(1.+qnh2*dt)
  635. end do !ivec
  636. end if
  637. if ( mod(iter,maxit) == 0 ) then
  638. ! --- Long living compounds
  639. do ivec=1,lvec
  640. yv(ivec,ich4)=y0v(ivec,ich4)/(1.+rrv(ivec,kch4oh)*yv(ivec,ioh)*DT)
  641. PCO=yv(ivec,ich2o)*(rjv(ivec,jach2o)+rjv(ivec,jbch2o)+yv(ivec,ioh)&
  642. *rrv(ivec,kfrmoh))+rjv(ivec,j45)*yv(ivec,iald2)+rjv(ivec,j74)*yv(ivec,imgly)&
  643. +0.37*rrv(ivec,kc58)*yv(ivec,iole)*yv(ivec,io3)+0.43*rrv(ivec,kc62)&
  644. *yv(ivec,ieth)*yv(ivec,io3)+0.36*rrv(ivec,kc77)*yv(ivec,iisop)*yv(ivec,io3)&
  645. +rrv(ivec,kc41)*yv(ivec,ich2o)*yv(ivec,ino3)
  646. XLCO = rrv(ivec,kcooh)*yv(ivec,ioh)
  647. XLCO = XLCO + vdv(ivec,ico)
  648. yv(ivec,ico)=(y0v(ivec,ico)+PCO*DT)/(1.+XLCO*DT)
  649. PPAR=0.63*rrv(ivec,kc77)*yv(ivec,iisop)*yv(ivec,io3)+0.63*rrv(ivec,kc76)*yv(ivec,iisop)*yv(ivec,ioh)
  650. XLPAR=rrv(ivec,kc52)*yv(ivec,ioh)+rrv(ivec,kc83)*yv(ivec,irxpar)
  651. yv(ivec,ipar)=(y0v(ivec,ipar)+PPAR*DT)/(1.+XLPAR*DT)
  652. !cmk ____added rn222 chemistry in EBI language
  653. yv(ivec,irn222) = y0v(ivec,irn222)/(1.+rrv(ivec,krn222)*dt)
  654. yv(ivec,ipb210) = y0v(ivec,ipb210)+y0v(ivec,irn222)-yv(ivec,irn222)
  655. !if(yv(ivec,ipb210) < 0.0 .or. yv(ivec,irn222) < 0.0) then
  656. ! print *, 'Negatives .....rn222, pb210', y0v(ivec,irn222), yv(ivec,irn222) , y0v(ivec,ipb210), yv(ivec,ipb210)
  657. !end if
  658. end do !ivec
  659. end if
  660. end do !ITER
  661. end subroutine DO_EBI
  662. subroutine NOYmass
  663. integer i,j,imax
  664. real :: ncormax,ncorav,totn,totn0,fnoy,fnoy1
  665. real :: ncorr,ncorr1,ncorr2,ncorr3, totdep
  666. logical :: nerr
  667. ncormax=0.
  668. ncorav=0.
  669. nerr=.false.
  670. imax = 0
  671. do j=j1,j2
  672. do i=i1,i2
  673. #ifdef with_zoom
  674. if(zoomed(i,j)/=region) cycle
  675. #endif
  676. imax = imax + 1
  677. !
  678. !** Guarantee exact mass conservation of NOY
  679. ! (this may matter a few percent)
  680. !
  681. fnoy=y(i,j,ino)+y(i,j,ino2)+y(i,j,ino3)+2.*y(i,j,in2o5)+y(i,j,ihno4)
  682. if (level == 1) then
  683. #ifndef without_dry_deposition
  684. totdep = (y(i,j,ino) *vd(region,ino )%surf(i,j) + &
  685. y(i,j,ino2)*vd(region,ino2)%surf(i,j) + &
  686. y(i,j,ino3)*vd(region,ino3)%surf(i,j) + &
  687. y(i,j,ihno3)*vd(region,ihno3)%surf(i,j) + &
  688. y(i,j,ipan)*vd(region,ipan)%surf(i,j) + &
  689. y(i,j,iorgntr)*vd(region,iorgntr)%surf(i,j) + &
  690. 2*y(i,j,in2o5)*vd(region,in2o5)%surf(i,j) + &
  691. y(i,j,ihno4)*vd(region,ihno4)%surf(i,j) )*dt/ye(i,j,idz)
  692. #else
  693. totdep = 0.0
  694. #endif
  695. else
  696. totdep = 0.0
  697. end if
  698. totn0=y0(i,j,inox)+y0(i,j,ihno3)+y0(i,j,ipan)+ &
  699. y0(i,j,iorgntr) + ye(i,j,ieno)*dt - totdep
  700. ! note that emino is added here and the total deposition is subtracted
  701. !
  702. ! totn0 contains all nitrogen at beginning of timestep + nox emissions
  703. !
  704. !
  705. ! totn contains all nitrogen at end of timestep
  706. !
  707. totn=fnoy+y(i,j,ihno3)+y(i,j,ipan)+y(i,j,iorgntr)
  708. ! correction factor for all nitrogen compounds
  709. ncorr=totn-totn0
  710. if ( totn < tiny(totn) ) cycle
  711. if ( (abs(ncorr)/totn) > 0.05 ) then !CMK changed from 0.1 to 0.05
  712. nerr=.true.
  713. !AJS>>>
  714. ! print *,'NOYmass: N-error....',region,level,i,j,totn0,totn
  715. ! print *,'NOYmass: emino ',ye(i,j,ieno)*dt/y0(i,j,iair)*1e9
  716. ! print *,'NOYmass: NO(0) ', &
  717. ! y0(i,j,ino)/y0(i,j,iair)*1e9,y(i,j,ino)/y(i,j,iair)*1e9
  718. ! print *,'NOYmass: NO2(0) ', &
  719. ! y0(i,j,ino2)/y0(i,j,iair)*1e9,y(i,j,ino2)/y(i,j,iair)*1e9
  720. ! print *,'NOYmass: O3(0) ', &
  721. ! y0(i,j,io3)/y0(i,j,iair)*1e9,y(i,j,io3)/y(i,j,iair)*1e9
  722. ! print *,'NOYmass: NO3(0) ', &
  723. ! y0(i,j,ino3)/y0(i,j,iair)*1e9,y(i,j,ino3)/y(i,j,iair)*1e9
  724. ! print *,'NOYmass: N2O5(0) ', &
  725. ! y0(i,j,in2o5)/y0(i,j,iair)*1e9,y(i,j,in2o5)/y(i,j,iair)*1e9
  726. ! print *,'NOYmass: HNO4(0) ', &
  727. ! y0(i,j,ihno4)/y0(i,j,iair)*1e9,y(i,j,ihno4)/y(i,j,iair)*1e9
  728. ! print *,'NOYmass: HNO3(0) ', &
  729. ! y0(i,j,ihno3)/y0(i,j,iair)*1e9,y(i,j,ihno3)/y(i,j,iair)*1e9
  730. ! print *,'NOYmass: PAN(0) ', &
  731. ! y0(i,j,ipan)/y0(i,j,iair)*1e9,y(i,j,ipan)/y(i,j,iair)*1e9
  732. ! print *,'NOYmass: ORGNT(0) ', &
  733. ! y0(i,j,iorgntr)/y0(i,j,iair)*1e9,y(i,j,iorgntr)/y(i,j,iair)*1e9
  734. ! print *,'NOYmass: NOx(0) ', &
  735. ! y0(i,j,inox)/y0(i,j,iair)*1e9,y(i,j,inox)/y(i,j,iair)*1e9
  736. ! print *,'NOYmass: ',rj(i,j,jhno3),rr(i,j,kohhno3)*y(i,j,ioh), &
  737. ! y(i,j,ioh)/y(i,j,iair)*1e9
  738. !<<<AJS
  739. end if
  740. ! maximum and average correction factor in this loop
  741. ncormax=max(abs(ncormax),abs(ncorr/totn))
  742. ncorav=ncorav+abs(ncorr/totn)
  743. !
  744. ! first correct hno3, pan and organic nitrates
  745. ! (as a group of reservoir tracers)
  746. !
  747. totn=y(i,j,ihno3)+y(i,j,ipan)+y(i,j,iorgntr)
  748. if ( totn < tiny(totn) ) cycle
  749. ncorr1=y(i,j,ihno3) *(1.-ncorr/totn)
  750. ncorr2=y(i,j,ipan) *(1.-ncorr/totn)
  751. ncorr3=y(i,j,iorgntr)*(1.-ncorr/totn)
  752. y(i,j,ihno3) =max(0.,ncorr1)
  753. y(i,j,ipan) =max(0.,ncorr2)
  754. y(i,j,iorgntr)=max(0.,ncorr3)
  755. ncorr=ncorr1+ncorr2+ncorr3-y(i,j,ihno3)-y(i,j,ipan)- y(i,j,iorgntr)
  756. !
  757. ! the remainder is used to scale the noy components
  758. !
  759. fnoy1=(fnoy+ncorr)/fnoy
  760. y(i,j,ino) =fnoy1*y(i,j,ino)
  761. y(i,j,ino2) =fnoy1*y(i,j,ino2)
  762. y(i,j,ino3) =fnoy1*y(i,j,ino3)
  763. y(i,j,in2o5)=fnoy1*y(i,j,in2o5)
  764. y(i,j,ihno4)=fnoy1*y(i,j,ihno4)
  765. y(i,j,inox) =y(i,j,ino)+y(i,j,ino2)+y(i,j,ino3)+ &
  766. 2.*y(i,j,in2o5)+y(i,j,ihno4)
  767. end do
  768. end do
  769. if ( nerr ) then
  770. write (gol,'("NOYmass: N-mass balance error, ncorr>5% ")'); call goPr
  771. write (gol,'(" Maximum correction : ",f8.2)') ncormax; call goPr
  772. write (gol,'(" Average correction in this loop (imax) : ",f8.2," (",i6,")")') ncorav/imax, imax; call goPr
  773. end if
  774. end subroutine NOYmass
  775. #ifdef with_budgets
  776. !--------------------------------------------------------------------------
  777. ! TM5 !
  778. !--------------------------------------------------------------------------
  779. !BOP
  780. !
  781. ! !IROUTINE:
  782. !
  783. ! !DESCRIPTION: increase reaction budgets for each reaction
  784. ! arrays nrr and nrj determine which species are
  785. ! involved in a reaction
  786. !\\
  787. !\\
  788. ! !INTERFACE:
  789. !
  790. subroutine INCC2C3
  791. !
  792. #ifdef with_tendencies
  793. use TRACER_DATA, only : PLC_AddValue, plc_ipr_lddep, plc_kg_from_tm
  794. #endif
  795. ! integer, intent(out) :: status
  796. integer :: i01,n1,n2,jl,i,j
  797. ! nrj and nrr used for reaction budget calculations
  798. integer,dimension(nj),parameter :: nrj=(/io3,ino2,ih2o2,ihno3,ihno4,in2o5,ich2o,ich2o, &
  799. ich3o2h,ino3,ino3,ipan,iorgntr,iald2,imgly,irooh,io2/)
  800. integer,dimension(nreac,2),parameter :: nrr = reshape((/ &
  801. ino,iho2,ich3o2,ino2,ioh,ino2,ino,ino2,in2o5,ihno4,&
  802. ino2,ihno4,iair,ih2o,io3,ico,io3,ih2o2,ich2o,ich4, &
  803. ioh,ioh,ich3o2, ich3o2, iho2,iho2,in2o5,in2o5,ioh,ich2o,&
  804. iald2,iald2,ic2o3,ic2o3,ipan,ic2o3,ic2o3,ipar,iror,iror,&
  805. ioh,io3,ino3,ioh,io3,ioh,ioh,io3,ino3,ixo2,&
  806. ixo2,ixo2n,ixo2,irxpar,iorgntr,ixo2n,idms,idms,idms,iso2,&
  807. inh3,inh3,inh2,inh2,inh2,inh2,inh2,irn222,io3,io2,&
  808. ixo2,ixo2n,in2o5,ino3,iho2,iho2, &
  809. !second reaction partner (if monmolecular = 0)
  810. io3,ino,ino,ioh,ihno3,io3,ino3,ino3, 0, ioh, &
  811. iho2,0,0,0,iho2,ioh,ioh,ioh,ioh,ioh, &
  812. ich3o2h,irooh,iho2, ich3o2, ioh,iho2,0,0,0,ino3,&
  813. ioh,ino3,ino,ino2,0,ic2o3,iho2,ioh, 0, 0,&
  814. iole,iole,iole,ieth,ieth,imgly,iisop,iisop,iisop,ino,&
  815. ixo2,ino,iho2,ipar,ioh,iho2,ioh,ioh,ino3,ioh,&
  816. iacid,ioh,ino,ino2,iho2,0,io3,0,0,0,&
  817. ixo2n,ixo2n,0,0,0,0/),(/nreac,2/))
  818. real :: c1,xdep
  819. c1=dt*1000./xmair !conversion to moles...
  820. ! Reaction budgets
  821. do i01=1,nj !photolysis rates
  822. n1=nrj(i01)
  823. do j=j1,j2
  824. do i=i1,i2
  825. #ifdef with_zoom
  826. if(zoomed(i,j)/=region) cycle
  827. #endif
  828. if(n1 > 0) cr2(i,j,i01)=cr2(i,j,i01)+rj(i,j,i01)*y(i,j,n1)
  829. end do
  830. end do
  831. end do!i01=1,nj
  832. !
  833. do i01=1,nreac !reactions
  834. n1=nrr(i01,1) !make sure n1 > 0
  835. n2=nrr(i01,2)
  836. if (n2 > 0.) then
  837. do j=j1,j2
  838. do i=i1,i2
  839. #ifdef with_zoom
  840. if(zoomed(i,j)/=region) cycle
  841. #endif
  842. cr3(i,j,i01)= cr3(i,j,i01)+y(i,j,n1)*y(i,j,n2)*rr(i,j,i01)
  843. end do
  844. end do
  845. else
  846. do j=j1,j2
  847. do i=i1,i2
  848. #ifdef with_zoom
  849. if(zoomed(i,j)/=region) cycle
  850. #endif
  851. cr3(i,j,i01)= cr3(i,j,i01)+y(i,j,n1)*rr(i,j,i01)
  852. end do
  853. end do
  854. end if
  855. end do !i01=1,nreac
  856. if ( level == 1 ) then ! deposition budget
  857. do i01=1,ntrace
  858. if (fscale(i01) > 0) then
  859. do j=j1,j2
  860. do i=i1,i2
  861. #ifdef with_zoom
  862. if(zoomed(i,j)/=region) cycle
  863. #endif
  864. #ifndef without_dry_deposition
  865. if (i01 .ne. inox) then
  866. xdep = y(i,j,i01)*vd(region,i01)%surf(i,j)/ye(i,j,idz)* &
  867. c1*ye(i,j,iairm)/y(i,j,iair) !from updated concentrations
  868. else ! compute nox deposition from other contributors!
  869. xdep = (y(i,j,ino) *vd(region,ino)%surf(i,j) + &
  870. y(i,j,ino2 )*vd(region,ino2)%surf(i,j)+ &
  871. y(i,j,ino3) *vd(region,ino3)%surf(i,j)+ &
  872. y(i,j,ihno3)*vd(region,ihno3)%surf(i,j)+ &
  873. 2*y(i,j,in2o5)*vd(region,in2o5)%surf(i,j)) &
  874. /ye(i,j,idz)* &
  875. c1*ye(i,j,iairm)/y(i,j,iair) !from updated concentrations
  876. endif
  877. #else
  878. xdep = 0.0
  879. #endif
  880. buddep_dat(region)%dry(i,j,i01) = &
  881. buddep_dat(region)%dry(i,j,i01) + xdep
  882. if ( i01 == 1 ) then !seperate deposition from 'other' chemistry
  883. #ifndef without_dry_deposition
  884. sum_deposition(region) = sum_deposition(region) - &
  885. xdep*ra(1)*1e-3 ! in kg
  886. #endif
  887. sum_chemistry(region) = sum_chemistry(region) + &
  888. (y(i,j,1)-y0(i,j,1))/y(i,j,iair)* &
  889. ye(i,j,iairm)/xmair*ra(1) + xdep*ra(1)*1e-3
  890. end if
  891. ! FIXME TENDENCIES
  892. #ifdef with_tendencies
  893. ! Add deposition budget in kg to tendencies;
  894. ! (mole tm tracer) * (g/mole) * (kg/g) = kg tm tracer
  895. call PLC_AddValue( region, plc_ipr_lddep, i, j, 1, i01, &
  896. xdep * ra(i01) * 1e-3 * plc_kg_from_tm(i01), & ! kg plc tracer
  897. status )
  898. ! IF_NOTOK_RETURN(status=1)
  899. #endif
  900. end do
  901. end do
  902. endif
  903. end do !i01
  904. else ! other layers
  905. do j=j1,j2
  906. do i=i1,i2
  907. #ifdef with_zoom
  908. if(zoomed(i,j)/=region) cycle
  909. #endif
  910. sum_chemistry(region) = sum_chemistry(region) + &
  911. (y(i,j,1)-y0(i,j,1))/y(i,j,iair)*ye(i,j,iairm)/xmair*ra(1)
  912. end do
  913. end do
  914. end if !level ==1
  915. end subroutine INCC2C3
  916. !--------------------------------------------------------------------------
  917. ! TM5 !
  918. !--------------------------------------------------------------------------
  919. !BOP
  920. !
  921. ! !IROUTINE: REACBUD
  922. !
  923. ! !DESCRIPTION: accumulate budgets, o3 P/L
  924. !\\
  925. !\\
  926. ! !INTERFACE:
  927. !
  928. SUBROUTINE REACBUD
  929. !
  930. ! !USES:
  931. !
  932. USE BUDGET_GLOBAL, ONLY : budg_dat, nzon_vg
  933. !
  934. !EOP
  935. !------------------------------------------------------------------------
  936. !BOC
  937. integer :: i01, i, j, nzone, nzone_v
  938. real :: c1
  939. c1=dt*1000./xmair !conversion to moles
  940. do j=j1,j2
  941. do i=i1,i2
  942. #ifdef with_zoom
  943. if(zoomed(i,j)/=region) cycle
  944. #endif
  945. nzone=budg_dat(region)%nzong(i,j) !global budget
  946. nzone_v=nzon_vg(level) !level is passed to ebi...
  947. do i01=1,nj
  948. budrjg(nzone,nzone_v,i01)=budrjg(nzone,nzone_v,i01)+ &
  949. cr2(i,j,i01)*c1*ye(i,j,iairm)/y(i,j,iair) !units mole
  950. end do !nj
  951. ! ozone production on a 3D grid:
  952. ! defined as: HO2 + NO, CH3O2 + NO, XO2 + NO, C2O3 + NO
  953. o3p(region)%d3(i,j,level) = o3p(region)%d3(i,j,level) + &
  954. (cr3(i,j,2) + cr3(i,j,3) + cr3(i,j,33) + cr3(i,j,50)) &
  955. *c1*ye(i,j,iairm)/y(i,j,iair) ! acc. moles/gridbox
  956. o3l(region)%d3(i,j,level) = o3l(region)%d3(i,j,level) + &
  957. (cr3(i,j,4)-2*cr3(i,j,7) + 2*cr3(i,j,6) + cr3(i,j,8) - cr3(i,j,9) + &
  958. cr3(i,j,15) + cr3(i,j,17) + cr3(i,j,42) - cr3(i,j,43) + &
  959. cr3(i,j,45) + cr3(i,j,48) - 0.1*cr3(i,j,49) - cr3(i,j,55) + &
  960. cr2(i,j,1) - cr2(i,j,4) - cr2(i,j,6) - cr2(i,j,13) - 2.*cr2(i,j,10)) &
  961. *c1*ye(i,j,iairm)/y(i,j,iair) ! acc. moles/gridbox
  962. o3l(region)%d3(i,j,level) = o3l(region)%d3(i,j,level) - &
  963. cr4(i,j,1)*(1000./xmair)*ye(i,j,iairm)/y(i,j,iair) !O3 + SO2 (note negative)
  964. !PLS ! ch4+oh
  965. !PLS ch4oh(region)%d3(i,j,level) = ch4oh(region)%d3(i,j,level) + &
  966. !PLS cr3(i,j,20)*c1*ye(i,j,iairm)/y(i,j,iair) ! acc. moles/gridbox
  967. !PLS ! S gas phase production (OH + SO2---> SO4, OH + DMS = 0.25 MSA)
  968. !PLS so4pg(region)%d3(i,j,level) = so4pg(region)%d3(i,j,level) + &
  969. !PLS (0.25*cr3(i,j,58) + cr3(i,j,60))*c1*ye(i,j,iairm)/y(i,j,iair) ! acc. moles/gridbox OH + SO2
  970. !PLS ! SO4 wet production
  971. !PLS so4pa(region)%d3(i,j,level) = so4pa(region)%d3(i,j,level) - &
  972. !PLS (cr4(i,j,1)+cr4(i,j,2))*(1000./xmair)*ye(i,j,iairm)/y(i,j,iair) ! acc. moles/gridbox note neg.
  973. do i01=1,nreac
  974. budrrg(nzone,nzone_v,i01)=budrrg(nzone,nzone_v,i01)+ &
  975. cr3(i,j,i01)*c1*ye(i,j,iairm)/y(i,j,iair) !units mole
  976. end do
  977. do i01=1,nreacw
  978. budrwg(nzone,nzone_v,i01)=budrwg(nzone,nzone_v,i01)- &
  979. cr4(i,j,i01)*(1000./xmair)*ye(i,j,iairm)/y(i,j,iair) ! mole
  980. !note: changed sign to get 'positive' budget, just a
  981. ! matter of definition, !CMK
  982. end do
  983. end do
  984. end do
  985. !sum up global budgets (done in chemistry/chemistry_done)
  986. end subroutine REACBUD
  987. !EOC
  988. #endif
  989. end subroutine EBI
  990. !EOC
  991. !--------------------------------------------------------------------------
  992. ! TM5 !
  993. !--------------------------------------------------------------------------
  994. !BOP
  995. !
  996. ! !IROUTINE: WETS
  997. !
  998. ! !DESCRIPTION: aqueous phase chemistry of sulfur (and other): oxidation of
  999. ! SO2 and uptake of other gases in the aqueous phase
  1000. ! Method : implicit solution of oxidation of SO2
  1001. !\\
  1002. !\\
  1003. ! !INTERFACE:
  1004. !
  1005. #ifdef with_budgets
  1006. subroutine wetS(region, level, is, js, y0, dt, y, ye, c4, status)
  1007. #else
  1008. subroutine wetS(region, level, is, js, y0, dt, y, ye, status)
  1009. #endif
  1010. !
  1011. ! !USES:
  1012. !
  1013. use Dims, only: CheckShape, idatei
  1014. use global_data, only: region_dat
  1015. use reaction_data, only: nreacw, ntlow, kso2hp, kso2o3
  1016. use chem_param
  1017. use dims, only: im, jm
  1018. use Binas, only: Avog
  1019. !
  1020. ! !INPUT PARAMETERS:
  1021. !
  1022. integer,intent(in) :: region !region region under operation (provides im,jm,lm via chemistry.mod)
  1023. integer,intent(in) :: level, is, js ! vertical level, tile start indices
  1024. real, intent(in) :: dt ! chemistry timestep
  1025. real, intent(in) :: y0(is:,js:,:) ! initial concentration
  1026. !
  1027. ! !OUTPUT PARAMETERS:
  1028. !
  1029. real, intent(out) :: y(is:,js:,:) ! concentrations at time is t
  1030. integer,intent(out) :: status
  1031. !
  1032. ! !INPUT/OUTPUT PARAMETERS:
  1033. !
  1034. real, intent(inout) :: ye(is:,js:,:) ! extra fields (temp, cc, pH)
  1035. #ifdef with_budgets
  1036. real, intent(inout) :: c4(is:,js:,:) ! budget accumulatior
  1037. #endif
  1038. !
  1039. ! !REVISION HISTORY:
  1040. ! ???? - Ad Jeuken (KNMI) and Frank Dentener (IMAU) - v0
  1041. ! Jan 2002 - Maarten Krol (IMAU) - adapted for TM5
  1042. ! Feb 2007 - Elisabetta Vignati (JRC) - adapted for TM5/M7
  1043. ! 22 Mar 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  1044. !
  1045. !EOP
  1046. !------------------------------------------------------------------------
  1047. !BOC
  1048. character(len=*), parameter :: rname = mname//'/Wets'
  1049. #ifdef with_zoom
  1050. integer, dimension(:,:), pointer :: zoomed
  1051. #endif
  1052. integer n,i,j,l,itemp,iter
  1053. real x1,x2,x3,b1,b2,so2x,dh2o2,dso2,disc,dnh3,dn2o5,xso2o3a,xso2o3b,co2
  1054. real,parameter :: rg=0.08314
  1055. real,dimension(:,:),allocatable :: hkso2 ! Henry's constant for sulfur dioxide
  1056. real,dimension(:,:),allocatable :: hkh2o2 ! Henry's constant for hydroperoxide
  1057. real,dimension(:,:),allocatable :: hko3 ! Henry's constant for ozone
  1058. real,dimension(:,:),allocatable :: dkso2 ! Dissociation constant for SO2
  1059. real,dimension(:,:),allocatable :: dkhso3 ! Dissociation constant for HSO3-
  1060. real,dimension(:,:),allocatable :: dkh2o ! dissociation constant water
  1061. real,dimension(:,:),allocatable :: dknh3 ! dissociation constant ammonia
  1062. real,dimension(:,:),allocatable :: hknh3 ! Henry's constant ammonia
  1063. real,dimension(:,:),allocatable :: hkco2 ! Henry's constant CO2
  1064. real,dimension(:,:),allocatable :: dkco2 ! Dissociation constant CO2
  1065. real phs4 ! effective dissolvation of S(IV)
  1066. real phso2 ! effective dissolvation of SO2
  1067. real phh2o2 ! effective dissolvation of H2O2
  1068. real phozone ! effective dissolvation of O3
  1069. real,dimension(:,:),allocatable :: hplus !concentration h+
  1070. real,dimension(:,:),allocatable :: sulph !accumul+coarse mode sulphate
  1071. real a1,a2,a,b,c,z,ft ! help variables
  1072. real xcov,xliq,xl,temp,rt,ztr,h2o,air,press ! meteo
  1073. real,dimension(:,:,:),allocatable :: rw ! reaction rates
  1074. logical,dimension(:,:),allocatable :: cloudy
  1075. integer :: i1, i2, j1, j2
  1076. real :: l_sum_wet
  1077. ! --- begin --------------------------------
  1078. call Get_DistGrid( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  1079. ! check arguments ...
  1080. call CheckShape( (/i2-i1+1, j2-j1+1, maxtrace/), shape(y0), status )
  1081. IF_NOTOK_RETURN(status=1)
  1082. call CheckShape( (/i2-i1+1, j2-j1+1, maxtrace/), shape(y ), status )
  1083. IF_NOTOK_RETURN(status=1)
  1084. call CheckShape( (/i2-i1+1, j2-j1+1, n_extra /), shape(ye), status )
  1085. IF_NOTOK_RETURN(status=1)
  1086. #ifdef with_budgets
  1087. call CheckShape( (/i2-i1+1, j2-j1+1, nreacw /), shape(c4), status )
  1088. IF_NOTOK_RETURN(status=1)
  1089. #endif
  1090. #ifdef with_zoom
  1091. zoomed => region_dat(region)%zoomed
  1092. #endif
  1093. allocate(hkso2 (i1:i2, j1:j2))
  1094. allocate(hkh2o2 (i1:i2, j1:j2))
  1095. allocate(hko3 (i1:i2, j1:j2))
  1096. allocate(dkso2 (i1:i2, j1:j2))
  1097. allocate(dkhso3 (i1:i2, j1:j2))
  1098. allocate(dkh2o (i1:i2, j1:j2))
  1099. allocate(dknh3 (i1:i2, j1:j2))
  1100. allocate(hknh3 (i1:i2, j1:j2))
  1101. allocate(hkco2 (i1:i2, j1:j2))
  1102. allocate(dkco2 (i1:i2, j1:j2))
  1103. allocate(hplus (i1:i2, j1:j2))
  1104. allocate(rw (i1:i2, j1:j2, nreacw))
  1105. allocate(cloudy (i1:i2, j1:j2))
  1106. allocate(sulph (i1:i2, j1:j2))
  1107. !-----------------------------
  1108. ! wet phase reactions
  1109. !-----------------------------
  1110. rw =0.0
  1111. hplus=0.0
  1112. !
  1113. ! JEW: now scaled to 2000 to account for annual growth of ~2ppbv/yr-1
  1114. !
  1115. co2=3.69e-4 ! was parameter co2=3.75e-4,
  1116. #if defined (with_budgets)
  1117. l_sum_wet = 0.0
  1118. #endif
  1119. do j = j1, j2
  1120. do i = i1, i2
  1121. #ifdef with_zoom
  1122. if(zoomed(i,j)/=region) cycle
  1123. #endif
  1124. cloudy(i,j)=.false.
  1125. ! lwc is dimensionless
  1126. if ((ye(i,j,ilwc) > 1e-10).and.(ye(i,j,icc) > 0.02)) then
  1127. cloudy(i,j)=.true.
  1128. TEMP=ye(i,j,i_temp)
  1129. ZTR=(1./TEMP-1./298)
  1130. RT=TEMP*rg
  1131. ITEMP=nint(TEMP-float(ntlow))
  1132. !
  1133. !CEV sulph is the initial total sulphate content in accumulation+
  1134. !coarse mode, the incloud production is calculated on bulk
  1135. !characteristics, and redistributed on the modes depending on their
  1136. !particle numbers
  1137. #ifdef with_m7
  1138. sulph(i,j)=y0(i,j,iso4acs)+y0(i,j,iso4cos)
  1139. #else
  1140. sulph(i,j)=y0(i,j,iso4)
  1141. #endif
  1142. !
  1143. ! Henry and dissociation equilibria
  1144. !
  1145. dkh2o(i,j) =1.01e-14*exp(-6706.0 *ztr) !h2o<=>hplus+so3--
  1146. !bug hkco2(i,j) =3.4e-2*(2420.*ztr) ! is already dimensionless
  1147. hkco2(i,j) =3.4e-2*exp(2420.*ztr) ! is already dimensionless
  1148. dkco2(i,j) =4.5E-7*exp(-1000.*ztr) !co2aq<=>hco3- + hplus
  1149. hkso2(i,j) =henry(iso2,itemp)*rt !dimensionless
  1150. dknh3(i,j) =1.8e-5*exp(-450.*ztr) !nh3<=>nh4+ + OH-
  1151. hknh3(i,j) =henry(inh3,itemp)*rt !dimensionless
  1152. hkh2o2(i,j)=henry(ih2o2,itemp)*rt !dimensionless
  1153. hko3(i,j) =henry(io3,itemp)*rt !dimensionless
  1154. dkso2(i,j) =1.7e-2*exp(2090.*ztr) !so2<=>hso3m+hplus
  1155. dkhso3(i,j)=6.6e-8*exp(1510.*ztr) !hso3m<=>so3-- + hplus
  1156. !
  1157. ! calculate H+ from initial sulfate, ammonium, hno3, and nh3
  1158. ! if solution is strongly acidic no further calculations are performed
  1159. !
  1160. xl=ye(i,j,ilwc)*Avog*1e-3/ye(i,j,icc)
  1161. !x1 is initial strong acidity from SO4 and NO3
  1162. !
  1163. !acidity from strong acids alone
  1164. !
  1165. !CMK hplus(i,j)=(2.*y0(i,j,iso4)+y0(i,j,imsa)-y0(i,j,inh4)+ &
  1166. !CMK y0(i,j,ihno3)+y0(i,j,ino3_a))/xl
  1167. hplus(i,j)=(2.*sulph(i,j) + &
  1168. y0(i,j,imsa)-y0(i,j,inh4)+ &
  1169. y0(i,j,ihno3)+y0(i,j,ino3_a))/xl
  1170. end if
  1171. end do
  1172. end do
  1173. do iter=1,10
  1174. do j=j1, j2
  1175. do i=i1, i2
  1176. #ifdef with_zoom
  1177. if ( zoomed(i,j) /= region ) cycle
  1178. #endif
  1179. ! only if solution pH>4.5
  1180. if ( cloudy(i,j) .and. hplus(i,j) < 3e-5 ) then
  1181. xl=ye(i,j,ilwc)*Avog*1e-3/ye(i,j,icc)
  1182. !CEV y0(i,j,iso4)---> sulph(i,j)
  1183. x1=(2.*sulph(i,j)+y0(i,j,imsa)+y0(i,j,ihno3)+ &
  1184. y0(i,j,ino3_a))/xl
  1185. !x2 is initial total NHx
  1186. x2=(y0(i,j,inh3)+y0(i,j,inh4))/xl
  1187. !x3 is combined dissolution and solubility const for CO2
  1188. x3=dkco2(i,j)*hkco2(i,j)*co2
  1189. a1=dkh2o(i,j)/dknh3(i,j)*(1.+1./hknh3(i,j)) ! integration constant
  1190. a2=y0(i,j,iso2)/xl !initial SO2
  1191. ! trap division by zero ...
  1192. if ( hplus(i,j) == 0.0 ) then
  1193. z = 0.0
  1194. else
  1195. z = a2/( hplus(i,j)/dkso2(i,j)*(1.0+1.0/hkso2(i,j)) + dkhso3(i,j)/hplus(i,j) + 1.0 )
  1196. end if
  1197. ! solve quadratic equation for new H+ concentration:
  1198. a=1.+x2/(a1+hplus(i,j))
  1199. b=-x1-z
  1200. c=-x3-2.*dkhso3(i,j)*z
  1201. z=max(0.,(b*b-4.*a*c))
  1202. hplus(i,j)=max(1.e-10,(-b+sqrt(z))/(2.*a))
  1203. end if
  1204. end do !
  1205. end do ! i,j loop
  1206. end do !iter
  1207. do j=j1,j2
  1208. do i=i1,i2
  1209. #ifdef with_zoom
  1210. if(zoomed(i,j)/=region) cycle
  1211. #endif
  1212. if (cloudy(i,j)) then
  1213. temp=ye(i,j,i_temp)
  1214. ZTR=(1./TEMP-1./298)
  1215. xliq=ye(i,j,ilwc)/ye(i,j,icc)
  1216. xl=ye(i,j,ilwc)*Avog*1e-3/ye(i,j,icc)
  1217. ye(i,j,iph)=-log10(hplus(i,j)) ! pH for diagnostics
  1218. ! phase factor ratio of aqueous phase to gas phase concentration
  1219. phs4 =hkso2(i,j) *(1.+dkso2(i,j)/hplus(i,j)+ &
  1220. dkso2(i,j)*dkhso3(i,j)/hplus(i,j)/hplus(i,j))*xliq
  1221. phso2 =hkso2(i,j) *xliq
  1222. phh2o2 =hkh2o2(i,j)*xliq
  1223. phozone=hko3(i,j) *xliq
  1224. ! the original rate equations could be partly in look-up table
  1225. rw(i,j,KSO2HP) =8e4*exp(-3560.*ztr)/(0.1+hplus(i,j))
  1226. XSO2O3A=4.39e11*exp(-4131./temp)+2.56e3*exp(-966./temp) !S(IV)
  1227. XSO2O3B=2.56e3*exp(-966./temp)/hplus(i,j)
  1228. !divide by [H+]!S(IV)
  1229. ! make rate constants dimensionless by multiplying
  1230. ! by (1./xliq/avo=6e20)
  1231. ! multiply with the fractions of concentrations residing
  1232. ! in the aqueous phase
  1233. rw(i,j,KSO2HP)=rw(i,j,KSO2HP)/xl*phso2/(1.+phs4)*phh2o2/(1.+phh2o2)
  1234. rw(i,j,KSO2O3)=(XSO2O3A+XSO2O3B)/xl*phs4/(1.+phs4)*phozone/ &
  1235. (1.+phozone)
  1236. end if !cloudy
  1237. end do !
  1238. end do ! I,J, LOOP
  1239. !------------- Start main loop
  1240. do j=j1,j2
  1241. do i=i1,i2
  1242. #ifdef with_zoom
  1243. if(zoomed(i,j)/=region) cycle
  1244. #endif
  1245. !
  1246. ! only cloud chemistry if substantial amount of clouds are present
  1247. !
  1248. if (cloudy(i,j)) then
  1249. !
  1250. ! oxidation of S(IV) by O3
  1251. !
  1252. so2x=y0(i,j,iso2)
  1253. xcov=ye(i,j,icc)
  1254. x1=min(100.,rw(i,j,kso2o3)*y0(i,j,io3)*dt)
  1255. dso2=y0(i,j,iso2)*xcov*(exp(-x1)-1.)
  1256. !only applied to xcov part of cloud
  1257. !CMK print *, i,j, xcov, x1, y0(i,j,iso2), dso2
  1258. dso2=max(-y0(i,j,io3)*xcov,dso2)! limit to o3 availability
  1259. !CEV y(i,j,iso2)=y0(i,j,iso2)+dso2
  1260. !NOTE CMK: parallel MPI should take care here!
  1261. #ifdef with_m7
  1262. ft = y0(i,j,iacs_n) + y0(i,j,icos_n)
  1263. if (ft > tiny(ft)) then
  1264. y(i,j,iso4acs)=y0(i,j,iso4acs)-dso2*(y0(i,j,iacs_n)/ft)
  1265. y(i,j,iso4cos)=y0(i,j,iso4cos)-dso2*(y0(i,j,icos_n)/ft)
  1266. y(i,j,iso2)=y0(i,j,iso2)+dso2
  1267. y(i,j,io3)=y0(i,j,io3)+dso2
  1268. #ifdef with_budgets
  1269. c4(i,j,1)=c4(i,j,1)+dso2
  1270. #endif
  1271. else
  1272. !CEV y(i,j,iso4)=y0(i,j,iso4)-dso2
  1273. y(i,j,iso4acs)=y0(i,j,iso4acs)
  1274. y(i,j,iso4cos)=y0(i,j,iso4cos)
  1275. y(i,j,iso2)=y0(i,j,iso2)
  1276. y(i,j,io3)=y0(i,j,io3)
  1277. endif
  1278. !CEV y(i,j,io3)=y0(i,j,io3)+dso2
  1279. #else
  1280. ! gas phase chemistry: ft = 0.
  1281. y(i,j,iso4)=y0(i,j,iso4)-dso2
  1282. y(i,j,iso2)=y0(i,j,iso2)+dso2
  1283. y(i,j,io3)=y0(i,j,io3)+dso2
  1284. #ifdef with_budgets
  1285. c4(i,j,1)=c4(i,j,1)+dso2
  1286. #endif
  1287. #endif
  1288. #ifdef with_budgets
  1289. if ( io3 == 1 ) l_sum_wet = l_sum_wet- &
  1290. dso2 *ye(i,j,iairm)/ (fscale(1)*y(i,j,iair))
  1291. if ( iso2 == 1 ) l_sum_wet = l_sum_wet+ &
  1292. dso2 *ye(i,j,iairm)/ (fscale(1)*y(i,j,iair))
  1293. if ( iso4 == 1 ) l_sum_wet = l_sum_wet- &
  1294. dso2 *ye(i,j,iairm)/ (fscale(1)*y(i,j,iair))
  1295. !CEV c4(i,j,1)=c4(i,j,1)+dso2
  1296. #endif
  1297. xliq=ye(i,j,ilwc)/ye(i,j,icc)
  1298. !
  1299. ! oxidation of S(IV) by H2O2
  1300. !
  1301. !*** here we explicitly solve the dv:
  1302. ! y'=P-Q*y-R*y*y (P and Q are 0=>b3=0.)
  1303. !
  1304. so2x=y(i,j,iso2)
  1305. if ( so2x > tiny(so2x) ) then
  1306. b1=rw(i,j,kso2hp)
  1307. b2=b1*(y0(i,j,ih2o2)-so2x)
  1308. disc=min(100.,sqrt(b2*b2)) ! disc is b2 for b3=0.0
  1309. x1=(b2-disc)/(-2.*b1) ! in this case x1 =0.
  1310. x2=(b2+disc)/(-2.*b1)
  1311. x3=(so2x-x1)/(so2x-x2)*exp(-disc*dt)
  1312. so2x=(x1-x2*x3)/(1.-x3)
  1313. dso2=(so2x-y(i,j,iso2))*xcov
  1314. dso2=max(dso2,-y0(i,j,ih2o2)*xcov)
  1315. !CEV y(i,j,iso2) =y(i,j,iso2)+dso2 ! dso2 is loss of SO2 and H2O2
  1316. ! divide produced SO4 over CO/ACC
  1317. #ifdef with_m7
  1318. ft = y0(i,j,iacs_n) + y0(i,j,icos_n)
  1319. if (ft > tiny(ft)) then
  1320. y(i,j,iso4acs)=y(i,j,iso4acs)-dso2*(y0(i,j,iacs_n)/ft)
  1321. y(i,j,iso4cos)=y(i,j,iso4cos)-dso2*(y0(i,j,icos_n)/ft)
  1322. y(i,j,iso2)=y(i,j,iso2)+dso2
  1323. y(i,j,ih2o2)=y0(i,j,ih2o2)+dso2
  1324. #ifdef with_budgets
  1325. c4(i,j,2)=c4(i,j,2)+dso2
  1326. #endif
  1327. else
  1328. y(i,j,ih2o2) =y0(i,j,ih2o2)
  1329. endif
  1330. #else
  1331. ! gas - phase chemistry
  1332. y(i,j,iso4)=y(i,j,iso4)-dso2
  1333. y(i,j,iso2)=y(i,j,iso2)+dso2
  1334. y(i,j,ih2o2)=y0(i,j,ih2o2)+dso2
  1335. #ifdef with_budgets
  1336. c4(i,j,2)=c4(i,j,2)+dso2
  1337. #endif
  1338. #endif
  1339. #ifdef with_budgets
  1340. if ( ih2o2 == 1 ) l_sum_wet = l_sum_wet- &
  1341. dso2 *ye(i,j,iairm)/ (fscale(1)*y(i,j,iair))
  1342. if ( iso2 == 1 ) l_sum_wet = l_sum_wet- &
  1343. dso2 *ye(i,j,iairm)/ (fscale(1)*y(i,j,iair))
  1344. if ( iso4 == 1 ) l_sum_wet = l_sum_wet+ &
  1345. dso2 *ye(i,j,iairm)/ (fscale(1)*y(i,j,iair))
  1346. !CEV c4(i,j,2)=c4(i,j,2)+dso2
  1347. #endif
  1348. end if
  1349. !
  1350. ! NH3 uptake in cloud droplets is limited by SO4 availability
  1351. ! no HNO3 is considered at this point
  1352. ! assume instantaneous uptake of NH3 incloud only in cloudy part
  1353. !
  1354. ! EQSAM gives hell to any NH3/NH4 interchange. It first drops both in one heap
  1355. ! and then redistributes. So this cloud chemistry reaction does not matter.
  1356. end if !cloudy
  1357. end do ! i,j,loop
  1358. end do !
  1359. #ifdef with_budgets
  1360. sum_wetchem(region) = sum_wetchem(region) + l_sum_wet
  1361. #endif
  1362. !free memory
  1363. deallocate(hkso2 )
  1364. deallocate(hkh2o2 )
  1365. deallocate(hko3 )
  1366. deallocate(dkso2 )
  1367. deallocate(dkhso3 )
  1368. deallocate(dkh2o )
  1369. deallocate(dknh3 )
  1370. deallocate(hknh3 )
  1371. deallocate(hkco2 )
  1372. deallocate(dkco2 )
  1373. deallocate(hplus )
  1374. deallocate(rw )
  1375. deallocate(cloudy )
  1376. deallocate(sulph )
  1377. #ifdef with_zoom
  1378. nullify(zoomed)
  1379. #endif
  1380. status = 0
  1381. end subroutine WETS
  1382. !EOC
  1383. !--------------------------------------------------------------------------
  1384. ! TM5 !
  1385. !--------------------------------------------------------------------------
  1386. !BOP
  1387. !
  1388. ! !IROUTINE: MARK_TRAC
  1389. !
  1390. ! !DESCRIPTION: calculate nox/pan/orgn/hno3 analogous to ebi scheme
  1391. ! ozone production from marked nox
  1392. ! simple nhx chemistry, scaled to real nhx
  1393. !\\
  1394. !\\
  1395. ! !INTERFACE:
  1396. !
  1397. subroutine MARK_TRAC( region, level, is, js, y, rr, rj, dt, ye)
  1398. !
  1399. ! !USES:
  1400. !
  1401. use chem_param
  1402. use Dims, only : CheckShape
  1403. use global_data, only : region_dat
  1404. use dims, only : at, bt, im, jm
  1405. #ifdef with_budgets
  1406. use budget_global, only : budg_dat, nzon_vg
  1407. #endif
  1408. !
  1409. ! !INPUT PARAMETERS:
  1410. !
  1411. integer, intent(in) :: region, level, is, js
  1412. real :: dt ! time step
  1413. !
  1414. ! !INPUT/OUTPUT PARAMETERS:
  1415. !
  1416. real, intent(inout):: y (is:,js:,:) ! concentrations
  1417. real, intent(in) :: rr(is:,js:,:) ! reaction rates
  1418. real, intent(in) :: rj(is:,js:,:) ! photolysis rates
  1419. real, intent(in) :: ye(is:,js:,:) ! help fields ( air masses )
  1420. !
  1421. ! !REVISION HISTORY:
  1422. ! Jan 1999 - fjd
  1423. ! Jan 2002 - MK - adapted for TM5
  1424. ! 22 Mar 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  1425. !
  1426. !EOP
  1427. !------------------------------------------------------------------------
  1428. !BOC
  1429. #ifdef with_zoom
  1430. integer, dimension(:,:), pointer :: zoomed
  1431. #endif
  1432. integer :: status, i1, i2, j1, j2
  1433. ! --- begin --------------------------------
  1434. call Get_DistGrid( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  1435. ! check arguments ...
  1436. call CheckShape( (/i2-i1+1, j2-j1+1, maxtrace/), shape(y ), status )
  1437. call CheckShape( (/i2-i1+1, j2-j1+1, nreac /), shape(rr), status )
  1438. call CheckShape( (/i2-i1+1, j2-j1+1, nj /), shape(rj), status )
  1439. call CheckShape( (/i2-i1+1, j2-j1+1, n_extra /), shape(ye), status )
  1440. #ifdef with_zoom
  1441. zoomed => region_dat(region)%zoomed
  1442. #endif
  1443. call MARK_O3S
  1444. !
  1445. ! more marked tracers possible here
  1446. !
  1447. #ifdef with_zoom
  1448. nullify(zoomed)
  1449. #endif
  1450. contains
  1451. subroutine mark_o3s
  1452. !---------------------------------------------------
  1453. ! marked tracer O3S stratospheric ozone
  1454. !---------------------------------------------------
  1455. #ifndef without_dry_deposition
  1456. use dry_deposition, only: vd
  1457. #endif
  1458. integer :: i, j, nzone, nzone_v
  1459. real :: p3, xl3, o3old
  1460. do j = j1, j2
  1461. do i = i1, i2
  1462. #ifdef with_zoom
  1463. if(zoomed(i,j)/=region) cycle
  1464. #endif
  1465. if (at(level+1)+bt(level+1)*1e5<= 14000) then !
  1466. ! well, you want to count all layers below 140 hPa
  1467. ! (given surface pressure of 1e5 Pa)
  1468. ! in the current model setup (25 layers) this means
  1469. ! 12077 + 1e5*0.00181 = 12258 Pa and above...
  1470. ! p3: production of o3 in stratosphere
  1471. P3 = rj(i,j,jano3)*y(i,j,ino3)+ &
  1472. rj(i,j,jno2)*y(i,j,ino2)
  1473. XL3= rr(i,j,ko3ho2)*y(i,j,iho2)+&
  1474. rr(i,j,ko3oh)*y(i,j,ioh)+ &
  1475. rr(i,j,kno2o3)*y(i,j,ino2)+&
  1476. rj(i,j,jo3d)+&
  1477. rr(i,j,knoo3)*y(i,j,ino)+&
  1478. rr(i,j,kc62)*y(i,j,ieth)+&
  1479. rr(i,j,kc58)*y(i,j,iole)+&
  1480. rr(i,j,kc77)*y(i,j,iisop)
  1481. else
  1482. !
  1483. ! these are only the net destruction reactions
  1484. !
  1485. P3 = 0.
  1486. XL3= rr(i,j,ko3ho2)*y(i,j,iho2)+&
  1487. rr(i,j,ko3oh)*y(i,j,ioh)+&
  1488. rj(i,j,jo3d)+&
  1489. rr(i,j,kc62)*y(i,j,ieth)+&
  1490. rr(i,j,kc58)*y(i,j,iole)+&
  1491. rr(i,j,kc77)*y(i,j,iisop)
  1492. ! add up deposition....
  1493. #ifndef without_dry_deposition
  1494. if ( level == 1 ) &
  1495. XL3 = XL3 + vd(region,io3)%surf(i,j)/ye(i,j,idz)
  1496. #endif
  1497. end if
  1498. o3old=y(i,j,io3s)
  1499. y(i,j,io3s)=(o3old+p3*dt)/(1.+xl3*dt)
  1500. #ifdef with_budgets
  1501. nzone=budg_dat(region)%nzong(i,j) ! global budget
  1502. nzone_v=nzon_vg(level)
  1503. budmarkg(nzone,nzone_v,1)=budmarkg(nzone,nzone_v,1)+ &
  1504. (y(i,j,io3s)-o3old)*ye(i,j,iairm)*1000./xmair/y(i,j,iair)
  1505. #endif
  1506. end do
  1507. end do !i,j
  1508. end subroutine MARK_O3S
  1509. end subroutine MARK_TRAC
  1510. !EOC
  1511. end module EBISCHEME