CAMP 1.0.0
Chemistry Across Multiple Phases
rxn_aqueous_equilibrium.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_rxn_aqueous_equilibrium module.
7!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
8!> \page camp_rxn_aqueous_equilibrium CAMP: Aqueous-Phase Equilibrium
9!!
10!! Aqueous equilibrium reactions are calculated as forward and reverse
11!! reactions. The reverse rate constant must be provided as part of the input
12!! data and the forward rate constant is calculated using the provided
13!! reverse rate constant and an equilibrium constant of the following format:
14!!
15!! \f[
16!! Ae^{C({1/T-1/298})}
17!! \f]
18!!
19!! where \f$A\f$ is the pre-exponential factor (\f$s^{-1}\f$), \f$C\f$ is a
20!! constant and \f$T\f$ is the temperature (K).
21!!
22!! Input data for aqueous equilibrium equations should take the form :
23!! \code{.json}
24!! {
25!! "type" : "AQUEOUS_EQUILIBRIUM",
26!! "A" : 123.45,
27!! "C" : 123.45,
28!! "k_reverse" : 123.45,
29!! "phase" : "my aqueous phase",
30!! "time unit" : "MIN",
31!! "aqueous-phase water" : "H2O_aq",
32!! "ion pair" : "spec3-spec4",
33!! "reactants" : {
34!! "spec1" : {},
35!! "spec2" : { "qty" : 2 },
36!! ...
37!! },
38!! "products" : {
39!! "spec3" : {},
40!! "spec4" : { "qty" : 0.65 },
41!! ...
42!! }
43!! ...
44!! }
45!! \endcode
46!! The key-value pairs \b reactants and \b products are required. Reactants
47!! and products without a \b qty value are assumed to appear once in the
48!! reaction equation. Reactant and product species must be present in the
49!! specified phase and include a \b molecular \b weight \b [\b kg \b mol-1]
50!! parameter in kg \f$\mbox{mole}^{-1}\f$. The
51!! parameter \b aqueous-phase \b water is required and must be the name of the
52!! aerosol-phase species that is used for water. The parameter \b ion \b pair
53!! is optional. When it is included its value must be the name of an ion pair
54!! that is present in the specified aerosol phase. Its mean binary activity
55!! coefficient will be applied to the reverse reaction.
56!!
57!! When \b A is not included, it is assumed to be 1.0, when \b C is not
58!! included, it is assumed to be 0.0. The reverse reaction rate constant
59!! \b k_reverse is required.
60!!
61!! The unit for time is assumed to be s, but inclusion of the optional
62!! key-value pair \b time \b unit = \b MIN can be used to indicate a rate with
63!! min as the time unit.
64!!
65!!
66
67!> The rxn_aqueous_equilibrium_t type and associated functions.
69
73 use camp_constants, only: const
77 use camp_util, only: i_kind, dp, to_string, &
80
81 implicit none
82 private
83
84#define NUM_REACT_ this%condensed_data_int(1)
85#define NUM_PROD_ this%condensed_data_int(2)
86#define NUM_AERO_PHASE_ this%condensed_data_int(3)
87#define A_ this%condensed_data_real(1)
88#define C_ this%condensed_data_real(2)
89#define RATE_CONST_REVERSE_ this%condensed_data_real(3)
90#define WATER_CONC_ this%condensed_data_real(4)
91#define ACTIVITY_COEFF_VALUE_ this%condensed_data_real(5)
92#define NUM_INT_PROP_ 3
93#define NUM_REAL_PROP_ 5
94#define NUM_ENV_PARAM_ 1
95#define REACT_(x) this%condensed_data_int(NUM_INT_PROP_+x)
96#define PROD_(x) this%condensed_data_int(NUM_INT_PROP_+NUM_REACT_*NUM_AERO_PHASE_+x)
97#define WATER_(x) this%condensed_data_int(NUM_INT_PROP_+(NUM_REACT_+NUM_PROD_)*NUM_AERO_PHASE_+x)
98#define ACTIVITY_COEFF_(x) this%condensed_data_int(NUM_INT_PROP_+(NUM_REACT_+NUM_PROD_+1)*NUM_AERO_PHASE_+x)
99#define DERIV_ID_(x) this%condensed_data_int(NUM_INT_PROP_+(NUM_REACT_+NUM_PROD_+2)*NUM_AERO_PHASE_+x)
100#define JAC_ID_(x) this%condensed_data_int(NUM_INT_PROP_+(2*(NUM_REACT_+NUM_PROD_)+2)*NUM_AERO_PHASE_+x)
101#define MASS_FRAC_TO_M_(x) this%condensed_data_real(NUM_REAL_PROP_+x)
102#define REACT_CONC_(x) this%condensed_data_real(NUM_REAL_PROP_+NUM_REACT_+NUM_PROD_+x)
103#define PROD_CONC_(x) this%condensed_data_real(NUM_REAL_PROP_+2*NUM_REACT_+NUM_PROD_+x)
104#define SMALL_WATER_CONC_(x) this%condensed_data_real(NUM_REAL_PROP_+2*NUM_REACT_+2*NUM_PROD_+x)
105#define SMALL_CONC_(x) this%condensed_data_real(NUM_REAL_PROP_+2*NUM_REACT_+2*NUM_PROD_+NUM_AERO_PHASE_+x)
106
108
109 !> Generic test reaction data type
110 type, extends(rxn_data_t) :: rxn_aqueous_equilibrium_t
111 contains
112 !> Reaction initialization
113 procedure :: initialize
114 !> Finalize the reaction
117
118 !> Constructor for rxn_aqueous_equilibrium_t
120 procedure :: constructor
121 end interface rxn_aqueous_equilibrium_t
122
123contains
124
125!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
126
127 !> Constructor for Aqueous equilibrium reaction
128 function constructor() result(new_obj)
129
130 !> A new reaction instance
131 type(rxn_aqueous_equilibrium_t), pointer :: new_obj
132
133 allocate(new_obj)
134 new_obj%rxn_phase = aero_rxn
135
136 end function constructor
137
138!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
139
140 !> Initialize the reaction data, validating component data and loading
141 !! any required information into the condensed data arrays for use during
142 !! solving
143 subroutine initialize(this, chem_spec_data, aero_phase, aero_rep, n_cells)
144
145 !> Reaction data
146 class(rxn_aqueous_equilibrium_t), intent(inout) :: this
147 !> Chemical species data
148 type(chem_spec_data_t), intent(in) :: chem_spec_data
149 !> Aerosol phase data
150 type(aero_phase_data_ptr), intent(in) :: aero_phase(:)
151 !> Aerosol representations
152 type(aero_rep_data_ptr), pointer, intent(in) :: aero_rep(:)
153 !> Number of grid cells to solve simultaneously
154 integer(kind=i_kind), intent(in) :: n_cells
155
156 type(property_t), pointer :: spec_props, reactants, products
157 character(len=:), allocatable :: key_name, spec_name, water_name, &
158 phase_name, string_val, ion_pair_name
159 integer(kind=i_kind) :: i_phase_inst, j_spec, i_qty, i_aero_rep, &
160 i_aero_phase, num_spec_per_phase, num_phase, num_react, &
161 num_prod, temp_int, tracer_type
162 real(kind=dp) :: temp_real
163 type(string_t), allocatable :: unique_names(:), react_names(:), &
164 prod_names(:)
165
166 ! Get the property set
167 if (.not. associated(this%property_set)) call die_msg(206493887, &
168 "Missing property set needed to initialize reaction")
169
170 ! Get the aerosol phase name
171 key_name = "aerosol phase"
172 call assert_msg(138126714, &
173 this%property_set%get_string(key_name, phase_name), &
174 "Missing aerosol phase in aqueous-equilibrium reaction")
175
176 ! Get the aerosol-phase water name
177 key_name = "aerosol-phase water"
178 call assert_msg(583327500, &
179 this%property_set%get_string(key_name, water_name), &
180 "Missing aerosol-phase water in aqueous-equilibrium reaction")
181
182 ! Get reactant species
183 key_name = "reactants"
184 call assert_msg(237749385, &
185 this%property_set%get_property_t(key_name, reactants), &
186 "Missing reactant species in aqueous-equilibrium reaction")
187
188 ! Get product species
189 key_name = "products"
190 call assert_msg(350520025, &
191 this%property_set%get_property_t(key_name, products), &
192 "Missing product species in aqueous-equilibrium reaction")
193
194 ! Count the number of species per phase instance (including species
195 ! with a "qty" specified)
196 call reactants%iter_reset()
197 num_react = 0
198 do while (reactants%get_key(spec_name))
199 ! Get properties included with this reactant in the reaction data
200 call assert(422080799, reactants%get_property_t(val=spec_props))
201 key_name = "qty"
202 if (spec_props%get_int(key_name, temp_int)) &
203 num_react = num_react + temp_int - 1
204 call reactants%iter_next()
205 num_react = num_react + 1
206 end do
207 call products%iter_reset()
208 num_prod = 0
209 do while (products%get_key(spec_name))
210 ! Get properties included with this product in the reaction data
211 call assert(971363961, products%get_property_t(val=spec_props))
212 key_name = "qty"
213 if (spec_props%get_int(key_name, temp_int)) &
214 num_prod = num_prod + temp_int - 1
215 call products%iter_next()
216 num_prod = num_prod + 1
217 end do
218 num_spec_per_phase = num_prod + num_react
219
220 ! Check for aerosol representations
221 call assert_msg(191050890, associated(aero_rep), &
222 "Missing aerosol representation for aqueous equilibrium reaction")
223 call assert_msg(868319733, size(aero_rep).gt.0, &
224 "Missing aerosol representation for aqueous equilibrium reaction")
225
226 ! Count the instances of this phase/species pair
227 num_phase = 0
228 do i_aero_rep = 1, size(aero_rep)
229
230 ! Check for the specified phase in this aero rep
231 if (aero_rep(i_aero_rep)%val%num_phase_instances(phase_name).eq.0) cycle
232
233 ! Get the unique names for aerosol-phase water
234 unique_names = aero_rep(i_aero_rep)%val%unique_names( &
235 phase_name = phase_name, spec_name = water_name)
236 call assert_msg(416554966, allocated(unique_names), &
237 "Missing aerosol-phase water species '"//water_name// &
238 "' in phase '"//phase_name//"'")
239 call assert_msg(344829020, size(unique_names).gt.0, &
240 "Missing aerosol-phase water species '"//water_name// &
241 "' in phase '"//phase_name//"'")
242
243 ! Count the instances of the specified phase in this aero rep
244 ! (One instance per unique water name)
245 num_phase = num_phase + size(unique_names)
246
247 deallocate(unique_names)
248
249 end do
250
251 ! Make sure there is at least one phase present
252 call assert_msg(925748425, num_phase.gt.0, &
253 "No aerosol phase '"//phase_name//"' present.")
254
255 ! Allocate space in the condensed data arrays
256 allocate(this%condensed_data_int(num_int_prop_ + &
257 num_phase * (num_spec_per_phase * (num_spec_per_phase + 4) + 2)))
258 allocate(this%condensed_data_real(num_real_prop_ + &
259 2 * num_spec_per_phase + 2 * num_phase))
260 this%condensed_data_int(:) = int(0, kind=i_kind)
261 this%condensed_data_real(:) = real(0.0, kind=dp)
262
263 ! Save space for the environment-dependent parameters
264 this%num_env_params = num_env_param_
265
266 ! Set the number of products, reactants and aerosol phase instances
267 num_react_ = num_react
268 num_prod_ = num_prod
269 num_aero_phase_ = num_phase
270
271 ! Get the rate constant parameters
272 key_name = "A"
273 if (.not. this%property_set%get_real(key_name, a_)) then
274 a_ = 1.0
275 end if
276 key_name = "C"
277 if (.not. this%property_set%get_real(key_name, c_)) then
278 c_ = 0.0
279 end if
280 key_name = "k_reverse"
281 call assert_msg(519823533, &
282 this%property_set%get_real(key_name, rate_const_reverse_), &
283 "Missing 'k_reverse' for aqueous equilibrium reaction")
284 key_name = "time_unit"
285 if (this%property_set%get_string(key_name, string_val)) then
286 if (trim(string_val).eq."MIN") then
287 rate_const_reverse_ = rate_const_reverse_ / 60.0
288 end if
289 end if
290
291 ! Set up an array to the reactant, product and water names
292 allocate(react_names(num_react_))
293 allocate(prod_names(num_prod_))
294
295 ! Get the chemical properties for the reactants
296 call reactants%iter_reset()
297 i_phase_inst = 0
298 do while (reactants%get_key(spec_name))
299
300 ! Get the reactant species properties
301 call assert_msg(513131584, &
302 chem_spec_data%get_property_set(spec_name, spec_props), &
303 "Missing properties required for aqueous equilibrium "// &
304 "reaction involving species '"//trim(spec_name)//"'")
305
306 ! Get the molecular weight
307 key_name = "molecular weight [kg mol-1]"
308 call assert_msg(332898361, spec_props%get_real(key_name, temp_real), &
309 "Missing 'molecular weight' for species '"//trim(spec_name)// &
310 "' in aqueous equilibrium reaction.")
311
312 ! Set properties for each occurance of a reactant in the rxn equation
313 call assert(971363961, reactants%get_property_t(val=spec_props))
314 key_name = "qty"
315 if (.not.spec_props%get_int(key_name, temp_int)) temp_int = 1
316 do i_qty = 1, temp_int
317 i_phase_inst = i_phase_inst + 1
318
319 ! Add the reactant name to the list
320 react_names(i_phase_inst)%string = spec_name
321
322 ! Use the MW to calculate the mass frac -> M conversion
323 mass_frac_to_m_(i_phase_inst) = 1.0d3/temp_real
324
325 end do
326
327 ! Go to the next reactant
328 call reactants%iter_next()
329
330 end do
331
332 ! Get the chemical properties for the products
333 call products%iter_reset()
334 i_phase_inst = 0
335 do while (products%get_key(spec_name))
336
337 ! Get the product species properties
338 call assert_msg(513131584, &
339 chem_spec_data%get_property_set(spec_name, spec_props), &
340 "Missing properties required for aqueous equilibrium "// &
341 "reaction involving species '"//trim(spec_name)//"'")
342
343 ! Get the molecular weight
344 key_name = "molecular weight [kg mol-1]"
345 call assert_msg(332898361, spec_props%get_real(key_name, temp_real), &
346 "Missing 'molecular weight' for species '"//trim(spec_name)// &
347 "' in aqueous equilibrium reaction.")
348
349 ! Set properties for each occurance of a reactant in the rxn equation
350 call assert(294785742, products%get_property_t(val=spec_props))
351 key_name = "qty"
352 if (.not.spec_props%get_int(key_name, temp_int)) temp_int = 1
353 do i_qty = 1, temp_int
354 i_phase_inst = i_phase_inst + 1
355
356 ! Add the product name to the list
357 prod_names(i_phase_inst)%string = spec_name
358
359 ! Use the MW to calculate the mass frac -> M conversion
360 mass_frac_to_m_(num_react_ + i_phase_inst) = 1.0d3/temp_real
361
362 end do
363
364 ! Go to the next product
365 call products%iter_next()
366
367 end do
368
369 ! Check for an ion pair to use for the activity coefficient of the reverse
370 ! reaction
371 key_name = "ion pair"
372 if (.not. this%property_set%get_string(key_name, ion_pair_name)) then
373 ion_pair_name = ""
374 end if
375
376 ! Set the state array indices for the reactants, products and water
377 i_aero_phase = 0
378 do i_aero_rep = 1, size(aero_rep)
379
380 ! Check for the specified phase in this aero rep
381 if (aero_rep(i_aero_rep)%val%num_phase_instances(phase_name).eq.0) cycle
382
383 ! Get the unique names for aerosol-phase water
384 unique_names = aero_rep(i_aero_rep)%val%unique_names( &
385 phase_name = phase_name, spec_name = water_name)
386
387 ! Save the number of instances to check for the presence of
388 ! each product and reactant
389 num_phase = size(unique_names)
390
391 ! Save the state ids for aerosol water concentration
392 do i_phase_inst = 1, num_phase
393 water_(i_aero_phase + i_phase_inst) = &
394 aero_rep(i_aero_rep)%val%spec_state_id( &
395 unique_names(i_phase_inst)%string)
396 end do
397
398 deallocate(unique_names)
399
400 ! If an ion pair was specified, save its id for each phase instance
401 if (ion_pair_name.ne."") then
402
403 ! Get the unique names for the ion pair
404 unique_names = aero_rep(i_aero_rep)%val%unique_names( &
405 phase_name = phase_name, spec_name = ion_pair_name)
406
407 ! Make sure the right number of instances are present
408 call assert_msg(298310186, size(unique_names).eq.num_phase, &
409 "Incorrect instances of ion pair '"//ion_pair_name// &
410 "' in phase '"//phase_name// &
411 "' in an aqueous equilibrium reaction")
412
413 ! Make sure the specified ion pair is of the right tracer type
414 call assert(690720371, &
415 chem_spec_data%get_type(ion_pair_name, tracer_type))
416 call assert_msg(450743055, tracer_type.eq.chem_spec_activity_coeff, &
417 "Ion pair '"//ion_pair_name//"' must have type "// &
418 "'ION_PAIR' to be used as an ion pair in an aqueous "// &
419 "equilibrium reaction.")
420
421 ! Save the ion pair id
422 do i_phase_inst = 1, num_phase
423 activity_coeff_(i_aero_phase + i_phase_inst) = &
424 aero_rep(i_aero_rep)%val%spec_state_id( &
425 unique_names(i_phase_inst)%string)
426 end do
427
428 deallocate(unique_names)
429
430 else
431 do i_phase_inst = 1, num_phase
432 activity_coeff_(i_aero_phase + i_phase_inst) = 0
433 end do
434 end if
435
436 ! Loop through the reactants
437 do i_phase_inst = 1, num_react_
438
439 ! Get the unique names for the reactants
440 unique_names = aero_rep(i_aero_rep)%val%unique_names( &
441 phase_name = phase_name, &
442 spec_name = react_names(i_phase_inst)%string)
443
444 ! Make sure the right number of instances are present
445 call assert_msg(280008989, size(unique_names).eq.num_phase, &
446 "Incorrect instances of reactant '"// &
447 react_names(i_phase_inst)%string// &
448 "' in phase '"//phase_name// &
449 "' in an aqueous equilibrium reaction")
450
451 ! Save the state ids for the reactant concentration
452 ! IDs are grouped by phase instance:
453 ! R1(phase1), R2(phase1), ..., R1(phase2)...
454 do j_spec = 1, num_phase
455 react_((i_aero_phase+j_spec-1)*num_react_ + i_phase_inst) = &
456 aero_rep(i_aero_rep)%val%spec_state_id( &
457 unique_names(j_spec)%string)
458 end do
459
460 deallocate(unique_names)
461
462 end do
463
464 ! Loop through the products
465 do i_phase_inst = 1, num_prod_
466
467 ! Get the unique names for the products
468 unique_names = aero_rep(i_aero_rep)%val%unique_names( &
469 phase_name = phase_name, &
470 spec_name = prod_names(i_phase_inst)%string)
471
472 ! Make sure the right number of instances are present
473 call assert_msg(557959349, size(unique_names).eq.num_phase, &
474 "Incorrect instances of product '"// &
475 prod_names(i_phase_inst)%string// &
476 "' in phase '"//phase_name// &
477 "' in an aqueous equilibrium reaction")
478
479 ! Save the state ids for the product concentration
480 ! IDs are grouped by phase instance:
481 ! P1(phase1), P2(phase1), ..., P1(phase2)...
482 do j_spec = 1, num_phase
483 prod_((i_aero_phase+j_spec-1)*num_prod_ + i_phase_inst) = &
484 aero_rep(i_aero_rep)%val%spec_state_id( &
485 unique_names(j_spec)%string)
486 end do
487
488 deallocate(unique_names)
489
490 end do
491
492 ! Increment the index offset for the next aerosol representation
493 i_aero_phase = i_aero_phase + num_phase
494
495 end do
496
497 end subroutine initialize
498
499!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
500
501 !> Finalize the reaction
502 subroutine finalize(this)
503
504 !> Reaction data
505 type(rxn_aqueous_equilibrium_t), intent(inout) :: this
506
507 if (associated(this%property_set)) &
508 deallocate(this%property_set)
509 if (allocated(this%condensed_data_real)) &
510 deallocate(this%condensed_data_real)
511 if (allocated(this%condensed_data_int)) &
512 deallocate(this%condensed_data_int)
513
514 end subroutine finalize
515
516!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
517
518 !> Finalize an array of reactions
519 subroutine finalize_array(this)
520
521 !> Array of reaction data
522 type(rxn_aqueous_equilibrium_t), intent(inout) :: this(:)
523
524 integer(kind=i_kind) :: i_rxn
525
526 do i_rxn = 1, size(this)
527 call finalize(this(i_rxn))
528 end do
529
530 end subroutine finalize_array
531
532!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
533
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.
Get a list of unique names for each element on the camp_camp_state::camp_state_t::state_var array for...
Interface for to_string functions.
Definition util.F90:32
The abstract aero_phase_data_t structure and associated subroutines.
subroutine finalize_array(this)
Finalize the aerosol phase data.
type(aero_phase_data_t) function, pointer constructor(phase_name, init_size)
Constructor for aero_phase_data_t.
subroutine finalize(this)
Finalize the aerosol phase data.
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_activity_coeff
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 rxn_aqueous_equilibrium_t type and associated functions.
The rxn_data_t structure and associated subroutines.
Definition rxn_data.F90:60
integer(kind=i_kind), parameter, public aero_rxn
Aerosol-phase reaction.
Definition rxn_data.F90:89
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 reaction data type.
Definition rxn_data.F90:99
String type for building arrays of string of various size.
Definition util.F90:53