CAMP 1.0.0
Chemistry Across Multiple Phases
sub_model_ZSR_aerosol_water.F90
Go to the documentation of this file.
1! Copyright (C) 2021 Barcelona Supercomputing Center and University of
2! Illinois at Urbana-Champaign
3! SPDX-License-Identifier: MIT
4
5!> \file
6!> The camp_sub_model_ZSR_aerosol_water module.
7
8! TODO Incorporate deliquesence calculations
9!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
10!> \page camp_sub_model_ZSR_aerosol_water CAMP: ZSR Aerosol Water
11!!
12!! ZSR aerosol water calculates equilibrium aerosol water content
13!! based on the Zdanovski-Stokes-Robinson mixing rule \cite Jacobson1996 in
14!! the following generalized format:
15!!
16!! \f[
17!! W = \sum\limits_{i=0}^{n}\frac{1000 M_i}{MW_i m_{i}(a_w)}
18!! \f]
19!!
20!! where \f$M\f$ is the concentration of binary electrolyte \f$i\f$
21!! (\f$\mbox{$\mu$g}\,\mbox{m}^{-3}\f$) with molecular weight
22!! \f$MW_i\f$ (\f$\mbox{kg}\,\mbox{mol}^{-1}\f$) and molality
23!! \f$m_{i}\f$ at a given water activity \f$a_w\f$ (RH; 0--1)
24!! contributing to the total aerosol water content \f$W\f$
25!! (\f$\mbox{$\mu$g}\,\mbox{m}^{-3}\f$).
26!!
27!! Input data for ZSR aerosol water calculations have the following format :
28!! \code{.json}
29!! { "camp-data" : [
30!! {
31!! "type" : "SUB_MODEL_ZSR_AEROSOL_WATER",
32!! "aerosol phase" : "my aero phase",
33!! "gas-phase water" : "H2O",
34!! "aerosol-phase water" : "H2O_aq",
35!! "ion pairs" : {
36!! "Na2SO4" : {
37!! "type" : "JACOBSON",
38!! "ions" : {
39!! "Nap" : { "qty" : 2 },
40!! "SO4mm" : {}
41!! },
42!! "Y_j" : [-3.295311e3, 3.188349e4, -1.305168e5, 2.935608e5],
43!! "low RH" : 0.51
44!! },
45!! "H2SO4" : {
46!! "type" : "EQSAM",
47!! "ions" : {
48!! "SO4mm" : {}
49!! },
50!! "NW" : 4.5,
51!! "ZW" : 0.5,
52!! "MW" : 0.0980
53!! }
54!! ...
55!! }
56!! }
57!! ]}
58!! \endcode
59!! The key-value pair \b aerosol \b phase is required to specify the aerosol
60!! phase for which to calculate water content. Key-value pairs
61!! \b gas-phase \b water and \b aerosol-phase \b water must also be present
62!! and specify the names for the water species in each phase. The final
63!! required key-value pair is \b ion \b pairs which should contain a set of
64!! key-value pairs where the key of each member of the set is the name of a
65!! binary electrolyte and the contents contain parameters required to
66!! estimate the contribution of the this electrolyte to total aerosol water.
67!! The name of the electrolyte may or may not refer to an actual aerosol-phase
68!! species.
69!!
70!! Each binary electrolyte must include a \b type that refers to a method
71!! of calculating ion-pair contributions to aerosol water. Valid values for
72!! \b type are \b JACOBSON and \b EQSAM. These are described next.
73!!
74!! Aerosol water from ion pairs with type \b JACOBSON use equations (28) and
75!! (29) in Jacobson et al. (1996) \cite Jacobson1996 where experimentally
76!! determined binary solution molalities are fit to a polynomial as:
77!!
78!! \f[
79!! \sqrt{m_{i}(a_w)} = Y_0 + Y_1 a_w + Y_2 a_w^2 + Y_3 a_w^3 + ...,
80!! \f]
81!!
82!! where \f$Y_j\f$ are the fitting parameters. Thus, \f$m_i(a_w)\f$ is
83!! calculated at each time step, assuming constant \f$a_w\f$. These values
84!! must be included in a key-value pair \b Y_j whose value is an array
85!! with the \f$Y_j\f$ parameters. The size of the array corresponds to the
86!! order of the polynomial equation, which must be greater than 1. The
87!! key-value pair \b low \b RH is required to specify the lowest RH (0--1)
88!! for which this fit is valid. This value for RH will be used for all lower
89!! RH in calculations of \f$m_i(a_w)\f$ as per Jacobson et al. (1996)
90!! \cite Jacobson1996.
91!!
92!! The key-value pair \b ions must contain the set of ions this binary
93!! electrolyte includes. Each species must correspond to a species present in
94!! \b aerosol \b phase and have a \b charge parameter that specifies their
95!! charge (uncharged species are not permitted in this set) and a
96!! \b molecular \b weight \b [\b kg \b mol-1]
97!! (\f$\mbox{kg}\,\mbox{mol}^{-1}\f$) property.
98!! Ions without a \b qty specified are assumed to appear once in the binary
99!! electrolyte. The total molecular weight for the binary electroly
100!! \f$MW_i\f$ is calculated as a sum of its ionic components, and the ion
101!! species concentrations are used to determine the \f$M_i\f$ during
102!! integration. The aerosol-phase water species to be calculated using
103!! the ZSR method must have the key-value pair \b tracer \b type
104!! with value "CONSTANT".
105!!
106!! For the above example, the following input data should be present:
107!! \code{.json}
108!! {
109!! "name" : "H2O",
110!! "type" : "CHEM_SPEC",
111!! "phase" : "GAS",
112!! },
113!! {
114!! "name" : "H2O_aq",
115!! "type" : "CHEM_SPEC",
116!! "tracer type" : "CONSTANT",
117!! "phase" : "AEROSOL",
118!! "density [kg m-3]" : 1.0,
119!! "molecular weight [kg mol-1]" : 0.01801
120!! },
121!! {
122!! "name" : "Nap",
123!! "type" : "CHEM_SPEC",
124!! "phase" : "AEROSOL",
125!! "charge" : 1,
126!! "density [kg m-3]" : 1.0,
127!! "molecular weight [kg mol-1]" : 0.0229898
128!! },
129!! {
130!! "name" : "SO4mm",
131!! "type" : "CHEM_SPEC",
132!! "phase" : "AEROSOL",
133!! "charge" : -2,
134!! "density [kg m-3]" : 1.0,
135!! "molecular weight [kg mol-1]" : 0.09606
136!! },
137!! {
138!! "name" : "my aero phase",
139!! "type" : "AERO_PHASE",
140!! "species" : ["Nap", "SO4mm", H2O_aq"]
141!! }
142!! \endcode
143!! Aerosol water from ion pairs with type \b EQSAM use the parameterization of
144!! Metzger et al. (2002) \cite Metzger2002 for aerosol water content:
145!!
146!! \f[
147!! \sqrt{m_{i}(a_w)} = (NW_i MW_{H2O}/MW_i (1/a_w-1))^{ZW_i}
148!! \f]
149!!
150!! where \f$NW_i\f$ and \f$ZW_i\f$ are fitting parameters \cite Metzger2002,
151!! and must be provided in key-value pairs \b NW and \b ZW, along with the
152!! binary electrolyte molecular weight \b MW
153!! (\f$\mbox{kg}\,\mbox{mol}^{-1}\f$). The key-value pair \b ions must
154!! contain a set of ions that can be summed to calculate \f$M_i\f$ at runtime.
155!!
156!!
157
158! TODO Find a way to incorporate the "regimes" in EQSAM
159
160!> The sub_model_ZSR_aerosol_water_t type and associated functions.
162
166 use camp_constants, only: const
168 use camp_property
170 use camp_util, only: i_kind, dp, to_string, &
173
174 implicit none
175 private
176#define ACT_CALC_JACOBSON 1
177#define ACT_CALC_EQSAM 2
178
179#define NUM_PHASE_ this%condensed_data_int(1)
180#define GAS_WATER_ID_ this%condensed_data_int(2)
181#define NUM_ION_PAIR_ this%condensed_data_int(3)
182#define TOTAL_INT_PARAM_ this%condensed_data_int(4)
183#define TOTAL_FLOAT_PARAM_ this%condensed_data_int(5)
184#define NUM_INT_PROP_ 5
185#define NUM_REAL_PROP_ 0
186#define NUM_ENV_PARAM_ 1
187#define PHASE_ID_(p) this%condensed_data_int(NUM_INT_PROP_+p)
188#define PAIR_INT_PARAM_LOC_(x) this%condensed_data_int(NUM_INT_PROP_+NUM_PHASE_+x)
189#define PAIR_FLOAT_PARAM_LOC_(x) this%condensed_data_int(NUM_INT_PROP_+NUM_PHASE_+NUM_ION_PAIR_+x)
190#define TYPE_(x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x))
191#define JACOB_NUM_CATION_(x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+1)
192#define JACOB_NUM_ANION_(x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+2)
193#define JACOB_CATION_ID_(x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+3)
194#define JACOB_ANION_ID_(x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+4)
195#define JACOB_NUM_Y_(x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+5)
196#define JACOB_GAS_WATER_JAC_ID_(p,x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+5+p)
197#define JACOB_CATION_JAC_ID_(p,x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+5+NUM_PHASE_+p)
198#define JACOB_ANION_JAC_ID_(p,x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+5+2*NUM_PHASE_+p)
199#define EQSAM_NUM_ION_(x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+1)
200#define EQSAM_GAS_WATER_JAC_ID_(p,x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+1+p)
201#define EQSAM_ION_ID_(x,y) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+1+NUM_PHASE_+y)
202#define EQSAM_ION_JAC_ID_(p,x,y) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+1+NUM_PHASE_+EQSAM_NUM_ION_(x)+(y-1)*NUM_PHASE_+p)
203#define JACOB_low_RH_(x) this%condensed_data_real(PAIR_FLOAT_PARAM_LOC_(x))
204#define JACOB_CATION_MW_(x) this%condensed_data_real(PAIR_FLOAT_PARAM_LOC_(x)+1)
205#define JACOB_ANION_MW_(x) this%condensed_data_real(PAIR_FLOAT_PARAM_LOC_(x)+2)
206#define JACOB_Y_(x,y) this%condensed_data_real(PAIR_FLOAT_PARAM_LOC_(x)+2+y)
207#define EQSAM_NW_(x) this%condensed_data_real(PAIR_FLOAT_PARAM_LOC_(x))
208#define EQSAM_ZW_(x) this%condensed_data_real(PAIR_FLOAT_PARAM_LOC_(x)+1)
209#define EQSAM_ION_PAIR_MW_(x) this%condensed_data_real(PAIR_FLOAT_PARAM_LOC_(x)+2)
210#define EQSAM_ION_MW_(x,y) this%condensed_data_real(PAIR_FLOAT_PARAM_LOC_(x)+2+y)
211
213
214 !> Generic test reaction data type
216 contains
217 !> Reaction initialization
218 procedure :: initialize
219 !> Return a real number representing the priority of the sub-model
220 !! calculations. Low priority sub models may depend on the results
221 !! of higher priority sub models.
222 procedure :: priority
223 !> Finalize
224 final :: finalize
226
227 !> Constructor for sub_model_ZSR_aerosol_water_t
229 procedure :: constructor
231
232contains
233
234!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
235
236 !> Constructor for ZSR aerosol water reaction
237 function constructor() result(new_obj)
238
239 !> A new reaction instance
240 type(sub_model_zsr_aerosol_water_t), pointer :: new_obj
241
242 allocate(new_obj)
243
244 end function constructor
245
246!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
247
248 !> Initialize the reaction data, validating component data and loading
249 !! any required information into the condensed data arrays for use during
250 !! solving
251 subroutine initialize(this, aero_rep_set, aero_phase_set, chem_spec_data)
252
253 !> Reaction data
254 class(sub_model_zsr_aerosol_water_t), intent(inout) :: this
255 !> The set of aerosol representations
256 type(aero_rep_data_ptr), pointer, intent(in) :: aero_rep_set(:)
257 !> The set of aerosol phases
258 type(aero_phase_data_ptr), pointer, intent(in) :: aero_phase_set(:)
259 !> Chemical species data
260 type(chem_spec_data_t), intent(in) :: chem_spec_data
261
262 type(property_t), pointer :: spec_props, ion_pairs, ion_pair, sub_props, &
263 ions
264 character(len=:), allocatable :: key_name, spec_name, phase_name
265 integer(kind=i_kind) :: n_phase, n_ion_pair, n_int_param, n_float_param, &
266 i_aero_rep, i_phase, i_ion_pair, i_ion, i_spec, i_sub_prop, &
267 qty, int_val, charge, total_charge, tracer_type
268 real(kind=dp) :: real_val, molecular_weight
269 type(string_t), allocatable :: unique_spec_names(:)
270 character(len=:), allocatable :: str_type, ion_pair_name, ion_name
271
272 ! Get the reaction property set
273 if (.not. associated(this%property_set)) call die_msg(344693903, &
274 "Missing property set needed to initialize ZSR aerosol water"// &
275 " reaction.")
276
277 ! Get the aerosol phase name
278 key_name = "aerosol phase"
279 call assert_msg(613734060, &
280 this%property_set%get_string(key_name, phase_name), &
281 "Missing aerosol phase in ZSR aerosol water reaction.")
282
283 ! Count the instances of the aerosol phase
284 n_phase = 0
285 do i_aero_rep = 1, size(aero_rep_set)
286
287 ! Get the number of instances of the phase in this representation
288 n_phase = n_phase + &
289 aero_rep_set(i_aero_rep)%val%num_phase_instances(phase_name)
290
291 end do
292
293 call assert_msg(450206321, n_phase.gt.0, &
294 "Aerosol phase '"//phase_name//"' not present in any aerosol "// &
295 "representation for ZSR aerosol water reaction.")
296
297 ! Get the ion pairs
298 key_name = "ion pairs"
299 call assert_msg(640916964, &
300 this%property_set%get_property_t(key_name, ion_pairs), &
301 "Missing ion pairs in ZSR aerosol water reaction.")
302
303 ! Count the ion pairs
304 n_ion_pair = ion_pairs%size()
305 call assert_msg(743158990, n_ion_pair .gt. 0, &
306 "Empty ion pair set in ZSR aerosol water reaction.")
307
308 ! Get the number of parameters required for each ion pair
309 n_int_param = num_int_prop_ + n_phase + 2*n_ion_pair
310 n_float_param = num_real_prop_
311 call ion_pairs%iter_reset()
312 do i_ion_pair = 1, n_ion_pair
313
314 ! Get the name of the ion pair
315 call assert(476976534, ion_pairs%get_key(ion_pair_name))
316
317 ! Get the ion pair properties
318 call assert_msg(280814432, ion_pairs%get_property_t(val=ion_pair), &
319 "Missing ion pair properties for '"//ion_pair_name// &
320 "' in ZSR aerosol water reaction.")
321
322 ! Get the activity calculation type
323 key_name = "type"
324 call assert_msg(334930304, ion_pair%get_string(key_name, str_type), &
325 "Missing activity calculation type for ion pair '"// &
326 ion_pair_name//"' in ZSR aerosol water reaction.")
327
328 ! Get the number of parameters according to activity calculation type
329 if (str_type.eq."JACOBSON") then
330
331 ! Get the number of Y_j parameters
332 key_name = "Y_j"
333 call assert_msg(286454243, &
334 ion_pair%get_property_t(key_name, sub_props), &
335 "Missing Y_j parameters for Jacobson activity calculation "//&
336 "for ion pair '"//ion_pair_name//"'.")
337
338 call assert_msg(495036486, sub_props%size().gt.0, &
339 "Insufficient Y_j parameters for Jacobson activity "// &
340 "calculation for ion pair '"//ion_pair_name//"' in "// &
341 "ZSR aerosol water reaction.")
342
343 n_float_param = n_float_param + 3 + sub_props%size()
344 n_int_param = n_int_param + 6 + 3*n_phase
345
346 else if (str_type.eq."EQSAM") then
347
348 ! Get the number of ions
349 key_name = "ions"
350 call assert_msg(244982851, &
351 ion_pair%get_property_t(key_name, sub_props), &
352 "Mission ions for EQSAM activity calculation for ion "// &
353 "pair '"//ion_pair_name//"' in ZSR aerosol water "// &
354 "reaction.")
355
356 call assert_msg(849524804, sub_props%size().gt.0, &
357 "Insufficient ions specified for EQSAM activity "// &
358 "calculation for ion pair '"//ion_pair_name// &
359 "' in ZSR aerosol water reaction.")
360
361 n_float_param = n_float_param + 3 + sub_props%size()
362 n_int_param = n_int_param + 2 + n_phase + (1+n_phase)*sub_props%size()
363
364 else
365 call die_msg(704759248, "Invalid activity type specified for ZSR "// &
366 "aerosol water reaction: '"//str_type//"'")
367 end if
368
369 call ion_pairs%iter_next()
370 end do
371
372
373 ! Allocate space in the condensed data arrays
374 allocate(this%condensed_data_int(n_int_param))
375 allocate(this%condensed_data_real(n_float_param))
376 this%condensed_data_int(:) = int(0, kind=i_kind)
377 this%condensed_data_real(:) = real(0.0, kind=dp)
378
379 ! Save space for the environment-dependent parameters
380 this%num_env_params = num_env_param_
381
382 ! Set some data dimensions
383 num_phase_ = n_phase
384 num_ion_pair_ = n_ion_pair
385 total_int_param_ = n_int_param
386 total_float_param_ = n_float_param
387
388 ! Set the gas-phase water species
389 key_name = "gas-phase water"
390 call assert_msg(386389634, &
391 this%property_set%get_string(key_name, spec_name), &
392 "Missing gas-phase water species name in ZSR aerosol water "// &
393 "reaction.")
394
395 gas_water_id_ = chem_spec_data%gas_state_id(spec_name)
396
397 call assert_msg(709909577, gas_water_id_ .gt. 0, &
398 "Cannot find gas-phase water species '"//spec_name//"' for "// &
399 "ZSR aerosol water reaction.")
400
401 ! Set the aerosol-water species
402 key_name = "aerosol-phase water"
403 call assert_msg(771445226, &
404 this%property_set%get_string(key_name, spec_name), &
405 "Missing aerosol-phase water species name in ZSR aerosol "// &
406 "water reaction.")
407
408 ! Check the tracer type for the aerosol water species
409 call assert(939974986, &
410 chem_spec_data%get_type(spec_name, tracer_type))
411 call assert_msg(145575786, tracer_type.eq.chem_spec_constant, &
412 "ZSR calculated species "//trim(spec_name)// &
413 " must be of tracer type CONSTANT")
414
415 ! Make the PHASE_ID_(x) hold the state id of aerosol water in each
416 ! phase instance. Then the aerosol water id is 1, and the ion
417 ! ids will be relative to the water id in each phase.
418 i_phase = 1
419 do i_aero_rep = 1, size(aero_rep_set)
420 unique_spec_names = aero_rep_set(i_aero_rep)%val%unique_names( &
421 phase_name = phase_name, spec_name = spec_name)
422 if (.not.allocated(unique_spec_names)) cycle
423 do i_spec = 1, size(unique_spec_names)
424 phase_id_(i_phase) = aero_rep_set(i_aero_rep)%val%spec_state_id( &
425 unique_spec_names(i_spec)%string)
426 call assert(204327668, phase_id_(i_phase).gt.0)
427 i_phase = i_phase + 1
428 end do
429 deallocate(unique_spec_names)
430 end do
431 i_phase = i_phase - 1
432 call assert_msg(418435744, i_phase.eq.num_phase_, &
433 "Incorrect number of aerosol water instances in ZSR aerosol "// &
434 "water reaction. Expected "//trim(to_string(num_phase_))// &
435 " but got "//trim(to_string(i_phase)))
436
437 ! Save the ion-pair parameters
438 n_int_param = num_int_prop_ + num_phase_ + 2*num_ion_pair_
439 n_float_param = num_real_prop_
440 call ion_pairs%iter_reset()
441 do i_ion_pair = 1, n_ion_pair
442
443 ! Get the name of the ion pair
444 call assert(476976534, ion_pairs%get_key(ion_pair_name))
445
446 ! Get the ion pair properties
447 call assert(660267400, ion_pairs%get_property_t(val=ion_pair))
448
449 ! Set the location of this ion pair's parameters in the condensed data
450 ! arrays.
451 pair_int_param_loc_(i_ion_pair) = n_int_param + 1
452 pair_float_param_loc_(i_ion_pair) = n_float_param + 1
453
454 ! Get the activity calculation type
455 key_name = "type"
456 call assert(288245799, ion_pair%get_string(key_name, str_type))
457
458 ! Get the number of parameters according to activity calculation type
459 if (str_type.eq."JACOBSON") then
460
461 ! Set the type
462 type_(i_ion_pair) = act_calc_jacobson
463
464 ! Get the Y_j parameters
465 key_name = "Y_j"
466 call assert(227500762, ion_pair%get_property_t(key_name, sub_props))
467 jacob_num_y_(i_ion_pair) = sub_props%size()
468 call sub_props%iter_reset()
469 do i_sub_prop = 1, sub_props%size()
470 call assert_msg(149509565, sub_props%get_real(val=real_val), &
471 "Invalid Y parameter for ion pair '"// &
472 ion_pair_name//"' in ZSR aerosol water reaction.")
473 jacob_y_(i_ion_pair, i_sub_prop) = real_val
474 call sub_props%iter_next()
475 end do
476
477 ! Get the low RH value
478 key_name = "low RH"
479 call assert_msg(462500894, ion_pair%get_real(key_name, real_val), &
480 "Missing 'low RH' value for ion pair '"// &
481 ion_pair_name//"' in ZSR aerosol water reaction.")
482 jacob_low_rh_(i_ion_pair) = real_val
483
484 ! Get the number and id of the ions and the ion-pair molecular weight
485 molecular_weight = 0.0
486 key_name = "ions"
487 call assert_msg(661006818, ion_pair%get_property_t(key_name, ions), &
488 "Mission ions for Jacobson activity calculation for ion "// &
489 "pair '"//ion_pair_name//"' in ZSR aerosol water "// &
490 "reaction.")
491 call assert_msg(880831496, ions%size().eq.2, &
492 "Invalid number of unique ions specified for ion pair '"// &
493 ion_pair_name//"' in for Jacobson activity "// &
494 "calculation in ZSR aerosol water reaction. Expected 2 "// &
495 "got "//trim(to_string(ions%size())))
496 call ions%iter_reset()
497 total_charge = 0
498 do i_ion = 1, 2
499
500 ! Get the ion name
501 call assert(849711956, ions%get_key(ion_name))
502
503 ! Get the qty, if specified
504 qty = 1
505 if (ions%get_property_t(val=sub_props)) then
506 key_name = "qty"
507 if (sub_props%get_int(key_name, int_val)) qty = int_val
508 end if
509
510 ! Get the species properties
511 call assert_msg(315479897, &
512 chem_spec_data%get_property_set(ion_name, spec_props), &
513 "Missing species properties for ion '"//ion_name// &
514 "' in ZSR aerosol water reaction.")
515
516 ! Add the molecular weight
517 key_name = "molecular weight [kg mol-1]"
518 call assert_msg(897812513, &
519 spec_props%get_real(key_name, molecular_weight), &
520 "Missing molecular weight for ion '"//ion_name// &
521 "' in ZSR aerosol water reaction.")
522
523 ! Add the charge from this species
524 key_name = "charge"
525 call assert_msg(310667885, spec_props%get_int(key_name, charge), &
526 "Missing charge for ion '"//ion_name//"' in ZSR "// &
527 "aerosol water reaction.")
528
529 if (charge.gt.0) then
530 jacob_num_cation_(i_ion_pair) = qty
531 jacob_cation_mw_(i_ion_pair) = molecular_weight
532 else if (charge.lt.0) then
533 jacob_num_anion_(i_ion_pair) = qty
534 jacob_anion_mw_(i_ion_pair) = molecular_weight
535 else
536 call die_msg(899416917, "Neutral species '"//ion_name// &
537 "' not allowed in ZSR aerosol water reaction ion pair")
538 end if
539
540 ! Add contribution to total charge
541 total_charge = total_charge + qty * charge
542
543 ! Get the state ids for this species
544 i_phase = 1
545 do i_aero_rep = 1, size(aero_rep_set)
546 unique_spec_names = aero_rep_set(i_aero_rep)%val%unique_names( &
547 phase_name = phase_name, spec_name = ion_name)
548 if (.not.allocated(unique_spec_names)) cycle
549 do i_spec = 1, size(unique_spec_names)
550 if (charge.gt.0) then
551 if (i_phase.eq.1) then
552 jacob_cation_id_(i_ion_pair) = &
553 aero_rep_set(i_aero_rep)%val%spec_state_id( &
554 unique_spec_names(i_spec)%string) - &
555 phase_id_(i_phase)
556 else
557 call assert(473680545, jacob_cation_id_(i_ion_pair).eq. &
558 aero_rep_set(i_aero_rep)%val%spec_state_id( &
559 unique_spec_names(i_spec)%string) - &
560 phase_id_(i_phase))
561 end if
562 else
563 if (i_phase.eq.1) then
564 jacob_anion_id_(i_ion_pair) = &
565 aero_rep_set(i_aero_rep)%val%spec_state_id( &
566 unique_spec_names(i_spec)%string) - &
567 phase_id_(i_phase)
568 else
569 call assert(234155524, jacob_anion_id_(i_ion_pair).eq. &
570 aero_rep_set(i_aero_rep)%val%spec_state_id( &
571 unique_spec_names(i_spec)%string) - &
572 phase_id_(i_phase))
573 end if
574 end if
575 i_phase = i_phase + 1
576 end do
577 deallocate(unique_spec_names)
578 end do
579 i_phase = i_phase - 1
580 call assert_msg(623684811, i_phase.eq.num_phase_, &
581 "Incorrect number of instances of ion species '"// &
582 ion_name//"' in ZSR aerosol water reaction. Expected "// &
583 trim(to_string(num_phase_))//" but got "// &
584 trim(to_string(i_phase)))
585
586 ! Get the next ion
587 call ions%iter_next()
588
589 end do
590
591 call assert_msg(319151390, total_charge.eq.0, &
592 "Charge imbalance for ion pair '"//ion_pair_name// &
593 " in ZSR aerosol water reaction. Total charge: "// &
594 trim(to_string(total_charge)))
595
596 n_float_param = n_float_param + 3 + jacob_num_y_(i_ion_pair)
597 n_int_param = n_int_param + 6 + 3*n_phase
598
599 else if (str_type.eq."EQSAM") then
600
601 ! Set the type
602 type_(i_ion_pair) = act_calc_eqsam
603
604 ! Get the required parameters for calculating activity
605 key_name = "NW"
606 call assert_msg(692339107, &
607 ion_pair%get_real(key_name, eqsam_nw_(i_ion_pair)), &
608 "Missing parameter NW for ion pair '"//ion_pair_name// &
609 "' in ZSR aerosol water reaction.")
610
611 key_name = "ZW"
612 call assert_msg(894917625, &
613 ion_pair%get_real(key_name, eqsam_zw_(i_ion_pair)), &
614 "Missing parameter ZW for ion pair '"//ion_pair_name// &
615 "' in ZSR aerosol water reaction.")
616
617 key_name = "MW"
618 call assert_msg(272128568, &
619 ion_pair%get_real(key_name, eqsam_ion_pair_mw_(i_ion_pair)), &
620 "Missing parameter MW for ion pair '"//ion_pair_name// &
621 "' in ZSR aerosol water reaction.")
622
623 ! Get the number and id of ions
624 key_name = "ions"
625 call assert(381088140, ion_pair%get_property_t(key_name, ions))
626 eqsam_num_ion_(i_ion_pair) = ions%size()
627 call ions%iter_reset()
628 do i_ion = 1, ions%size()
629
630 ! Get the ion name
631 call assert(849711956, ions%get_key(ion_name))
632
633 ! Get the species properties
634 call assert_msg(826137761, &
635 chem_spec_data%get_property_set(ion_name, spec_props), &
636 "Missing species properties for ion '"//ion_name// &
637 "' in ZSR aerosol water reaction.")
638
639 ! Add the molecular weight
640 key_name = "molecular weight [kg mol-1]"
641 call assert_msg(598142298, &
642 spec_props%get_real(key_name, molecular_weight), &
643 "Missing molecular weight for ion '"//ion_name// &
644 "' in ZSR aerosol water reaction.")
645 eqsam_ion_mw_(i_ion_pair, i_ion) = molecular_weight
646
647 ! Set the ion id (relative to water within the specified phase)
648 i_phase = 1
649 do i_aero_rep = 1, size(aero_rep_set)
650 unique_spec_names = aero_rep_set(i_aero_rep)%val%unique_names( &
651 phase_name = phase_name, spec_name = ion_name)
652 if (.not.allocated(unique_spec_names)) cycle
653 do i_spec = 1, size(unique_spec_names)
654 if (i_phase.eq.1) then
655 eqsam_ion_id_(i_ion_pair,i_ion) = &
656 aero_rep_set(i_aero_rep)%val%spec_state_id( &
657 unique_spec_names(i_spec)%string) - &
658 phase_id_(i_phase)
659 else
660 call assert(973648240, eqsam_ion_id_(i_ion_pair,i_ion) .eq. &
661 aero_rep_set(i_aero_rep)%val%spec_state_id( &
662 unique_spec_names(i_spec)%string) - &
663 phase_id_(i_phase))
664 end if
665 i_phase = i_phase + 1
666 end do
667 deallocate(unique_spec_names)
668 end do
669 i_phase = i_phase - 1
670 call assert_msg(900921350, i_phase.eq.num_phase_, &
671 "Incorrect number of instances of ion species '"// &
672 ion_name//"' in ZSR aerosol water reaction. Expected "// &
673 trim(to_string(num_phase_))//" but got "// &
674 trim(to_string(i_phase)))
675
676 ! Get the next ion
677 call ions%iter_next()
678
679 end do
680
681 n_float_param = n_float_param + 3 + eqsam_num_ion_(i_ion_pair)
682 n_int_param = n_int_param + 2 + num_phase_ + &
683 (1+num_phase_)*eqsam_num_ion_(i_ion_pair)
684
685 else
686 call die_msg(186680407, "Internal error.")
687 end if
688
689 call ion_pairs%iter_next()
690 end do
691
692 call assert(859412771, n_int_param.eq.total_int_param_)
693 call assert(568314442, n_float_param.eq.total_float_param_)
694
695 end subroutine initialize
696
697!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
698
699 !> Return a real number representing the priority of the sub model
700 !! calculations. Low priority sub models may use the results of higher
701 !! priority sub models. Lower numbers indicate higher priority.
702 !!
703 !! ZSR calculations do not depend on other sub model calculations, so can be
704 !! high priority.
705 function priority(this)
706
707 !> Sub model priority
708 real(kind=dp) :: priority
709 !> Sub model data
710 class(sub_model_zsr_aerosol_water_t), intent(in) :: this
711
712 priority = 1.0;
713
714 end function priority
715
716!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
717
718 !> Finalize the reaction
719 elemental subroutine finalize(this)
720
721 !> Reaction data
722 type(sub_model_zsr_aerosol_water_t), intent(inout) :: this
723
724 if (associated(this%property_set)) &
725 deallocate(this%property_set)
726 if (allocated(this%condensed_data_real)) &
727 deallocate(this%condensed_data_real)
728 if (allocated(this%condensed_data_int)) &
729 deallocate(this%condensed_data_int)
730
731 end subroutine finalize
732
733!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
734
Initialize the aerosol representation data, validating component data and loading any required inform...
Get the non-unique name of a chemical species by its unique name.
Return a real number representing the priority of the sub model calculations. Low priority sub models...
Interface for to_string functions.
Definition util.F90:32
The abstract aero_phase_data_t structure and associated subroutines.
elemental subroutine finalize(this)
Finalize the aerosol phase data.
type(aero_phase_data_t) function, pointer constructor(phase_name, init_size)
Constructor for aero_phase_data_t.
The abstract aero_rep_data_t structure and associated subroutines.
The camp_state_t structure and associated subroutines.
Definition camp_state.F90:9
The chem_spec_data_t structure and associated subroutines.
integer(kind=i_kind), parameter, public chem_spec_constant
Physical constants.
Definition constants.F90:9
integer, parameter dp
Kind of a double precision real number.
Definition constants.F90:16
type(const_t), save const
Fixed variable for accessing the constant's values.
Definition constants.F90:77
integer, parameter i_kind
Kind of an integer.
Definition constants.F90:21
The property_t structure and associated subroutines.
Definition property.F90:9
The abstract sub_model_data_t structure and associated subroutines.
The sub_model_ZSR_aerosol_water_t type and associated functions.
Common utility subroutines.
Definition util.F90:9
subroutine assert(code, condition_ok)
Errors unless condition_ok is true.
Definition util.F90:165
subroutine die_msg(code, error_msg)
Error immediately.
Definition util.F90:196
subroutine assert_msg(code, condition_ok, error_msg)
Errors unless condition_ok is true.
Definition util.F90:130
Pointer type for building arrays.
Pointer to aero_rep_data_t extending types.
Abstract sub-model data type.
String type for building arrays of string of various size.
Definition util.F90:38