CAMP 1.0.0
Chemistry Across Multiple Phases
rxn_HL_phase_transfer.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_HL_phase_transfer module.
7
8!> \page camp_rxn_HL_phase_transfer CAMP: Henry's Law Phase-Transfer Reaction
9!!
10!! Henry's Law phase-trasfer reactions use equilibrium rate constants that
11!! are calculated as:
12!!
13!! \f[
14!! HLC(298K) * e^{C({1/T-1/298})}
15!! \f]
16!!
17!! where \f$HLC(298K)\f$ is the Henry's Law constant at 298 K
18!! [M\f$\mbox{Pa}^{-1}\f$], \f$C\f$ is a constant [K] and
19!! \f$T\f$ is the temperature [K]. Uptake kinetics are based on
20!! the particle effective radius, \f$r_{eff}\f$ [\f$\mbox{m}\f$], the
21!! condensing species gas-phase diffusion coefficient, \f$D_g\f$
22!! [\f$\mbox{m}^2\,\mbox{s}^{-1}\f$], its molecular weight \f$MW\f$
23!! [kg\f$\mbox{mol}^{-3}\f$], and \f$N^{*}\f$, which is
24!! used to calculate the mass accomodation coefficient.
25!!
26!! Mass accomodation coefficients and condensation rate constants are
27!! calculated using the method of Ervans et al. (2003) \cite Ervens2003 and
28!! references therein. Mass accomodation coefficients (\f$\alpha\f$) are
29!! calculated as:
30!!
31!! \f[
32!! \Delta H_{obs} = -10 \times (N^*-1) + 7.53 \times (N^{*2/3}-1) - 0.1 \times 10 \quad (\mbox{kcal}\,\mbox{M}^{-1})
33!! \f]
34!! \f[
35!! \Delta S_{obs} = -13 \times (N^*-1) - 19 \times (N^*-1) + 9.21 \times (N^{*2/3}-1) - 0.1 \times 13 \quad (\mbox{cal}\,\mbox{M}^{-1}\,\mbox{K}^{-1})
36!! \f]
37!! \f[
38!! \frac{\alpha}{1-\alpha} = e^{\frac{-\Delta G^{*}}{RT}}
39!! \f]
40!! If \f$\Delta H\f$ and \f$\Delta S\f$ are not provided, \f$\alpha\f$ is
41!! set to 0.1 \cite Zaveri2008.
42!!
43!! Condensation rate constants are calculated following \cite Zaveri2008 as:
44!! \f[
45!! k_c = 4 \pi r D_g f_{fs}( K_n, \alpha )
46!! \f]
47!! where \f$r\f$ is the radius of the particle(s) [m], \f$D_g\f$ is the
48!! diffusion coefficient of the gas-phase species [\f$\mbox{m}^2\,\mbox{s}^{-1}\f$],
49!! \f$f_{fs}( K_n, \alpha )\f$ is the Fuchs Sutugin transition regime correction
50!! factor [unitless], \f$K_n\f$ is the Knudsen Number [unitess], and \f$\alpha\f$
51!! is the mass accomodation coefficient.
52!!
53!! Rates can be calculated as:
54!! \f[
55!! r_c = [G] N_a k_c
56!! \f]
57!! where \f$[G]\f$ is the gas-phase species concentration [ppm], \f$N_a\f$ is
58!! the number concentration of particles [\f$\mbox{particle}\,\mbox{m}^{-3}\f$] and
59!! the rate \f$r_c\f$ is in [\f$\mbox{ppm}\,\mbox{s}^{-1}\f$].
60!! The particle radius used
61!! to calculate \f$k_{f}\f$ is the effective radius [\f$r_{eff}\f$], which is
62!! taken as the "least-wrong" choice for condensation rates, as it is weighted
63!! to surface area \cite Zender2002 .
64!!
65!! Input data for Phase transfer equations have the following format :
66!! \code{.json}
67!! {
68!! "type" : "HL_PHASE_TRANSFER",
69!! "gas-phase species" : "my gas spec",
70!! "aerosol-phase species" : "my aero spec",
71!! "areosol phase" : "my aqueous phase",
72!! "aerosol-phase water" : "H2O_aq",
73!! ...
74!! }
75!! \endcode
76!! The key-value pairs \b gas-phase \b species, and \b aerosol-phase
77!! \b species are required. Only one gas- and one aerosol-phase species are
78!! allowed per phase-transfer reaction. Additionally, gas-phase species must
79!! include parameters named \b HLC(298K) \b [\b M \b Pa-1], which is the Henry's
80!! Law constant at 298 K, \b HLC \b exp \b factor \b [\b K], which is the
81!! Henry's Law constant exponential factor "C", \b diffusion \b coeff \b [\b m2
82!! \b s-1], which specifies the diffusion coefficient in
83!! \f$\mbox{m}^2\,\mbox{s}^{-1}\f$, and \b molecular \b weight
84!! \b [\b kg \b mol-1], which specifies the molecular weight of the species in
85!! \f$\mbox{kg}\,\mbox{mol}^{-1}\f$. They may optionally include the
86!! parameter \b N \b star, which will be used to calculate the mass
87!! accomodation coefficient. When this parameter is not included, the mass
88!! accomodation coefficient is assumed to be 1.0.
89
90!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
91
92!> The rxn_HL_phase_transfer_t type and associated functions.
94
98 use camp_constants, only: const
100 use camp_property
101 use camp_rxn_data
102 use camp_util, only: i_kind, dp, to_string, &
105
106 implicit none
107 private
108
109#define DELTA_H_ this%condensed_data_real(1)
110#define DELTA_S_ this%condensed_data_real(2)
111#define DIFF_COEFF_ this%condensed_data_real(3)
112#define PRE_C_AVG_ this%condensed_data_real(4)
113#define A_ this%condensed_data_real(5)
114#define C_ this%condensed_data_real(6)
115#define CONV_ this%condensed_data_real(7)
116#define MW_ this%condensed_data_real(8)
117#define NUM_AERO_PHASE_ this%condensed_data_int(1)
118#define GAS_SPEC_ this%condensed_data_int(2)
119#define NUM_INT_PROP_ 2
120#define NUM_REAL_PROP_ 8
121#define NUM_ENV_PARAM_ 4
122#define DERIV_ID_(x) this%condensed_data_int(NUM_INT_PROP_+x)
123#define JAC_ID_(x) this%condensed_data_int(NUM_INT_PROP_+1+NUM_AERO_PHASE_+x)
124#define PHASE_INT_LOC_(x) this%condensed_data_int(NUM_INT_PROP_+2+6*NUM_AERO_PHASE_+x)
125#define PHASE_REAL_LOC_(x) this%condensed_data_int(NUM_INT_PROP_+2+7*NUM_AERO_PHASE_+x)
126#define AERO_SPEC_(x) this%condensed_data_int(PHASE_INT_LOC_(x))
127#define AERO_WATER_(x) this%condensed_data_int(PHASE_INT_LOC_(x)+1)
128#define AERO_PHASE_ID_(x) this%condensed_data_int(PHASE_INT_LOC_(x)+2)
129#define AERO_REP_ID_(x) this%condensed_data_int(PHASE_INT_LOC_(x)+3)
130#define NUM_AERO_PHASE_JAC_ELEM_(x) this%condensed_data_int(PHASE_INT_LOC_(x)+4)
131#define PHASE_JAC_ID_(x,s,e) this%condensed_data_int(PHASE_INT_LOC_(x)+4+(s-1)*NUM_AERO_PHASE_JAC_ELEM_(x)+e)
132#define SMALL_WATER_CONC_(x) this%condensed_data_real(PHASE_REAL_LOC_(x))
133#define EFF_RAD_JAC_ELEM_(x,e) this%condensed_data_real(PHASE_REAL_LOC_(x)+e)
134#define NUM_CONC_JAC_ELEM_(x,e) this%condensed_data_real(PHASE_REAL_LOC_(x)+NUM_AERO_PHASE_JAC_ELEM_(x)+e)
135
137
138 !> Generic test reaction data type
140 contains
141 !> Reaction initialization
142 procedure :: initialize
143 !> Finalize the reaction
144 final :: finalize
146
147 !> Constructor for rxn_HL_phase_transfer_t
149 procedure :: constructor
150 end interface rxn_hl_phase_transfer_t
151
152contains
153
154!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
155
156 !> Constructor for Phase transfer reaction
157 function constructor() result(new_obj)
158
159 !> A new reaction instance
160 type(rxn_hl_phase_transfer_t), pointer :: new_obj
161
162 allocate(new_obj)
163 new_obj%rxn_phase = aero_rxn
164
165 end function constructor
166
167!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
168
169 !> Initialize the reaction data, validating component data and loading
170 !! any required information into the condensed data arrays for use during
171 !! solving
172 subroutine initialize(this, chem_spec_data, aero_rep, n_cells)
173
174 !> Reaction data
175 class(rxn_hl_phase_transfer_t), intent(inout) :: this
176 !> Chemical species data
177 type(chem_spec_data_t), intent(in) :: chem_spec_data
178 !> Aerosol representations
179 type(aero_rep_data_ptr), pointer, intent(in) :: aero_rep(:)
180 !> Number of grid cells to solve simultaneously
181 integer(kind=i_kind), intent(in) :: n_cells
182
183 type(property_t), pointer :: spec_props
184 character(len=:), allocatable :: key_name, gas_spec_name, &
185 water_name, aero_spec_name, phase_name, error_msg
186 integer(kind=i_kind) :: i_spec, i_aero_rep, n_aero_ids, i_aero_id, &
187 n_aero_jac_elem, i_phase, tmp_size
188 type(string_t), allocatable :: unique_spec_names(:), &
189 unique_water_names(:)
190 integer(kind=i_kind), allocatable :: phase_ids(:)
191 real(kind=dp) :: temp_real, n_star
192
193 ! Get the property set
194 if (.not. associated(this%property_set)) call die_msg(318525776, &
195 "Missing property set needed to initialize reaction")
196
197 ! Get the gas-phase species name
198 key_name = "gas-phase species"
199 call assert_msg(847983010, &
200 this%property_set%get_string(key_name, gas_spec_name), &
201 "Missing gas-phase species in phase-transfer reaction")
202
203 ! Get the aerosol phase name
204 key_name = "aerosol phase"
205 call assert_msg(448087197, &
206 this%property_set%get_string(key_name, phase_name), &
207 "Missing aerosol phase in phase-transfer reaction")
208
209 ! Get the aerosol-phase species name
210 key_name = "aerosol-phase species"
211 call assert_msg(797902545, &
212 this%property_set%get_string(key_name, aero_spec_name), &
213 "Missing aerosol-phase species in phase-transfer reaction")
214
215 ! Set up a general error message
216 error_msg = " for HL partitioning reaction of gas-phase species '"// &
217 gas_spec_name//"' to aerosol-phase species '"// &
218 aero_spec_name//"' in phase '"//phase_name
219
220 ! Get the aerosol-phase water name
221 key_name = "aerosol-phase water"
222 call assert_msg(386889865, &
223 this%property_set%get_string(key_name, water_name), &
224 "Missing aerosol-phase water"//error_msg)
225
226 ! Check for aerosol representations
227 call assert_msg(234155350, associated(aero_rep), &
228 "Missing aerosol representation"//error_msg)
229 call assert_msg(207961800, size(aero_rep).gt.0, &
230 "Missing aerosol representation"//error_msg)
231
232 ! Count the instances of this phase/species pair, and the number of
233 ! Jacobian elements needed in calculations of mass, volume, etc.
234 n_aero_ids = 0
235 n_aero_jac_elem = 0
236 do i_aero_rep = 1, size(aero_rep)
237
238 ! Get the unique names in this aerosol representation for the
239 ! partitioning species and aerosol-phase water
240 unique_spec_names = aero_rep(i_aero_rep)%val%unique_names( &
241 phase_name = phase_name, spec_name = aero_spec_name)
242 unique_water_names = aero_rep(i_aero_rep)%val%unique_names( &
243 phase_name = phase_name, spec_name = water_name)
244
245 ! Skip aerosol representations that do not contain this phase
246 if (.not.allocated(unique_spec_names)) cycle
247
248 ! Check the size of the unique name lists
249 call assert_msg(598091463, size(unique_spec_names).eq. &
250 size(unique_water_names), "Missing species "// &
251 aero_spec_name//" or "//water_name//" in phase "//phase_name// &
252 " or improper implementation of aerosol phase in aerosol "// &
253 "representation"//error_msg)
254
255 ! Add these instances to the list
256 n_aero_ids = n_aero_ids + size(unique_spec_names)
257
258 ! Get the number of Jacobian elements for calculations of mass, volume,
259 ! number, etc. for this partitioning into this phase
260 phase_ids = aero_rep(i_aero_rep)%val%phase_ids(phase_name, is_at_surface=.true.)
261 do i_phase = 1, size(phase_ids)
262 n_aero_jac_elem = n_aero_jac_elem + &
263 aero_rep(i_aero_rep)%val%num_jac_elem(phase_ids(i_phase))
264 end do
265
266 deallocate(unique_spec_names)
267 deallocate(unique_water_names)
268
269 end do
270
271 ! Allocate space in the condensed data arrays
272 allocate(this%condensed_data_int(num_int_prop_ + 2 + n_aero_ids * 13 + &
273 n_aero_jac_elem * 2))
274 allocate(this%condensed_data_real(num_real_prop_ + n_aero_ids + &
275 n_aero_jac_elem * 2))
276 this%condensed_data_int(:) = int(0, kind=i_kind)
277 this%condensed_data_real(:) = real(0.0, kind=dp)
278
279 ! Save space for the environment-dependent parameters
280 this%num_env_params = num_env_param_
281
282 ! Set the number of aerosol-species instances
283 num_aero_phase_ = n_aero_ids
284
285 ! Get the properties required of the aerosol species
286 call assert_msg(669162256, &
287 chem_spec_data%get_property_set(aero_spec_name, spec_props), &
288 "Missing aerosol species properties"//error_msg)
289
290 ! Get the aerosol species molecular weight
291 key_name = "molecular weight [kg mol-1]"
292 call assert_msg(209812557, spec_props%get_real(key_name, mw_), &
293 "Missing property 'MW' for aerosol species"//error_msg)
294
295 ! Set the kg/m3 -> ppm conversion prefactor (multiply by T/P to get
296 ! conversion)
297 conv_ = const%univ_gas_const / mw_ * 1.0e6
298
299 ! Get the aerosol-phase water species
300 key_name = "aerosol-phase water"
301 call assert_msg(374667967, &
302 this%property_set%get_string(key_name, water_name), &
303 "Missing aerosol-phase water"//error_msg)
304
305 ! Set the ids of each aerosol-phase species instance
306 i_aero_id = 1
307 phase_int_loc_(i_aero_id) = num_int_prop_+8*num_aero_phase_+3
308 phase_real_loc_(i_aero_id) = num_real_prop_+1
309 do i_aero_rep = 1, size(aero_rep)
310
311 ! Get the unique names in this aerosol representation for the
312 ! partitioning species and aerosol-phase water
313 unique_spec_names = aero_rep(i_aero_rep)%val%unique_names( &
314 phase_name = phase_name, spec_name = aero_spec_name)
315 unique_water_names = aero_rep(i_aero_rep)%val%unique_names( &
316 phase_name = phase_name, spec_name = water_name)
317
318 ! Get the phase ids for this aerosol phase
319 phase_ids = aero_rep(i_aero_rep)%val%phase_ids(phase_name, is_at_surface=.true.)
320
321 ! Add the species concentration and activity coefficient ids to
322 ! the condensed data, and set the number of jacobian elements for
323 ! the aerosol representations and the locations of the real data
324 do i_spec = 1, size(unique_spec_names)
325 num_aero_phase_jac_elem_(i_aero_id) = &
326 aero_rep(i_aero_rep)%val%num_jac_elem(phase_ids(i_spec))
327 aero_spec_(i_aero_id) = &
328 aero_rep(i_aero_rep)%val%spec_state_id( &
329 unique_spec_names(i_spec)%string)
330 aero_water_(i_aero_id) = &
331 aero_rep(i_aero_rep)%val%spec_state_id( &
332 unique_water_names(i_spec)%string)
333 aero_phase_id_(i_aero_id) = phase_ids(i_spec)
334 aero_rep_id_(i_aero_id) = i_aero_rep
335 i_aero_id = i_aero_id + 1
336 if (i_aero_id .le. num_aero_phase_) then
337 phase_int_loc_(i_aero_id) = phase_int_loc_(i_aero_id - 1) + 5 + &
338 2*num_aero_phase_jac_elem_(i_aero_id - 1)
339 phase_real_loc_(i_aero_id) = phase_real_loc_(i_aero_id - 1) + 1 + &
340 2*num_aero_phase_jac_elem_(i_aero_id - 1)
341 end if
342 end do
343
344 deallocate(unique_spec_names)
345 deallocate(unique_water_names)
346
347 end do
348
349 ! Save the index of the gas-phase species in the state variable array
350 gas_spec_ = chem_spec_data%gas_state_id(gas_spec_name)
351
352 ! Make sure the species exists
353 call assert_msg(955306778, gas_spec_.gt.0, &
354 "Missing gas-phase species"//error_msg)
355
356 ! Get the required properties for the gas-phase species
357 call assert_msg(757296139, &
358 chem_spec_data%get_property_set(gas_spec_name, spec_props), &
359 "Missing gas-phase species properties"//error_msg)
360
361 ! Get Henry's Law constant parameters
362 key_name = "HLC(298K) [M Pa-1]"
363 call assert_msg(637925661, spec_props%get_real(key_name, a_), &
364 "Missing Henry's Law constant at 298 K"//error_msg)
365
366 key_name = "HLC exp factor [K]"
367 call assert_msg(801365019, spec_props%get_real(key_name, c_), &
368 "Missing Henry's Law constant exponential factor"// &
369 error_msg)
370
371 ! Get N* to calculate the mass accomodation coefficient. If it is not
372 ! present, set DELTA_H_ and DELTA_S_ to zero to indicate a mass accomodation
373 ! coefficient of 1.0
374 ! Mass accomodation equation is based on equations in:
375 ! Ervens, B., et al., 2003. "CAPRAM 2.4 (MODAC mechanism): An extended
376 ! and condensed tropospheric aqueous mechanism and its application."
377 ! J. Geophys. Res. 108, 4426. doi:10.1029/2002JD002202
378 key_name = "N star"
379 if (spec_props%get_real(key_name, n_star)) then
380 ! enthalpy change (kcal mol-1)
381 delta_h_ = real(- 10.0d0*(n_star-1.0d0) + &
382 7.53d0*(n_star**(2.0d0/3.0d0)-1.0d0) - 1.0d0, kind=dp)
383 ! entropy change (cal mol-1)
384 delta_s_ = real(- 32.0d0*(n_star-1.0d0) + &
385 9.21d0*(n_star**(2.0d0/3.0d0)-1.0d0) - 1.3d0, kind=dp)
386 ! Convert dH and dS to (J mol-1)
387 delta_h_ = real(delta_h_ * 4184.0d0, kind=dp)
388 delta_s_ = real(delta_s_ * 4.184d0, kind=dp)
389 else
390 delta_h_ = real(0.0, kind=dp)
391 delta_s_ = real(0.0, kind=dp)
392 end if
393
394 ! Get the diffusion coefficient (m^2/s)
395 key_name = "diffusion coeff [m2 s-1]"
396 call assert_msg(100205531, spec_props%get_real(key_name, diff_coeff_), &
397 "Missing diffusion coefficient for gas-phase species"//error_msg)
398
399 ! Calculate the constant portion of c_rms [m/(K^2*s)]
400 key_name = "molecular weight [kg mol-1]"
401 call assert_msg(469582180, spec_props%get_real(key_name, temp_real), &
402 "Missing molecular weight for gas-phase species"//error_msg)
403 pre_c_avg_ = sqrt(8.0*const%univ_gas_const/(const%pi*temp_real))
404
405 ! Check the sizes of the data arrays
406 tmp_size = phase_int_loc_(i_aero_id - 1) + 5 + &
407 2*num_aero_phase_jac_elem_(i_aero_id - 1) - 1
408 call assert_msg(881234422, size(this%condensed_data_int) .eq. tmp_size, &
409 "int array size mismatch"//error_msg)
410 tmp_size = phase_real_loc_(i_aero_id - 1) + 1 + &
411 2*num_aero_phase_jac_elem_(i_aero_id - 1) - 1
412 call assert_msg(520767976, size(this%condensed_data_real) .eq. tmp_size,&
413 "real array size mismatch"//error_msg)
414
415 end subroutine initialize
416
417!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
418
419 !> Finalize the reaction
420 elemental subroutine finalize(this)
421
422 !> Reaction data
423 type(rxn_hl_phase_transfer_t), intent(inout) :: this
424
425 if (associated(this%property_set)) &
426 deallocate(this%property_set)
427 if (allocated(this%condensed_data_real)) &
428 deallocate(this%condensed_data_real)
429 if (allocated(this%condensed_data_int)) &
430 deallocate(this%condensed_data_int)
431
432 end subroutine finalize
433
434!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
435
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.
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.
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_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
The rxn_HL_phase_transfer_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 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