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
111 contains
112 !> Reaction initialization
113 procedure :: initialize
114 !> Finalize the reaction
115 final :: finalize
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_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 representations
150 type(aero_rep_data_ptr), pointer, intent(in) :: aero_rep(:)
151 !> Number of grid cells to solve simultaneously
152 integer(kind=i_kind), intent(in) :: n_cells
153
154 type(property_t), pointer :: spec_props, reactants, products
155 character(len=:), allocatable :: key_name, spec_name, water_name, &
156 phase_name, string_val, ion_pair_name
157 integer(kind=i_kind) :: i_phase_inst, j_spec, i_qty, i_aero_rep, &
158 i_aero_phase, num_spec_per_phase, num_phase, num_react, &
159 num_prod, temp_int, tracer_type
160 real(kind=dp) :: temp_real
161 type(string_t), allocatable :: unique_names(:), react_names(:), &
162 prod_names(:)
163
164 ! Get the property set
165 if (.not. associated(this%property_set)) call die_msg(206493887, &
166 "Missing property set needed to initialize reaction")
167
168 ! Get the aerosol phase name
169 key_name = "aerosol phase"
170 call assert_msg(138126714, &
171 this%property_set%get_string(key_name, phase_name), &
172 "Missing aerosol phase in aqueous-equilibrium reaction")
173
174 ! Get the aerosol-phase water name
175 key_name = "aerosol-phase water"
176 call assert_msg(583327500, &
177 this%property_set%get_string(key_name, water_name), &
178 "Missing aerosol-phase water in aqueous-equilibrium reaction")
179
180 ! Get reactant species
181 key_name = "reactants"
182 call assert_msg(237749385, &
183 this%property_set%get_property_t(key_name, reactants), &
184 "Missing reactant species in aqueous-equilibrium reaction")
185
186 ! Get product species
187 key_name = "products"
188 call assert_msg(350520025, &
189 this%property_set%get_property_t(key_name, products), &
190 "Missing product species in aqueous-equilibrium reaction")
191
192 ! Count the number of species per phase instance (including species
193 ! with a "qty" specified)
194 call reactants%iter_reset()
195 num_react = 0
196 do while (reactants%get_key(spec_name))
197 ! Get properties included with this reactant in the reaction data
198 call assert(422080799, reactants%get_property_t(val=spec_props))
199 key_name = "qty"
200 if (spec_props%get_int(key_name, temp_int)) &
201 num_react = num_react + temp_int - 1
202 call reactants%iter_next()
203 num_react = num_react + 1
204 end do
205 call products%iter_reset()
206 num_prod = 0
207 do while (products%get_key(spec_name))
208 ! Get properties included with this product in the reaction data
209 call assert(971363961, products%get_property_t(val=spec_props))
210 key_name = "qty"
211 if (spec_props%get_int(key_name, temp_int)) &
212 num_prod = num_prod + temp_int - 1
213 call products%iter_next()
214 num_prod = num_prod + 1
215 end do
216 num_spec_per_phase = num_prod + num_react
217
218 ! Check for aerosol representations
219 call assert_msg(191050890, associated(aero_rep), &
220 "Missing aerosol representation for aqueous equilibrium reaction")
221 call assert_msg(868319733, size(aero_rep).gt.0, &
222 "Missing aerosol representation for aqueous equilibrium reaction")
223
224 ! Count the instances of this phase/species pair
225 num_phase = 0
226 do i_aero_rep = 1, size(aero_rep)
227
228 ! Check for the specified phase in this aero rep
229 if (aero_rep(i_aero_rep)%val%num_phase_instances(phase_name).eq.0) cycle
230
231 ! Get the unique names for aerosol-phase water
232 unique_names = aero_rep(i_aero_rep)%val%unique_names( &
233 phase_name = phase_name, spec_name = water_name)
234 call assert_msg(416554966, allocated(unique_names), &
235 "Missing aerosol-phase water species '"//water_name// &
236 "' in phase '"//phase_name//"'")
237 call assert_msg(344829020, size(unique_names).gt.0, &
238 "Missing aerosol-phase water species '"//water_name// &
239 "' in phase '"//phase_name//"'")
240
241 ! Count the instances of the specified phase in this aero rep
242 ! (One instance per unique water name)
243 num_phase = num_phase + size(unique_names)
244
245 deallocate(unique_names)
246
247 end do
248
249 ! Make sure there is at least one phase present
250 call assert_msg(925748425, num_phase.gt.0, &
251 "No aerosol phase '"//phase_name//"' present.")
252
253 ! Allocate space in the condensed data arrays
254 allocate(this%condensed_data_int(num_int_prop_ + &
255 num_phase * (num_spec_per_phase * (num_spec_per_phase + 4) + 2)))
256 allocate(this%condensed_data_real(num_real_prop_ + &
257 2 * num_spec_per_phase + 2 * num_phase))
258 this%condensed_data_int(:) = int(0, kind=i_kind)
259 this%condensed_data_real(:) = real(0.0, kind=dp)
260
261 ! Save space for the environment-dependent parameters
262 this%num_env_params = num_env_param_
263
264 ! Set the number of products, reactants and aerosol phase instances
265 num_react_ = num_react
266 num_prod_ = num_prod
267 num_aero_phase_ = num_phase
268
269 ! Get the rate constant parameters
270 key_name = "A"
271 if (.not. this%property_set%get_real(key_name, a_)) then
272 a_ = 1.0
273 end if
274 key_name = "C"
275 if (.not. this%property_set%get_real(key_name, c_)) then
276 c_ = 0.0
277 end if
278 key_name = "k_reverse"
279 call assert_msg(519823533, &
280 this%property_set%get_real(key_name, rate_const_reverse_), &
281 "Missing 'k_reverse' for aqueous equilibrium reaction")
282 key_name = "time_unit"
283 if (this%property_set%get_string(key_name, string_val)) then
284 if (trim(string_val).eq."MIN") then
285 rate_const_reverse_ = rate_const_reverse_ / 60.0
286 end if
287 end if
288
289 ! Set up an array to the reactant, product and water names
290 allocate(react_names(num_react_))
291 allocate(prod_names(num_prod_))
292
293 ! Get the chemical properties for the reactants
294 call reactants%iter_reset()
295 i_phase_inst = 0
296 do while (reactants%get_key(spec_name))
297
298 ! Get the reactant species properties
299 call assert_msg(513131584, &
300 chem_spec_data%get_property_set(spec_name, spec_props), &
301 "Missing properties required for aqueous equilibrium "// &
302 "reaction involving species '"//trim(spec_name)//"'")
303
304 ! Get the molecular weight
305 key_name = "molecular weight [kg mol-1]"
306 call assert_msg(332898361, spec_props%get_real(key_name, temp_real), &
307 "Missing 'molecular weight' for species '"//trim(spec_name)// &
308 "' in aqueous equilibrium reaction.")
309
310 ! Set properties for each occurance of a reactant in the rxn equation
311 call assert(971363961, reactants%get_property_t(val=spec_props))
312 key_name = "qty"
313 if (.not.spec_props%get_int(key_name, temp_int)) temp_int = 1
314 do i_qty = 1, temp_int
315 i_phase_inst = i_phase_inst + 1
316
317 ! Add the reactant name to the list
318 react_names(i_phase_inst)%string = spec_name
319
320 ! Use the MW to calculate the mass frac -> M conversion
321 mass_frac_to_m_(i_phase_inst) = 1.0d3/temp_real
322
323 end do
324
325 ! Go to the next reactant
326 call reactants%iter_next()
327
328 end do
329
330 ! Get the chemical properties for the products
331 call products%iter_reset()
332 i_phase_inst = 0
333 do while (products%get_key(spec_name))
334
335 ! Get the product species properties
336 call assert_msg(513131584, &
337 chem_spec_data%get_property_set(spec_name, spec_props), &
338 "Missing properties required for aqueous equilibrium "// &
339 "reaction involving species '"//trim(spec_name)//"'")
340
341 ! Get the molecular weight
342 key_name = "molecular weight [kg mol-1]"
343 call assert_msg(332898361, spec_props%get_real(key_name, temp_real), &
344 "Missing 'molecular weight' for species '"//trim(spec_name)// &
345 "' in aqueous equilibrium reaction.")
346
347 ! Set properties for each occurance of a reactant in the rxn equation
348 call assert(294785742, products%get_property_t(val=spec_props))
349 key_name = "qty"
350 if (.not.spec_props%get_int(key_name, temp_int)) temp_int = 1
351 do i_qty = 1, temp_int
352 i_phase_inst = i_phase_inst + 1
353
354 ! Add the product name to the list
355 prod_names(i_phase_inst)%string = spec_name
356
357 ! Use the MW to calculate the mass frac -> M conversion
358 mass_frac_to_m_(num_react_ + i_phase_inst) = 1.0d3/temp_real
359
360 end do
361
362 ! Go to the next product
363 call products%iter_next()
364
365 end do
366
367 ! Check for an ion pair to use for the activity coefficient of the reverse
368 ! reaction
369 key_name = "ion pair"
370 if (.not. this%property_set%get_string(key_name, ion_pair_name)) then
371 ion_pair_name = ""
372 end if
373
374 ! Set the state array indices for the reactants, products and water
375 i_aero_phase = 0
376 do i_aero_rep = 1, size(aero_rep)
377
378 ! Check for the specified phase in this aero rep
379 if (aero_rep(i_aero_rep)%val%num_phase_instances(phase_name).eq.0) cycle
380
381 ! Get the unique names for aerosol-phase water
382 unique_names = aero_rep(i_aero_rep)%val%unique_names( &
383 phase_name = phase_name, spec_name = water_name)
384
385 ! Save the number of instances to check for the presence of
386 ! each product and reactant
387 num_phase = size(unique_names)
388
389 ! Save the state ids for aerosol water concentration
390 do i_phase_inst = 1, num_phase
391 water_(i_aero_phase + i_phase_inst) = &
392 aero_rep(i_aero_rep)%val%spec_state_id( &
393 unique_names(i_phase_inst)%string)
394 end do
395
396 deallocate(unique_names)
397
398 ! If an ion pair was specified, save its id for each phase instance
399 if (ion_pair_name.ne."") then
400
401 ! Get the unique names for the ion pair
402 unique_names = aero_rep(i_aero_rep)%val%unique_names( &
403 phase_name = phase_name, spec_name = ion_pair_name)
404
405 ! Make sure the right number of instances are present
406 call assert_msg(298310186, size(unique_names).eq.num_phase, &
407 "Incorrect instances of ion pair '"//ion_pair_name// &
408 "' in phase '"//phase_name// &
409 "' in an aqueous equilibrium reaction")
410
411 ! Make sure the specified ion pair is of the right tracer type
412 call assert(690720371, &
413 chem_spec_data%get_type(ion_pair_name, tracer_type))
414 call assert_msg(450743055, tracer_type.eq.chem_spec_activity_coeff, &
415 "Ion pair '"//ion_pair_name//"' must have type "// &
416 "'ION_PAIR' to be used as an ion pair in an aqueous "// &
417 "equilibrium reaction.")
418
419 ! Save the ion pair id
420 do i_phase_inst = 1, num_phase
421 activity_coeff_(i_aero_phase + i_phase_inst) = &
422 aero_rep(i_aero_rep)%val%spec_state_id( &
423 unique_names(i_phase_inst)%string)
424 end do
425
426 deallocate(unique_names)
427
428 else
429 do i_phase_inst = 1, num_phase
430 activity_coeff_(i_aero_phase + i_phase_inst) = 0
431 end do
432 end if
433
434 ! Loop through the reactants
435 do i_phase_inst = 1, num_react_
436
437 ! Get the unique names for the reactants
438 unique_names = aero_rep(i_aero_rep)%val%unique_names( &
439 phase_name = phase_name, &
440 spec_name = react_names(i_phase_inst)%string)
441
442 ! Make sure the right number of instances are present
443 call assert_msg(280008989, size(unique_names).eq.num_phase, &
444 "Incorrect instances of reactant '"// &
445 react_names(i_phase_inst)%string// &
446 "' in phase '"//phase_name// &
447 "' in an aqueous equilibrium reaction")
448
449 ! Save the state ids for the reactant concentration
450 ! IDs are grouped by phase instance:
451 ! R1(phase1), R2(phase1), ..., R1(phase2)...
452 do j_spec = 1, num_phase
453 react_((i_aero_phase+j_spec-1)*num_react_ + i_phase_inst) = &
454 aero_rep(i_aero_rep)%val%spec_state_id( &
455 unique_names(j_spec)%string)
456 end do
457
458 deallocate(unique_names)
459
460 end do
461
462 ! Loop through the products
463 do i_phase_inst = 1, num_prod_
464
465 ! Get the unique names for the products
466 unique_names = aero_rep(i_aero_rep)%val%unique_names( &
467 phase_name = phase_name, &
468 spec_name = prod_names(i_phase_inst)%string)
469
470 ! Make sure the right number of instances are present
471 call assert_msg(557959349, size(unique_names).eq.num_phase, &
472 "Incorrect instances of product '"// &
473 prod_names(i_phase_inst)%string// &
474 "' in phase '"//phase_name// &
475 "' in an aqueous equilibrium reaction")
476
477 ! Save the state ids for the product concentration
478 ! IDs are grouped by phase instance:
479 ! P1(phase1), P2(phase1), ..., P1(phase2)...
480 do j_spec = 1, num_phase
481 prod_((i_aero_phase+j_spec-1)*num_prod_ + i_phase_inst) = &
482 aero_rep(i_aero_rep)%val%spec_state_id( &
483 unique_names(j_spec)%string)
484 end do
485
486 deallocate(unique_names)
487
488 end do
489
490 ! Increment the index offset for the next aerosol representation
491 i_aero_phase = i_aero_phase + num_phase
492
493 end do
494
495 end subroutine initialize
496
497!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
498
499 !> Finalize the reaction
500 elemental subroutine finalize(this)
501
502 !> Reaction data
503 type(rxn_aqueous_equilibrium_t), intent(inout) :: this
504
505 if (associated(this%property_set)) &
506 deallocate(this%property_set)
507 if (allocated(this%condensed_data_real)) &
508 deallocate(this%condensed_data_real)
509 if (allocated(this%condensed_data_int)) &
510 deallocate(this%condensed_data_int)
511
512 end subroutine finalize
513
514!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
515
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.
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_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:88
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 to aero_rep_data_t extending types.
Abstract reaction data type.
Definition rxn_data.F90:98
String type for building arrays of string of various size.
Definition util.F90:38