143 subroutine initialize(this, chem_spec_data, aero_rep, n_cells)
152 integer(kind=i_kind),
intent(in) :: n_cells
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
165 if (.not.
associated(this%property_set))
call die_msg(206493887, &
166 "Missing property set needed to initialize reaction")
169 key_name =
"aerosol phase"
171 this%property_set%get_string(key_name, phase_name), &
172 "Missing aerosol phase in aqueous-equilibrium reaction")
175 key_name =
"aerosol-phase water"
177 this%property_set%get_string(key_name, water_name), &
178 "Missing aerosol-phase water in aqueous-equilibrium reaction")
181 key_name =
"reactants"
183 this%property_set%get_property_t(key_name, reactants), &
184 "Missing reactant species in aqueous-equilibrium reaction")
187 key_name =
"products"
189 this%property_set%get_property_t(key_name, products), &
190 "Missing product species in aqueous-equilibrium reaction")
194 call reactants%iter_reset()
198 call assert(422080799, reactants%get_property_t(val=spec_props))
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
205 call products%iter_reset()
209 call assert(971363961, products%get_property_t(val=spec_props))
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
216 num_spec_per_phase = num_prod + num_react
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")
226 do i_aero_rep = 1,
size(aero_rep)
229 if (aero_rep(i_aero_rep)%val%num_phase_instances(phase_name).eq.0) cycle
233 phase_name = phase_name,
spec_name = water_name)
235 "Missing aerosol-phase water species '"//water_name// &
236 "' in phase '"//phase_name//
"'")
238 "Missing aerosol-phase water species '"//water_name// &
239 "' in phase '"//phase_name//
"'")
251 "No aerosol phase '"//phase_name//
"' present.")
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)
262 this%num_env_params = num_env_param_
265 num_react_ = num_react
267 num_aero_phase_ = num_phase
271 if (.not. this%property_set%get_real(key_name, a_))
then
275 if (.not. this%property_set%get_real(key_name, c_))
then
278 key_name =
"k_reverse"
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
290 allocate(react_names(num_react_))
291 allocate(prod_names(num_prod_))
294 call reactants%iter_reset()
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)//
"'")
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.")
311 call assert(971363961, reactants%get_property_t(val=spec_props))
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
318 react_names(i_phase_inst)%string =
spec_name
321 mass_frac_to_m_(i_phase_inst) = 1.0d3/temp_real
326 call reactants%iter_next()
331 call products%iter_reset()
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)//
"'")
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.")
348 call assert(294785742, products%get_property_t(val=spec_props))
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
355 prod_names(i_phase_inst)%string =
spec_name
358 mass_frac_to_m_(num_react_ + i_phase_inst) = 1.0d3/temp_real
363 call products%iter_next()
369 key_name =
"ion pair"
370 if (.not. this%property_set%get_string(key_name, ion_pair_name))
then
376 do i_aero_rep = 1,
size(aero_rep)
379 if (aero_rep(i_aero_rep)%val%num_phase_instances(phase_name).eq.0) cycle
383 phase_name = phase_name,
spec_name = water_name)
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( &
399 if (ion_pair_name.ne.
"")
then
403 phase_name = phase_name,
spec_name = ion_pair_name)
407 "Incorrect instances of ion pair '"//ion_pair_name// &
408 "' in phase '"//phase_name// &
409 "' in an aqueous equilibrium reaction")
413 chem_spec_data%get_type(ion_pair_name, tracer_type))
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.")
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( &
429 do i_phase_inst = 1, num_phase
430 activity_coeff_(i_aero_phase + i_phase_inst) = 0
435 do i_phase_inst = 1, num_react_
439 phase_name = phase_name, &
440 spec_name = react_names(i_phase_inst)%string)
444 "Incorrect instances of reactant '"// &
445 react_names(i_phase_inst)%string// &
446 "' in phase '"//phase_name// &
447 "' in an aqueous equilibrium reaction")
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( &
463 do i_phase_inst = 1, num_prod_
467 phase_name = phase_name, &
468 spec_name = prod_names(i_phase_inst)%string)
472 "Incorrect instances of product '"// &
473 prod_names(i_phase_inst)%string// &
474 "' in phase '"//phase_name// &
475 "' in an aqueous equilibrium reaction")
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( &
491 i_aero_phase = i_aero_phase + num_phase