CAMP 1.0.0
Chemistry Across Multiple Phases
sub_model_PDFiTE.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_PDFiTE module.
7!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
8!> \page camp_sub_model_PDFiTE CAMP: PD-FiTE Activity
9!!
10!! PD-FiTE activity calculates aerosol-phase species activities using
11!! Taylor series to describe partial derivatives of mean activity coefficients
12!! for ternary solutions, as described in Topping et al. (2009)
13!! \cite Topping2009 . The mean binary activity coefficients for ion pairs are
14!! calculated according to eq. 15 in \cite Topping2009 . The values are then
15!! made available to aqueous-phase reactions during solving.
16!!
17!! Input data for PDFiTE activity equations have the following format :
18!! \code{.json}
19!! { "camp-data" : [
20!! {
21!! "name" : "my PDFiTE activity",
22!! "type" : "SUB_MODEL_PDFITE",
23!! "gas-phase water" : "H2O",
24!! "aerosol-phase water" : "H2O_aq",
25!! "aerosol phase" : "my aero phase",
26!! "calculate for" : {
27!! "H-NO3" : {
28!! "interactions" : [
29!! {
30!! "ion pair" : "H-NO3",
31!! "min RH" : 0.0,
32!! "max RH" : 0.1,
33!! "B" : [ 0.925113 ]
34!! },
35!! {
36!! "ion pair" : "H-NO3",
37!! "min RH" : 0.1,
38!! "max RH" : 0.4,
39!! "B" : [ 0.12091, 13.497, -67.771, 144.01, -117.97 ]
40!! },
41!! {
42!! "ion pair" : "H-NO3",
43!! "min RH" : 0.4,
44!! "max RH" : 0.9,
45!! "B" : [ 1.3424, -0.8197, -0.52983, -0.37335 ]
46!! },
47!! {
48!! "ion pair" : "H-NO3",
49!! "min RH" : 0.9,
50!! "max RH" : 1.0,
51!! "B" : [ -0.3506505 ]
52!! },
53!! {
54!! "ion pair" : "NH4-NO3",
55!! "min RH" : 0.0,
56!! "max RH" : 0.1,
57!! "B" : [ -11.93308 ]
58!! },
59!! {
60!! "ion pair" : "NH4-NO3",
61!! "min RH" : 0.1,
62!! "max RH" : 0.99,
63!! "B" : [ -17.0372, 59.232, -86.312, 44.04 ]
64!! },
65!! {
66!! "ion pair" : "NH4-NO3",
67!! "min RH" : 0.99,
68!! "max RH" : 1.0,
69!! "B" : [ -0.2599432 ]
70!! }
71!! ]
72!! }
73!! ...
74!! }
75!! }
76!! ]}
77!! \endcode
78!! The key-value pair \b aerosol \b phase is required to specify the aerosol
79!! phase for which to calculate activity coefficients. The key-value pairs
80!! \b gas-phase \b water and \b aerosol-phase \b water must also be present
81!! and specify the names for the water species in each phase. The final
82!! required key-value pair is \b calculated \b for, which should contain a set
83!! of ion pairs that activity coefficients will be calculated for.
84!!
85!! The key names in this set must correspond to ion pairs that are present in
86!! the specified aerosol phase. The values must contain a key-value pair
87!! named \b interactions which includes an array of ion-pair interactions
88!! used to calculate equation 15 in \cite Topping2009 .
89!!
90!! Each element in the \b interactions array must include an \b ion pair
91!! that exists in the specified aerosol phase, a \b min \b RH and \b max \b RH
92!! that specify the bounds for which the fitted curve is valid, and an array
93!! of \b B values that specify the polynomial coefficients B0, B1, B2, ...
94!! as in equation 19 in \cite Topping2009 . At least one polynomial
95!! coefficient must be present.
96!!
97!! If at least one interaction with an ion pair is included, enough
98!! interactions with that ion pair must be included to cover the entire RH
99!! range (0.0--1.0). Interactions are assume to cover the range (minRH, maxRH],
100!! except for the lowest RH interaction, which covers th range [0.0, maxRH].
101!!
102!! When the interacting ion pair is the same as the ion-pair for which the
103!! mean binary activity coefficient is being calculated, the interaction
104!! parameters are used to calculate \f$ln(\gamma_A^0(\mathrm{RH}))\f$.
105!! Otherwise, the parameters are used to calculate
106!! \f$\frac{d\ln{\gamma_A(\mathrm{RH})}}{d(N_{B,M}N_{B,x})}\f$.
107!!
108!! For the above example, the following input data should be present:
109!! \code{.json}
110!! {
111!! "name" : "H2O",
112!! "type" : "CHEM_SPEC",
113!! "phase" : "GAS",
114!! },
115!! {
116!! "name" : "H2O_aq",
117!! "type" : "CHEM_SPEC",
118!! "phase" : "AEROSOL",
119!! },
120!! {
121!! "name" : "H_p",
122!! "type" : "CHEM_SPEC",
123!! "phase" : "AEROSOL",
124!! "charge" : 1,
125!! "molecular weight [kg mol-1]" : 1.008
126!! },
127!! {
128!! "name" : "NH4_p",
129!! "type" : "CHEM_SPEC",
130!! "phase" : "AEROSOL",
131!! "charge" : 1,
132!! "molecular weight" : 18.04
133!! },
134!! {
135!! "name" : "NO3_m",
136!! "type" : "CHEM_SPEC",
137!! "phase" : "AEROSOL",
138!! "charge" : -1
139!! "molecular weight [kg mol-1]" : 62.0049
140!! },
141!! {
142!! "name" : "NH4-NO3",
143!! "type" : "CHEM_SPEC",
144!! "tracer type" : "ION_PAIR",
145!! "ions" : {
146!! "NH4_p" : {},
147!! "NO3_m" : {}
148!! }
149!! },
150!! {
151!! "name" : "H-NO3",
152!! "type" : "CHEM_SPEC",
153!! "tracer type" : "ION_PAIR",
154!! "ions" : {
155!! "H_p" : {},
156!! "NO3_m" : {}
157!! }
158!! },
159!! {
160!! "name" : "my aero phase",
161!! "type" : "AERO_PHASE",
162!! "species" : ["H_p", "NO3_m", "NH4_p", "NH4-NO3", "H-NO3", "H2O_aq"]
163!! }
164!! \endcode
165!!
166!!
167
168!> The sub_model_PDFiTE_t type and associated functions.
170
174 use camp_constants, only: const
176 use camp_property
178 use camp_util, only: i_kind, dp, to_string, &
180 die_msg, string_t, &
182
183 implicit none
184 private
185
186#define NUM_PHASE_ this%condensed_data_int(1)
187#define GAS_WATER_ID_ this%condensed_data_int(2)
188#define NUM_ION_PAIRS_ this%condensed_data_int(3)
189#define TOTAL_INT_PARAM_ this%condensed_data_int(4)
190#define TOTAL_FLOAT_PARAM_ this%condensed_data_int(5)
191#define NUM_INT_PROP_ 5
192#define NUM_REAL_PROP_ 0
193#define NUM_ENV_PARAM_ 1
194#define PHASE_ID_(x) this%condensed_data_int(NUM_INT_PROP_+x)
195#define PAIR_INT_PARAM_LOC_(x) this%condensed_data_int(NUM_INT_PROP_+NUM_PHASE_+x)
196#define PAIR_FLOAT_PARAM_LOC_(x) this%condensed_data_int(NUM_INT_PROP_+NUM_PHASE_+NUM_ION_PAIRS_+x)
197#define ION_PAIR_ACT_ID_(x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x))
198#define NUM_CATION_(x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+1)
199#define NUM_ANION_(x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+2)
200#define CATION_ID_(x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+3)
201#define ANION_ID_(x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+4)
202#define NUM_INTER_(x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+5)
203#define JAC_WATER_ID_(p,x) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+5+p)
204#define JAC_CATION_ID_(p,x,y) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+5+NUM_PHASE_+(p-1)*NUM_ION_PAIRS_+y)
205#define JAC_ANION_ID_(p,x,y) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+5+(1+NUM_ION_PAIRS_)*NUM_PHASE_+(p-1)*NUM_ION_PAIRS_+y)
206#define NUM_B_(x,y) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+5+(1+2*NUM_ION_PAIRS_)*NUM_PHASE_+y)
207#define INTER_SPEC_ID_(x,y) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+5+(1+2*NUM_ION_PAIRS_)*NUM_PHASE_+NUM_INTER_(x)+y)
208#define INTER_SPEC_LOC_(x,y) this%condensed_data_int(PAIR_INT_PARAM_LOC_(x)+5+(1+2*NUM_ION_PAIRS_)*NUM_PHASE_+2*(NUM_INTER_(x))+y)
209#define CATION_MW_(x) this%condensed_data_real(PAIR_FLOAT_PARAM_LOC_(x))
210#define ANION_MW_(x) this%condensed_data_real(PAIR_FLOAT_PARAM_LOC_(x)+1)
211#define CATION_N_(x) this%condensed_data_real(PAIR_FLOAT_PARAM_LOC_(x)+2)
212#define ANION_N_(x) this%condensed_data_real(PAIR_FLOAT_PARAM_LOC_(x)+3)
213#define MIN_RH_(x,y) this%condensed_data_real(INTER_SPEC_LOC_(x,y))
214#define MAX_RH_(x,y) this%condensed_data_real(INTER_SPEC_LOC_(x,y)+1)
215#define B_Z_(x,y,z) this%condensed_data_real(INTER_SPEC_LOC_(x,y)+1+z)
216
217 ! Update types (These must match values in sub_model_UNIFAC.c)
218 ! (none for now)
219
220 public :: sub_model_pdfite_t
221
222 !> Generic test reaction data type
224 contains
225 !> Reaction initialization
226 procedure :: initialize
227 !> Return a real number representing the priority of the sub-model
228 !! calculations. Low priority sub models may depend on the results
229 !! of higher priority sub models.
230 procedure :: priority
231 !> Finalize the reaction
232 final :: finalize
233 end type sub_model_pdfite_t
234
235 !> Constructor for sub_model_PDFiTE_t
236 interface sub_model_pdfite_t
237 procedure :: constructor
238 end interface sub_model_pdfite_t
239
240contains
241
242!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
243
244 !> Constructor for activity reaction
245 function constructor() result(new_obj)
246
247 !> A new reaction instance
248 type(sub_model_pdfite_t), pointer :: new_obj
249
250 allocate(new_obj)
251
252 end function constructor
253
254!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
255
256 !> Initialize the reaction data, validating component data and loading
257 !! any required information into the condensed data arrays for use during
258 !! solving
259 subroutine initialize(this, aero_rep_set, aero_phase_set, chem_spec_data)
260
261 !> Reaction data
262 class(sub_model_pdfite_t), intent(inout) :: this
263 !> The set of aerosol representations
264 type(aero_rep_data_ptr), pointer, intent(in) :: aero_rep_set(:)
265 !> The set of aerosol phases
266 type(aero_phase_data_ptr), pointer, intent(in) :: aero_phase_set(:)
267 !> Chemical species data
268 type(chem_spec_data_t), intent(in) :: chem_spec_data
269
270 type(property_t), pointer :: spec_props, ion_pairs, ion_pair, &
271 sub_props, ions, interactions, interaction, poly_coeffs
272 character(len=:), allocatable :: key_name, spec_name, phase_name, &
273 string_val, inter_spec_name
274 integer(kind=i_kind) :: n_phase, n_ion_pair, n_int_param, n_float_param
275 integer(kind=i_kind) :: i_aero_rep, i_phase, i_ion_pair, i_ion, i_spec, &
276 i_poly_coeff, i_interaction, j_ion_pair, j_interaction
277 integer(kind=i_kind) :: qty, int_val, charge, total_charge, tracer_type
278 real(kind=dp) :: real_val, molecular_weight, min_rh, max_rh
279 type(string_t), allocatable :: unique_spec_names(:)
280 character(len=:), allocatable :: ion_pair_name, ion_name
281 type(string_t), allocatable :: ion_pair_names(:), temp_ion_pair_names(:)
282 integer(kind=i_kind), allocatable :: num_inter(:)
283 real(kind=dp), allocatable :: rh_range(:)
284
285 ! Get the reaction property set
286 if (.not. associated(this%property_set)) call die_msg(101529793, &
287 "Missing property set needed to initialize PDFiTE activity"// &
288 " reaction.")
289
290 ! Get the aerosol phase name
291 key_name = "aerosol phase"
292 call assert_msg(429861748, &
293 this%property_set%get_string(key_name, phase_name), &
294 "Missing aerosol phase in PDFiTE activity reaction.")
295
296 ! Count the instances of the aerosol phase
297 n_phase = 0
298 do i_aero_rep = 1, size(aero_rep_set)
299
300 ! Get the number of instances of the phase in this representation
301 n_phase = n_phase + &
302 aero_rep_set(i_aero_rep)%val%num_phase_instances(phase_name)
303
304 end do
305
306 call assert_msg(656403972, n_phase.gt.0, &
307 "Aerosol phase '"//phase_name//"' not present in any aerosol "// &
308 "representation for PDFiTE activity reaction.")
309
310 ! Get the ion pairs to calculate mean binary activity coefficients for
311 key_name = "calculate for"
312 call assert_msg(258251605, &
313 this%property_set%get_property_t(key_name, ion_pairs), &
314 "Missing ion pairs to calculate activity for in PDFiTE "// &
315 " activity reaction.")
316
317 ! Count the ion pairs to calculate activity coefficients for
318 n_ion_pair = ion_pairs%size()
319 call assert_msg(479529522, n_ion_pair .gt. 0, &
320 "Empty ion pair set in PDFiTE activity reaction.")
321
322 ! Allocate space for the ion pair names and array to check for their
323 ! interaction parameters
324 allocate(ion_pair_names(n_ion_pair))
325
326 ! Set the ion pair names
327 call ion_pairs%iter_reset()
328 do i_ion_pair = 1, n_ion_pair
329
330 ! Get the name of the ion_pair
331 call assert(497564051, ion_pairs%get_key(ion_pair_name))
332 ion_pair_names(i_ion_pair)%string = ion_pair_name
333
334 call ion_pairs%iter_next()
335 end do
336
337 ! Get the number of parameters required for each ion pair
338 ! Adding space for INT_PROPS and phase state ids
339 n_int_param = num_int_prop_ + n_phase
340 ! Adding space for REAL_PROPS
341 n_float_param = num_real_prop_
342 call ion_pairs%iter_reset()
343 do i_ion_pair = 1, n_ion_pair
344
345 ! Get the name of the ion_pair
346 call assert(680654801, ion_pairs%get_key(ion_pair_name))
347
348 ! Get the ion_pair properties
349 call assert_msg(287766741, ion_pairs%get_property_t(val=ion_pair), &
350 "Missing ion pair properties for '"//ion_pair_name// &
351 "' in PDFiTE activity reaction.")
352
353 ! Get the interactions
354 key_name = "interactions"
355 call assert_msg(883233319, &
356 ion_pair%get_property_t(key_name, interactions), &
357 "Missing interaction parameters for '"//ion_pair_name// &
358 "' in PDFiTE activity reaction.")
359
360 ! Loop through the interaction set and count the parameters for each
361 call interactions%iter_reset()
362 do i_interaction = 1, interactions%size()
363
364 ! Get the current interaction
365 call assert(347348920, interactions%get_property_t(val=interaction))
366
367 ! Get the name of the interacting ion pair for use in error messages
368 key_name = "ion pair"
369 call assert_msg(924945098, &
370 interaction%get_string(key_name, inter_spec_name), &
371 "Missing interaction species name for ion pair '"// &
372 ion_pair_name//"' in PD-FiTE activity reaction")
373
374 ! Get the set of polynomial coefficients
375 key_name = "B"
376 call assert_msg(157416082, &
377 interaction%get_property_t(key_name, poly_coeffs), &
378 "Missing 'B' array of polynomial coefficients for ion "// &
379 "pair '"//inter_spec_name//"' in activity coefficient "// &
380 "calculation for ion pair '"//ion_pair_name//"' in "// &
381 "PD-FiTE activity reaction.")
382
383 ! Check the number of polynomial coefficients
384 call assert_msg(320927773, poly_coeffs%size().gt.0, &
385 "Insufficient polynomial coefficients for PDFiTE activity "//&
386 "calculation for ion_pair '"//ion_pair_name//"'.")
387
388 ! Adding space for minRH, maxRH, B[]
389 n_float_param = n_float_param + 2 + poly_coeffs%size()
390
391 ! Adding space for size(B[]), interacting species id, location of
392 ! interaction parameters
393 n_int_param = n_int_param + 3
394
395 ! Make sure that this ion pair is in the list of ion pairs. If not,
396 ! add it to the list.
397 do j_ion_pair = 1, size(ion_pair_names)
398 if (inter_spec_name.eq.ion_pair_names(j_ion_pair)%string) exit
399 if (j_ion_pair.eq.size(ion_pair_names)) then
400 allocate(temp_ion_pair_names(j_ion_pair))
401 forall (i_spec=1:j_ion_pair)
402 temp_ion_pair_names(i_spec)%string = &
403 ion_pair_names(i_spec)%string
404 end forall
405 deallocate(ion_pair_names)
406 allocate(ion_pair_names(j_ion_pair+1))
407 forall (i_spec=1:j_ion_pair)
408 ion_pair_names(i_spec)%string = &
409 temp_ion_pair_names(i_spec)%string
410 end forall
411 deallocate(temp_ion_pair_names)
412 ion_pair_names(j_ion_pair+1)%string = inter_spec_name
413 end if
414 end do
415
416 call interactions%iter_next()
417 end do
418
419 call ion_pairs%iter_next()
420 end do
421
422 ! Update the number of ion pairs to include those from interactions that
423 ! activity coefficients are not calculated for
424 n_ion_pair = size(ion_pair_names)
425
426 ! Adding space for locations of int and float data for each ion pair,
427 ! ion pair activity coefficient state id, number of cations and anions,
428 ! state ids of cation and anion, the number of interactions,
429 ! Jacobian ids for each activity coeffcient per phase for contributions
430 ! from water and each other ion pair
431 n_int_param = n_int_param + (8+(1+2*n_ion_pair)*n_phase)*n_ion_pair
432 ! Adding space for MW of the cation and anion, and cation and anion
433 ! concentrations (for use during solving)
434 n_float_param = n_float_param + 4*n_ion_pair
435
436 ! Allocate space for an array used to make sure all ion pair interactions
437 ! are included and the RH range is covered for each
438 allocate(num_inter(n_ion_pair))
439 allocate(rh_range(n_ion_pair))
440
441 ! Allocate space in the condensed data arrays
442 allocate(this%condensed_data_int(n_int_param))
443 allocate(this%condensed_data_real(n_float_param))
444 this%condensed_data_int(:) = int(9999, kind=i_kind)
445 this%condensed_data_real(:) = real(9999.0, kind=dp)
446
447 ! Save space for the environment-dependent parameters
448 this%num_env_params = num_env_param_
449
450 ! Set some data dimensions
451 num_phase_ = n_phase
452 num_ion_pairs_ = n_ion_pair
453 total_int_param_ = n_int_param
454 total_float_param_ = n_float_param
455
456 ! Set the gas-phase water species
457 key_name = "gas-phase water"
458 call assert_msg(901506020, &
459 this%property_set%get_string(key_name, spec_name), &
460 "Missing gas-phase water species name in PDFiTE activity "// &
461 "reaction.")
462
463 gas_water_id_ = chem_spec_data%gas_state_id(spec_name)
464
465 call assert_msg(442608616, gas_water_id_ .gt. 0, &
466 "Cannot find gas-phase water species '"//spec_name//"' for "// &
467 "PDFiTE activity reaction.")
468
469 ! Set the aerosol-water species
470 key_name = "aerosol-phase water"
471 call assert_msg(214613153, &
472 this%property_set%get_string(key_name, spec_name), &
473 "Missing aerosol-phase water species name in PDFiTE activity "// &
474 "reaction.")
475
476 ! Make the PHASE_ID_(x) hold the state id of aerosol water in each
477 ! phase instance. Then the aerosol water id is 1, and the ion
478 ! ids will be relative to the water id in each phase.
479 i_phase = 1
480 do i_aero_rep = 1, size(aero_rep_set)
481 unique_spec_names = aero_rep_set(i_aero_rep)%val%unique_names( &
482 phase_name = phase_name, spec_name = spec_name)
483 if (.not.allocated(unique_spec_names)) cycle
484 do i_spec = 1, size(unique_spec_names)
485 phase_id_(i_phase) = aero_rep_set(i_aero_rep)%val%spec_state_id( &
486 unique_spec_names(i_spec)%string)
487 call assert(658622226, phase_id_(i_phase).gt.0)
488 i_phase = i_phase + 1
489 end do
490 deallocate(unique_spec_names)
491 end do
492 i_phase = i_phase - 1
493 call assert_msg(653357919, i_phase.eq.num_phase_, &
494 "Incorrect number of aerosol water instances in PDFiTE "// &
495 "activity reaction. Expected "//trim(to_string(num_phase_))// &
496 " but got "//trim(to_string(i_phase)))
497
498 ! Save the ion_pair parameters
499 n_int_param = num_int_prop_ + num_phase_ + 2*num_ion_pairs_
500 n_float_param = num_real_prop_
501 call ion_pairs%iter_reset()
502 do i_ion_pair = 1, n_ion_pair
503
504 ! Get the name of the ion_pair
505 ion_pair_name = ion_pair_names(i_ion_pair)%string
506
507 ! Set the location of this ion_pair's parameters in the condensed data
508 ! arrays.
509 pair_int_param_loc_(i_ion_pair) = n_int_param + 1
510 pair_float_param_loc_(i_ion_pair) = n_float_param + 1
511
512 ! Get the activity coefficient state ids for this ion_pair
513 i_phase = 1
514 do i_aero_rep = 1, size(aero_rep_set)
515 unique_spec_names = aero_rep_set(i_aero_rep)%val%unique_names( &
516 phase_name = phase_name, spec_name = ion_pair_name)
517 if (.not.allocated(unique_spec_names)) cycle
518 do i_spec = 1, size(unique_spec_names)
519 if (i_phase.eq.1) then
520 ion_pair_act_id_(i_ion_pair) = &
521 aero_rep_set(i_aero_rep)%val%spec_state_id( &
522 unique_spec_names(i_spec)%string) - &
523 phase_id_(i_phase)
524 else
525 call assert(142173386, ion_pair_act_id_(i_ion_pair).eq. &
526 aero_rep_set(i_aero_rep)%val%spec_state_id( &
527 unique_spec_names(i_spec)%string) - &
528 phase_id_(i_phase))
529 end if
530 i_phase = i_phase + 1
531 end do
532 deallocate(unique_spec_names)
533 end do
534 i_phase = i_phase - 1
535 call assert_msg(700406338, i_phase.eq.num_phase_, &
536 "Incorrect number of instances of ion pair '"// &
537 ion_pair_name//"' in PDFiTE activity reaction. Expected "// &
538 trim(to_string(num_phase_))//" but got "// &
539 trim(to_string(i_phase)))
540
541 ! Get the ion_pair species properties
542 call assert_msg(737691158, &
543 chem_spec_data%get_property_set(ion_pair_name, ion_pair), &
544 "Missing species properties for ion pair '"// &
545 ion_pair_name//"' in PDFiTE activity reaction.")
546
547 ! Make sure the specified ion pair is of the right tracer type
548 call assert(667033398, &
549 chem_spec_data%get_type(ion_pair_name, tracer_type))
550 call assert_msg(153203913, tracer_type.eq.chem_spec_activity_coeff, &
551 "Ion pair '"//ion_pair_name//"' must have a tracer type '"// &
552 "ION_PAIR' to participate in a PD-FiTE activity reaction.")
553
554 ! Get the number and id of the ions and their molecular weights
555 key_name = "ions"
556 call assert_msg(974596824, ion_pair%get_property_t(key_name, ions), &
557 "Mission ions for ion pair '"//ion_pair_name// &
558 "' in PDFiTE activity reaction.")
559
560 call assert_msg(852202160, ions%size().eq.2, &
561 "Invalid number of unique ions specified for ion pair '"// &
562 ion_pair_name//"' in for PDFiTE in activity reaction. "// &
563 "Expected 2 got "//trim(to_string(ions%size())))
564
565 ! TODO Consider moving some of the ion data validation to
566 ! camp_chem_spec_data
567 call ions%iter_reset()
568 total_charge = 0
569 do i_ion = 1, 2
570
571 ! Get the ion name
572 call assert(622753458, ions%get_key(ion_name))
573
574 ! Get the qty, if specified
575 qty = 1
576 if (ions%get_property_t(val=sub_props)) then
577 key_name = "qty"
578 if (sub_props%get_int(key_name, int_val)) qty = int_val
579 end if
580
581 ! Get the species properties
582 call assert_msg(619394685, &
583 chem_spec_data%get_property_set(ion_name, spec_props), &
584 "Missing species properties for ion '"//ion_name// &
585 "' in PDFiTE activity reaction.")
586
587 ! Get the molecular weight
588 key_name = "molecular weight [kg mol-1]"
589 call assert_msg(951085413, &
590 spec_props%get_real(key_name, molecular_weight), &
591 "Missing molecular weight for ion '"//ion_name// &
592 "' in PDFiTE activity reaction.")
593
594 ! Add the charge from this species
595 key_name = "charge"
596 call assert_msg(663798152, spec_props%get_int(key_name, charge), &
597 "Missing charge for ion '"//ion_name//"' in PDFiTE "// &
598 "activity reaction.")
599
600 if (charge.gt.0) then
601 num_cation_(i_ion_pair) = qty
602 cation_mw_(i_ion_pair) = molecular_weight
603 else if (charge.lt.0) then
604 num_anion_(i_ion_pair) = qty
605 anion_mw_(i_ion_pair) = molecular_weight
606 else
607 call die_msg(939555855, "Neutral species '"//ion_name// &
608 "' not allowed in PDFiTE activity reaction ion pair")
609 end if
610
611 ! Add contribution to total charge
612 total_charge = total_charge + qty * charge
613
614 ! Get the state ids for this species
615 i_phase = 1
616 do i_aero_rep = 1, size(aero_rep_set)
617 unique_spec_names = aero_rep_set(i_aero_rep)%val%unique_names( &
618 phase_name = phase_name, spec_name = ion_name)
619 if (.not.allocated(unique_spec_names)) cycle
620 do i_spec = 1, size(unique_spec_names)
621 if (charge.gt.0) then
622 if (i_phase.eq.1) then
623 cation_id_(i_ion_pair) = &
624 aero_rep_set(i_aero_rep)%val%spec_state_id( &
625 unique_spec_names(i_spec)%string) - &
626 phase_id_(i_phase)
627 else
628 call assert(425726370, cation_id_(i_ion_pair).eq. &
629 aero_rep_set(i_aero_rep)%val%spec_state_id( &
630 unique_spec_names(i_spec)%string) - &
631 phase_id_(i_phase))
632 end if
633 else
634 if (i_phase.eq.1) then
635 anion_id_(i_ion_pair) = &
636 aero_rep_set(i_aero_rep)%val%spec_state_id( &
637 unique_spec_names(i_spec)%string) - &
638 phase_id_(i_phase)
639 else
640 call assert(192466600, anion_id_(i_ion_pair).eq. &
641 aero_rep_set(i_aero_rep)%val%spec_state_id( &
642 unique_spec_names(i_spec)%string) - &
643 phase_id_(i_phase))
644 end if
645 end if
646 i_phase = i_phase + 1
647 end do
648 deallocate(unique_spec_names)
649 end do
650 i_phase = i_phase - 1
651 call assert_msg(759322632, i_phase.eq.num_phase_, &
652 "Incorrect number of instances of ion species '"// &
653 ion_name//"' in PDFiTE activity reaction. Expected "// &
654 trim(to_string(num_phase_))//" but got "// &
655 trim(to_string(i_phase)))
656
657 ! Get the next ion
658 call ions%iter_next()
659
660 end do
661
662 call assert_msg(415650051, total_charge.eq.0, &
663 "Charge imbalance for ion_pair '"//ion_pair_name// &
664 " in PDFiTE activity reaction. Total charge: "// &
665 trim(to_string(total_charge)))
666
667 n_float_param = n_float_param + 4
668 n_int_param = n_int_param + 6 + (1+2*num_ion_pairs_)*num_phase_
669
670 ! The first portion of ion_pair_names holds species for which
671 ! activity coefficients are calculated
672 if (i_ion_pair.le.ion_pairs%size()) then
673 call assert(362061689, ion_pairs%get_key(string_val))
674 call assert(444603372, string_val.eq.ion_pair_name)
675
676 ! Get the ion_pair properties
677 call assert(520886936, ion_pairs%get_property_t(val=ion_pair))
678
679 ! Get the interactions
680 key_name = "interactions"
681 call assert(216229321, ion_pair%get_property_t(key_name,interactions))
682
683 ! Set the number of interactions for this ion pair
684 num_inter_(i_ion_pair) = interactions%size()
685
686 ! Get the interaction parameters
687 num_inter(:) = 0
688 call interactions%iter_reset()
689 do i_interaction = 1, interactions%size()
690
691 ! Set the location of the interaction float parameters
692 inter_spec_loc_(i_ion_pair, i_interaction) = n_float_param + 1
693
694 ! Get the current interaction
695 call assert(105466070, interactions%get_property_t(val=interaction))
696
697 ! Get the name of the interacting species
698 key_name = "ion pair"
699 call assert_msg(220815620, &
700 interaction%get_string(key_name, inter_spec_name), &
701 "Missing interacting species name for ion pair '"// &
702 ion_pair_name//"' in PDFiTE activity reaction.")
703
704 ! Mark the species as having an interaction and get the id of the
705 ! ion_pair in the 'calculate for' list
706 do i_spec = 1, size(ion_pair_names)
707 if (ion_pair_names(i_spec)%string.eq.inter_spec_name) then
708 num_inter(i_spec) = num_inter(i_spec) + 1
709 inter_spec_id_(i_ion_pair,i_interaction) = i_spec
710 exit
711 end if
712 end do
713
714 ! Set the minimum RH value
715 key_name = "min RH"
716 call assert_msg(519674084, &
717 interaction%get_real(key_name, &
718 min_rh_(i_ion_pair, i_interaction)), &
719 "Missing minimum RH value for ion pair '"// &
720 ion_pair_name//"' interaction with '"//inter_spec_name// &
721 "' in PD-FiTE activity reaction.")
722 min_rh = min_rh_(i_ion_pair, i_interaction)
723 call assert_msg(294172408, &
724 min_rh.ge.real(0.0, kind=dp).and. &
725 min_rh.lt.real(1.0, kind=dp), &
726 "Invalid value for minimum RH for ion pair '"// &
727 ion_pair_name//"' interaction with '"//inter_spec_name// &
728 "' in PD-FiTE activity reaction: "//to_string(min_rh))
729
730 ! Set the maximum RH value
731 key_name = "max RH"
732 call assert_msg(649525712, &
733 interaction%get_real(key_name, &
734 max_rh_(i_ion_pair, i_interaction)), &
735 "Missing maximum RH value for ion pair '"// &
736 ion_pair_name//"' interaction with '"//inter_spec_name// &
737 "' in PD-FiTE activity reaction.")
738 max_rh = max_rh_(i_ion_pair, i_interaction)
739 call assert_msg(840423507, &
740 max_rh.gt.real(0.0, kind=dp).and. &
741 max_rh.le.real(1.0, kind=dp), &
742 "Invalid value for maximum RH for ion pair '"// &
743 ion_pair_name//"' interaction with '"//inter_spec_name// &
744 "' in PD-FiTE activity reaction: "//to_string(max_rh))
745
746 ! Get the number of B_z parameters
747 key_name = "B"
748 call assert(981216440, &
749 interaction%get_property_t(key_name, poly_coeffs))
750 num_b_(i_ion_pair, i_interaction) = poly_coeffs%size()
751
752 ! Get the B_z parameters
753 call poly_coeffs%iter_reset()
754 do i_poly_coeff = 1, poly_coeffs%size()
755 call assert_msg(988796931, poly_coeffs%get_real(val=real_val), &
756 "Invalid polynomial coefficient for ion_pair '"// &
757 ion_pair_name//"' interaction with '"//inter_spec_name// &
758 "' in PDFiTE activity reaction.")
759 b_z_(i_ion_pair, i_interaction, i_poly_coeff) = real_val
760 call poly_coeffs%iter_next()
761 end do
762
763 n_float_param = n_float_param + 2 + num_b_(i_ion_pair, i_interaction)
764 n_int_param = n_int_param + 3
765
766 call interactions%iter_next()
767 end do
768
769 ! Check that all the interactions were included at least once
770 do i_spec = 1, size(num_inter)
771 call warn_assert_msg(793223082, num_inter(i_spec).ge.1, &
772 "Missing interaction parameters between ion_pair '"// &
773 ion_pair_name//"' and '"//ion_pair_names(i_spec)%string// &
774 "' in PDFiTE activity interaction: "// &
775 trim(to_string(num_inter(i_spec)))//".")
776 end do
777
778 ! Make sure no interactions with the same ion pair overlap in
779 ! their RH ranges and that the entire RH range (0.0-1.0) is covered.
780 ! Treat ranges as R = (minRH,maxRH] to avoid overlap at boundaries
781 rh_range(:) = 0.0
782 do i_interaction = 1, num_inter_(i_ion_pair)
783
784 ! Check for RH range overlaps with other interactions with this
785 ! ion pair
786 do j_interaction = i_interaction+1, num_inter_(i_ion_pair)
787 if (inter_spec_id_(i_ion_pair, i_interaction).ne. &
788 inter_spec_id_(i_ion_pair, j_interaction)) cycle
789 call assert_msg(858420675, &
790 min_rh_(i_ion_pair, i_interaction).ge. &
791 max_rh_(i_ion_pair, j_interaction).or. &
792 max_rh_(i_ion_pair, i_interaction).le. &
793 min_rh_(i_ion_pair, j_interaction), &
794 "Overlapping RH range for interactions for ion pair '"// &
795 ion_pair_name//"' in PD-FiTE activity reaction.")
796 end do
797
798 ! Add the constribution from this interaction to RH coverage for
799 ! the interacting ion pair
800 rh_range(inter_spec_id_(i_ion_pair, i_interaction)) = &
801 rh_range(inter_spec_id_(i_ion_pair, i_interaction)) + &
802 (max_rh_(i_ion_pair, i_interaction) - &
803 min_rh_(i_ion_pair, i_interaction))
804 end do
805
806 ! Make sure the entire RH range is covered
807 do i_spec = 1, size(rh_range)
808 call assert_msg(370258071, &
809 rh_range(i_spec).eq.real(1.0, kind=dp).or. &
810 num_inter(i_spec).eq.0, &
811 "Incomplete RH coverage for interaction with ion pair '"// &
812 ion_pair_names(i_spec)%string//"' for '"//ion_pair_name// &
813 "' PD-FiTE activity coefficient calculation.")
814 end do
815
816 call ion_pairs%iter_next()
817
818 ! The last portion of ion_pair_names includes ion pairs that are
819 ! included in the interactions but for which acitivty coefficients
820 ! are not calculated
821 else
822
823 ! Set the number of interactions to zero to indicate not to calculate
824 ! activity coefficients for this ion pair
825 num_inter_(i_ion_pair) = 0
826
827 end if
828
829 end do
830
831 call assert(938415336, n_int_param.eq.total_int_param_)
832 call assert(433208931, n_float_param.eq.total_float_param_)
833
834 deallocate(ion_pair_names)
835 deallocate(num_inter)
836 deallocate(rh_range)
837
838 end subroutine initialize
839
840!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
841
842 !> Finalize the reaction
843 elemental subroutine finalize(this)
844
845 !> Reaction data
846 type(sub_model_pdfite_t), intent(inout) :: this
847
848 if (associated(this%property_set)) &
849 deallocate(this%property_set)
850 if (allocated(this%condensed_data_real)) &
851 deallocate(this%condensed_data_real)
852 if (allocated(this%condensed_data_int)) &
853 deallocate(this%condensed_data_int)
854
855 end subroutine finalize
856
857!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
858
859 !> Return a real number representing the priority of the sub model
860 !! calculations. Low priority sub models may use the results of higher
861 !! priority sub models. Lower numbers indicate higher priority.
862 !!
863 !! PD-FiTE calculations may depend on water concentrations, so must be
864 !! lower priority than the ZSR sub model.
865 function priority(this)
866
867 !> Sub model priority
868 real(kind=dp) :: priority
869 !> Sub model data
870 class(sub_model_pdfite_t), intent(in) :: this
871
872 priority = 2.0;
873
874 end function priority
875
876!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
877
878end module camp_sub_model_pdfite
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_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 abstract sub_model_data_t structure and associated subroutines.
The sub_model_PDFiTE_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
subroutine warn_assert_msg(code, condition_ok, warning_msg)
Prints a warning message if condition_ok is false.
Definition util.F90:112
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