module_data_cmu_bulkaqchem.F

References to this file elsewhere.
1 !**********************************************************************************  
2 ! This computer software was prepared by Battelle Memorial Institute, hereinafter
3 ! the Contractor, under Contract No. DE-AC05-76RL0 1830 with the Department of 
4 ! Energy (DOE). NEITHER THE GOVERNMENT NOR THE CONTRACTOR MAKES ANY WARRANTY,
5 ! EXPRESS OR IMPLIED, OR ASSUMES ANY LIABILITY FOR THE USE OF THIS SOFTWARE.
6 !
7 ! MOSAIC module: see module_mosaic_driver.F for information and terms of use
8 !**********************************************************************************  
9 
10       module module_data_cmu_bulkaqchem
11 
12 
13       implicit none
14 
15 
16 
17 !-----------------------------------------------------------------------
18 !   aerpar.inc
19 !-----------------------------------------------------------------------
20 !******************************************************************
21 !                        aerosol parameters
22 !******************************************************************
23 !
24 ! useful constants
25 !
26       double precision pi, pi6
27       parameter (pi  = 3.14159)
28       parameter (pi6 = pi/6.0)
29 
30       double precision rho
31       parameter (rho = 1.4e12)       ! particle density [ug/m^3]
32 !
33 ! aerosol components in the aerosol concentration vector
34 !
35       integer nas, nah, naa, nan, nac, na4, naw, nae, nao, nar
36       integer nahso5, nahmsa, naspec
37       parameter (nas =  1)           ! sodium
38       parameter (nah =  2)           ! hydrogen
39       parameter (naa =  3)           ! ammonium
40       parameter (nan =  4)           ! nitrate
41       parameter (nac =  5)           ! chloride
42       parameter (na4 =  6)           ! sulfate
43       parameter (naw =  7)           ! water
44       parameter (nae =  8)           ! elemental carbon
45       parameter (nao =  9)           ! organics
46       parameter (nar = 10)           ! crustal
47       parameter (nahso5 = 11)        ! hso5-
48       parameter (nahmsa = 12)        ! hmsa
49       parameter (naspec = 12)        ! number of aerosol species
50 !
51 ! condensible gas-phase components in local arrays
52 !
53       integer ngca, ngcn, ngcc, ngc4, ngco, ngcspec
54       parameter (ngca =  1)          ! ammonia
55       parameter (ngcn =  2)          ! nitric acid
56       parameter (ngcc =  3)          ! hydrochloric acid
57       parameter (ngc4 =  4)          ! gas-phase sulfate
58       parameter (ngco =  5)          ! gas-phase organics
59       parameter (ngcspec = 5)        ! number of condensible gas-phase species
60 !
61 ! condensible gas-phase components in global gas-phase array
62 !
63 ! this must be customized to have the correct addresses
64 !
65       integer nga, ngn, ngc, ng4, ngo, ngspec
66       parameter (nga =  1)           ! ammonia
67       parameter (ngn =  2)           ! nitric acid
68       parameter (ngc =  3)           ! hydrochloric acid
69       parameter (ng4 =  4)           ! gas-phase sulfate
70       parameter (ngo =  5)           ! gas-phase organics
71       parameter (ngspec = 5)         ! number of condensible gas-phase species
72 !
73 ! total number of gas phase species so we know where the aerosol starts
74 !
75       integer ngtotal, ngas, naers
76 !     parameter (ngtotal = 50)
77       parameter (ngtotal = 26) 		! 2004-nov-15 rce
78       parameter (ngas=ngtotal)
79       parameter (naers=naspec)
80 
81 
82 
83 !-----------------------------------------------------------------------
84 !   droppar.inc
85 !-----------------------------------------------------------------------
86 ! updated droppar.inc for the bulk model
87 ! last update : 10 june 1998
88 !*************************************************************************
89 !                                droppar.inc
90 !*************************************************************************
91 !
92 !                aqueous-phase parameters and variables
93 !
94 ! aqueous-phase components
95 !
96 !   important : all components have the same positions in
97 !               both aerosol and aqueous matrices
98 !               never change this convention because aqmain
99 !               depends on it
100 !
101       integer ksod, khyd, kamm, knit, kchl, ksvi, kwat, kec, koc, kcru
102       parameter (ksod = nas)               ! na(+)
103       parameter (khyd = nah)               ! h(+)
104       parameter (kamm = naa)               ! nh4(+)
105       parameter (knit = nan)               ! no3(-)
106       parameter (kchl = nac)               ! cl(-)
107       parameter (ksvi = na4)               ! s(vi)
108       parameter (kwat = naw)               ! h2o
109       parameter (kec  = nae)               ! ec
110       parameter (koc  = nao)               ! oc
111       parameter (kcru = nar)               ! crustal
112 !      parameter (khso5 = 1)                ! hso5-
113 !      parameter (khmsa = 2)                ! hmsa
114 !      parameter (kform = 3)                ! formic acid
115 !
116 ! gases in local array
117 !
118 !     incorrect  ******* to be fixed *************
119       integer ngso2, ngh2o2, nghcho, nghcooh
120       integer nghno2, ngno, ngno2, ngo3, ngpan, ngoh, ngho2, ngno3
121       integer ngch3o2, ngch3o2h, ngch3oh, ngch3co3h
122       parameter (ngso2 = 11)
123       parameter (ngh2o2 = 12)
124       parameter (nghcho = 13)
125       parameter (nghcooh = 14)
126       parameter (nghno2 = 15)
127       parameter (ngno = 16)
128       parameter (ngno2 = 17)
129       parameter (ngo3 = 18)
130       parameter (ngpan = 19)
131       parameter (ngoh = 20)
132       parameter (ngho2 = 21)
133       parameter (ngno3 = 22)
134       parameter (ngch3o2 = 23)
135       parameter (ngch3o2h = 24)
136       parameter (ngch3oh = 25)
137       parameter (ngch3co3h = 26)
138 !
139 !     number of equations for aqueous-phase chemistry solution
140 !
141       integer meqn1max
142       parameter (meqn1max = 20)
143       integer, save :: meqn1 = meqn1max
144 !
145 !     activation diameter (dry)
146 !
147       double precision dactiv
148       parameter (dactiv = 0.7e-6)       ! in m
149 !
150 !
151 !
152 !     wet diameter
153 !
154       double precision avdiam
155       parameter (avdiam = 20.e-6)
156 !
157 !     choice of expression for iron chemistry
158 !               = 0 (no iron/manganese chemistry)
159 !          kiron = 1 (phenomenological, martin et al., 1991)
160 !                = 2 (martin, 1984)
161 !
162       integer kiron
163 !     parameter (kiron = 1)            ! was 1
164 !     parameter (kiron = 0)            ! rce 2004-mar-24 - turn off metal chem
165       parameter (kiron = 1)            ! rce 2005-jan-17 - turn it back on
166 !
167 !     choice of turning on or off radical chemisty
168 !     (it is better to turn it off during the night)
169 !
170       integer, save :: iradical
171 !     parameter (iradical = 0)		! rce 2004-nov-15 - now a common var
172 
173 !
174 !     choice of turning off chlorine chemistry
175 !
176       double precision chlorine
177       parameter (chlorine = 0.0)
178 !
179 !     parameter for scaling of photolysis rates
180 !
181       double precision, save :: photo
182 !     parameter (photo = 1.0)
183 !     parameter (photo = 0.0) 		! rce 2004-mar-24 - turn off photo chem
184 					! rce 2004-nov-15 - now a common var
185 !
186 !     fraction of crustal material that is alkaline
187 !
188       double precision caratio
189 !     parameter (caratio = 0.05)        ! was 0.1
190 ! rce 2005-jul-14 - reduce caratio to .001 to get lower ph
191 !     with 0.05 value, ca=.05*oin, and the initial aerosol is alkaline
192       parameter (caratio = 0.001)       
193 !
194 !
195 !
196 !     fraction of liquid water content that goes to each s.r. section
197 !
198       double precision frac1, frac2
199       parameter (frac1 = 0.8)               ! fraction of lwc in sect. 1
200       parameter (frac2 = 0.2)               ! fraction of lwc in sect. 2
201 !
202 !
203 !     assumption : fe(3+) and mn(2+) = 0.003%, 0.001% of crustal mass
204 !
205       double precision firon, fman
206 !     parameter (firon = 0.00003)
207 !     parameter (fman = 0.00001)
208 !     parameter (firon = 0.0)          ! rce 2004-mar-24 - turn off metal chem
209 !     parameter (fman  = 0.0)          ! rce 2004-mar-24 - turn off metal chem
210       parameter (firon = 0.00003)      ! rce 2005-jan-17 - turn it back on
211       parameter (fman = 0.00001)       ! rce 2005-jan-17 - turn it back on
212 
213 !     co2 mixing ratio (ppm)
214       double precision, save :: co2_mixrat
215 
216 !     common / aqcmu_cmn11 / iradical, photo, co2_mixrat
217 
218 
219 !-----------------------------------------------------------------------
220 !   dropcom.inc
221 !-----------------------------------------------------------------------
222 !
223 ! common groups and corresponding matrices for aqueous-phase module
224 !
225 	double precision, save :: akeq(17), akhen(21), akre(120)
226 	double precision, save :: wso2, wh2o2, whcho, whcooh, wnh3, whno3, whcl, wh2so4
227 	double precision, save :: wmol(29), amol(3), gmol(22)
228 !	common / drop / diameter, dd, daer
229 !	common / mw / wso2, wh2o2, whcho, whcooh, wnh3, whno3, whcl, wh2so4
230 !	common /aqrates2/akeq,akhen,akre
231 !	common /aqrates3/wmol,amol,gmol
232 
233 	double precision, save :: gcon(22), con(28), cmet(4), rad, wvol, chyd,   &
234 	        temp_cmuaq_cur, pres_cmuaq_cur
235 !	common / sstate / gcon, con, cmet, rad, wvol, chyd,   &
236 !	        temp_cmuaq_cur, pres_cmuaq_cur
237 
238 
239 
240 !-----------------------------------------------------------------------
241 !   math.inc
242 !-----------------------------------------------------------------------
243 !     include file for svode parameters and non-changing values
244 !     input to hybrid.f
245 
246 !     integer itol,itask,istate,iopt,mf,worki,lrw1,liw1
247       integer itol,itask,iopt,mf,worki,lrw1,liw1
248       double precision tola,tolr,workr
249       integer numfunc, mode, nprint, maxfev, ml, mu, lr,ldfjac
250       double precision factor, epsfcn, xtol
251 
252 !      for svode
253       parameter (itol = 4)
254 !     parameter (tola = 1.e-4)             ! was 1.e-3
255       parameter (tola = 1.e-6)             ! 17-may-2006 rce - need smaller tola
256       parameter (tolr = 1.e-5)             ! was 1.e-3
257       parameter (itask = 1)
258 !     parameter (istate = 1)       ! rce 2004-mar-18 - istate is a variable
259       parameter (iopt = 1)
260       parameter (mf = 22)
261       parameter (worki = 100000)             ! maximum steps allowed
262       parameter (workr = 300.0)
263 !  for bulk
264       parameter (lrw1 = 22+9*meqn1max+2*meqn1max**2)
265       parameter (liw1 = 30+meqn1max)
266 !
267 !   where
268 !      itol: 4=use arrays for tolerances
269 !      tola: absolute tolerance in ug/m3
270 !      tolr: relative tolerance
271 !      itask: 1 for normal computation of output values of y at t = tout.
272 !      istate: integer flag (input and output).  set istate = 1.
273 !      iopt: 0 to indicate no optional input used.
274 !      rwork: double precision work array of length at least..
275 !             20 + 16*neq                      for mf = 10,
276 !             22 +  9*neq + 2*neq**2           for mf = 21 or 22,
277 !             22 + 11*neq + (3*ml + 2*mu)*neq  for mf = 24 or 25.
278 !      lrw: declared length of rwork (in user's dimension statement).
279 !      iwork: integer work array of length at least..
280 !             30        for mf = 10,
281 !             30 + neq  for mf = 21, 22, 24, or 25.
282 !          if mf = 24 or 25, input in iwork(1),iwork(2) the lower
283 !          and upper half-bandwidths ml,mu.
284 !      liw: declared length of iwork (in user's dimension statement).
285 !      mf: method flag.  standard values are..
286 !          10 for nonstiff (adams) method, no jacobian used.
287 !          21 for stiff (bdf) method, user-supplied full jacobian.
288 !          22 for stiff method, internally generated full jacobian.
289 !          24 for stiff method, user-supplied banded jacobian.
290 !          25 for stiff method, internally generated banded jacobian.
291 !      iopt: 1 = some optional parameters used
292 !           here:  workr: rwork(6) (max absolute step size allowed -
293 !                                    default value is infinite.)
294 !                  worki: iwork(6) (maximum number of (internally defined)
295 !                                    steps allowed during one call to the
296 !				    solver. the default value is 500.)
297 
298 !      for hybrid.f
299 
300        parameter (numfunc = 7)
301 !      parameter (xtol = 0.1e0**3)
302        parameter (xtol = 1.0e-3)
303        parameter (maxfev = 300*(numfunc+1) )
304        parameter (ml = numfunc - 1, mu = numfunc -1)
305        parameter (epsfcn = 0.0e0, factor = 100., mode = 2)
306        parameter (nprint = 0)
307        parameter (lr = numfunc*(numfunc+1)/2, ldfjac = numfunc)
308 !
309 !      numfunc : number of functions and variables
310 !      xtol : termination occurs when the rel error  between two consecutive
311 !             iterates is at most xtol
312 !      maxfev : termination occurs when the number of calls to fcn is at least maxfev
313 !      ml     : specifies the number of subdiagonals within the band of the
314 !               jacobian matrix.  if the jacobian is not banded, set ml to at
315 !               least n -1.
316 !      mu     : specifies the number of superdiagonals within the band of the
317 !               jacobian matrix.  if the jacobian is not banded, set mu to at
318 !               least n -1.
319 !      epsfcn : used in determining a suitable step length for the
320 !               forward-difference approximation
321 !      factor : used in determining the initial step bound
322 !      mode   : if 1, the variables will be scaled internally; if 2, the
323 !               scaling is specified by the input diag.
324 !      nprint : input variable that enables controlled
325 !               printing of iterates if it is positive. in this case,
326 !               fcn is called with iflag = 0 at the beginning of the first
327 !               iteration and every nprint iterations thereafter and
328 !               immediately prior to return, with x and fvec available
329 !               for printing. if nprint is not positive, no special calls
330 !               of fcn with iflag = 0 are made.
331 
332 
333 
334 !-----------------------------------------------------------------------
335 !   etest_cmn71.inc
336 !-----------------------------------------------------------------------
337 !
338 !   maqurxn_all - if positive, all reactions are enabled.  
339 !           If zero/negative, all reactions rates are zeroed.
340 !   maqurxn_sulf1 - if positive, 4 primary sulfur reactions are enabled.
341 !           This has no effect when maqurxn_all=1. 
342 !           When maqurxn_all=0 & maqurxn_sulf1=1, only the 4 primary
343 !           sulfur reactions (rxns 72-75) are enabled.
344 !
345 !   mopt_eqrt_cons - if =20, certain equilib. constants and reaction rates 
346 !           are modified to allow closer comparison with 
347 !           other cloud chemistry codes
348 !   mequlib_h2o2_ho2m - currently not used
349 !   mgasrxn - currently not used
350 !
351 !   mdiag_fullequil - if positive, warning messages from subr. fullequil 
352 !           are enabled
353 !   mdiag_hybrd - if positive, warning messages from subr. hybrd are enabled
354 !   mdiag_negconc - if positive, warning messages from subr. aqoperator1
355 !           about negative concentrations are enabled
356 !   mdiag_rsrate - if positive, warning messages from subr. aqratesa
357 !           about sulfur mass balance are enabled.  This diagnostic is somewhat
358 !           misleading as some reactions do not conserve sulfur.
359 !   mdiag_svode - if positive, warning messages from subr. svode are enabled
360 !
361 !   mprescribe_ph - if positive, cloudwater ph is set to xprescribe_ph
362 !
363 	integer, save :: maqurxn_all = 1
364 	integer, save :: maqurxn_sulf1 = 0
365 	integer, save :: mopt_eqrt_cons = 0
366 	integer, save :: mequlib_h2o2_ho2m = 0
367 	integer, save :: mgasrxn = 0
368 	integer, save :: mdiag_fullequil = 1
369 	integer, save :: mdiag_hybrd = 1
370 	integer, save :: mdiag_negconc = 1
371 	integer, save :: mdiag_rsrate = 1
372 	integer, save :: mdiag_svode = 1
373 	integer, save :: mprescribe_ph = 0
374 	double precision,    save :: xprescribe_ph = 4.5
375 
376 !	common / etest_cmn71 /   &
377 !      	    maqurxn_all, maqurxn_sulf1, mequlib_h2o2_ho2m,   &
378 !      	    mgasrxn, mopt_eqrt_cons, mprescribe_ph, mdiagaa,   &
379 !      	    xprescribe_ph
380 
381 
382 !   gas constant in [atm/K/(mol/liter)]
383       double precision rideal
384       parameter (rideal = 0.082058e0)
385 
386 !   indices to wmol array, for molecular weights of aqueous species
387       integer kaqx_siv, kaqx_svi, kaqx_no3m, kaqx_h2o2,   &
388               kaqx_clm, kaqx_nh4p, kaqx_hso5m, kaqx_hmsa
389       parameter(kaqx_siv = 1)
390       parameter(kaqx_svi = 2)
391       parameter(kaqx_no3m = 4)
392       parameter(kaqx_h2o2 = 6)
393       parameter(kaqx_clm = 15)
394       parameter(kaqx_nh4p = 19)
395       parameter (kaqx_hso5m = 26)
396       parameter (kaqx_hmsa = 27)
397 
398 
399 
400       end module module_data_cmu_bulkaqchem