afivo-streamer 1.1
1D/2D/3D streamer simulations with AMR
Loading...
Searching...
No Matches
m_photoi.f90
Go to the documentation of this file.
1!> Top-module for photoionization, which can make use of different methods
2module m_photoi
3#include "../afivo/src/cpp_macros.h"
6 use m_af_all
7 use m_streamer
8 use m_types
11
12 implicit none
13 private
14
15 !> Whether photoionization is enabled
16 logical, protected, public :: photoi_enabled = .false.
17
18 !> Whether photoemission is enabled
19 logical, protected, public :: photoe_enabled = .false.
20
21 !> Which photoionization method to use (helmholtz, montecarlo)
22 character(len=20) :: photoi_method = 'helmholtz'
23
24 !> Which photoionization source to use (Zheleznyak, from_species)
25 character(len=20) :: photoi_source_type = 'Zheleznyak'
26
27 !> Which species is ionized by photoionization
28 character(len=20) :: photoi_species = 'O2_plus'
29
30 !> Index of species ionized by photoionization (in list of chemical species)
31 integer, public, protected :: photoi_species_index = -1
32
33 !> Name of the excited species in case photoi_source_type is 'from_species'
34 character(len=string_len) :: photoi_excited_species = 'UNDEFINED'
35
36 !> Index of the excited species
37 integer :: i_excited_species = -1
38
39 !> Photoionization efficiency factor, typically around 0.05-0.1, not for
40 !> Helmholtz-Luque should be 1.0
41 real(dp) :: photoi_eta = 0.05_dp
42
43 !> Quenching pressure for dry air
44 real(dp) :: photoi_quenching_pressure = 40e-3 ! bar
45
46 !> Photoionization quenching pressure for H2O in Aints model (bar)")
47 real(dp) :: photoi_quenching_pressure_h2o_aints = 0.3 * uc_torr_to_bar
48
49 !> Decay time in case photoi_source_type is 'from_species'
50 real(dp) :: photoi_photoemission_time = 0.0_dp
51
52 !> Update photoionization every N time step
53 integer, protected, public :: photoi_per_steps = 5
54
55 !> Update photoemission every N time step
56 integer, protected, public :: photoe_per_steps = 10
57
58 !> Optional variable (when using photoionization)
59 integer, public, protected :: i_photo = -1 ! Photoionization rate
60
61 public :: photoi_initialize
62 public :: photoi_set_src
63 ! public :: photoe_set_src
64
65contains
66
67 !> Initialize photoionization parameters
68 subroutine photoi_initialize(tree, cfg)
69 use m_config
70 type(af_t), intent(inout) :: tree
71 type(cfg_t), intent(inout) :: cfg !< The configuration for the simulation
72
73 !> [photoi_general_parameters]
74 call cfg_add_get(cfg, "photoi%enabled", photoi_enabled, &
75 "Whether photoionization is enabled")
76 call cfg_add_get(cfg, "photoi%per_steps", photoi_per_steps, &
77 "Update photoionization every N time steps")
78 call cfg_add_get(cfg, "photoi%method", photoi_method, &
79 "Which photoionization method to use (helmholtz, montecarlo)")
80 call cfg_add_get(cfg, "photoi%eta", photoi_eta, &
81 "Photoionization efficiency factor, typically around 0.05-0.1")
82 call cfg_add_get(cfg, "photoi%quenching_pressure", photoi_quenching_pressure, &
83 "Photoionization quenching pressure for dry air (bar)")
84 call cfg_add_get(cfg, "photoi%quenching_pressure_H2O_Aints", &
85 photoi_quenching_pressure_h2o_aints, &
86 "Photoionization quenching pressure for H2O in Aints model (bar)")
87 call cfg_add_get(cfg, "photoi%source_type", photoi_source_type, &
88 "Model (Zheleznyak, Naidis_humid, Aints_humid, from_species)")
89 call cfg_add_get(cfg, "photoi%excited_species", photoi_excited_species, &
90 "Which excited species to use when photoi%source_type = from_species")
91 call cfg_add_get(cfg, "photoi%species", photoi_species, &
92 "Which species is ionized by photoionization")
93 !> [photoi_general_parameters]
94
95 call cfg_add_get(cfg, "photoi%photoemission_time", photoi_photoemission_time, &
96 "Photoemission time delay in case photoi_source_type is 'from_species'")
97 call cfg_add_get(cfg, "photoe%enabled", photoe_enabled, &
98 "Whether photoemission is enabled")
99 call cfg_add_get(cfg, "photoe%per_steps", photoe_per_steps, &
100 "Update photoemission every N time step")
101
102 if (photoi_enabled) then
103 if (photoi_eta <= 0.0_dp) error stop "photoi%eta <= 0.0"
104 if (photoi_eta > 1.0_dp) error stop "photoi%eta > 1.0"
105 if (photoi_quenching_pressure <= 0.0_dp) &
106 error stop "photoi%quenching_pressure <= 0.0"
107
108 photoi_species_index = species_index(photoi_species)
109 if (photoi_species_index == -1) then
110 print *, "photoi%species not found (", trim(photoi_species), ")"
111 error stop "photoi%species not present"
112 end if
113
114 call af_add_cc_variable(tree, "photo", ix=i_photo)
115 call af_set_cc_methods(tree, i_photo, photoi_helmh_bc, af_gc_interp)
116
117 select case (photoi_source_type)
118 case ('Zheleznyak')
119 if (photoi_excited_species /= undefined_str) &
120 error stop "Cannot use photoi%excited_species with Zheleznyak"
121 case ("Naidis_humid")
122 if (photoi_method /= "montecarlo") &
123 error stop "Naidis_humid is not implemented for helmholtz"
124 case ("Aints_humid")
125 if (photoi_method /= "montecarlo") &
126 error stop "Aints_humid is not implemented for helmholtz"
127 case ('from_species')
128 if (photoi_excited_species == undefined_str) &
129 error stop "Please define photoi%excited_species"
130
131 i_excited_species = &
132 af_find_cc_variable(tree, trim(photoi_excited_species))
133 case default
134 error stop "Unknown value for photoi%source_type"
135 end select
136 end if
137
138 select case (photoi_method)
139 case ("helmholtz")
140 call photoi_helmh_initialize(tree, cfg, photoi_enabled, photoi_eta)
141 call phmc_initialize(cfg, .false., photoi_source_type)
142 case ("montecarlo")
143 call photoi_helmh_initialize(tree, cfg, .false., photoi_eta)
144 call phmc_initialize(cfg, photoi_enabled, photoi_source_type)
145 case default
146 print *, "Unknown photoi_method: ", trim(photoi_method)
147 error stop
148 end select
149
150 end subroutine photoi_initialize
151
152 !> Sets the photoionization
153 subroutine photoi_set_src(tree, dt)
154 use m_gas
155 type(af_t), intent(inout) :: tree
156 integer :: ix
157 real(dp), intent(in), optional :: dt
158 real(dp) :: quench_fac, decay_fraction
159 real(dp) :: eff_decay_time, decay_rate
160 real(dp) :: p_h2o
161
162 if (photoi_source_type == 'Aints_humid') then
163 ix = gas_index("H2O")
164 if (ix == -1) then
165 p_h2o = 0.0_dp
166 else
167 p_h2o = gas_fractions(ix) * gas_pressure
168 end if
169
170 ! Use custom quenching factor as discussed in doi:10.1002/ppap.200800031
171 quench_fac = 1/(1 + (gas_pressure - p_h2o)/photoi_quenching_pressure + &
172 p_h2o / photoi_quenching_pressure_h2o_aints)
173 else
174 ! Compute standard quenching factor for dry air
175 quench_fac = photoi_quenching_pressure / &
176 (gas_pressure + photoi_quenching_pressure)
177 end if
178
179 ! Set photon production rate per cell, which is proportional to the
180 ! ionization rate.
181 select case (photoi_source_type)
182 case ('Zheleznyak', 'Naidis_humid', 'Aints_humid')
183 call af_loop_box_arg(tree, photoionization_rate_from_alpha, &
184 [photoi_eta * quench_fac], .true.)
185 case ('from_species')
186 ! effective decay time when we have quenching
187 eff_decay_time = photoi_photoemission_time
188 decay_fraction = 1 - exp(-dt / eff_decay_time)
189 if (dt > 1e-6_dp * eff_decay_time) then
190 decay_rate = decay_fraction / dt
191 else
192 decay_rate = 1.0 / eff_decay_time
193 end if
194
195 call af_loop_box_arg(tree, photoionization_rate_from_species, &
196 [quench_fac * decay_rate, 1-decay_fraction], .true.)
197 end select
198
199 select case (photoi_method)
200 case ("helmholtz")
201 ! Use Helmholtz approximation
202 call photoi_helmh_compute(tree, i_photo)
203 case ("montecarlo")
204 if (phmc_physical_photons) then
205 call phmc_set_src(tree, st_rng, i_rhs, &
207 else
208 call phmc_set_src(tree, st_rng, i_rhs, &
210 end if
211 end select
212
213 end subroutine photoi_set_src
214
215 ! !> Sets the photoemission
216 ! subroutine photoe_set_src(tree, dt)
217 ! use m_units_constants
218 ! use m_gas
219
220 ! type(af_t), intent(inout) :: tree
221 ! real(dp), intent(in), optional :: dt
222 ! real(dp), parameter :: p_quench = 40.0e-3_dp
223 ! real(dp) :: quench_fac, decay_fraction, decay_rate
224
225 ! ! Compute quench factor, because some excited species will be quenched by
226 ! ! collisions, preventing the emission of a UV photon
227 ! quench_fac = p_quench / (gas_pressure + p_quench)
228
229 ! ! Set photon production rate per cell, which is proportional to the
230 ! ! ionization rate.
231 ! select case (photoi_source_type)
232 ! case ('Zheleznyak')
233 ! call af_loop_box_arg(tree, photoionization_rate_from_alpha, &
234 ! [photoi_eta * quench_fac], .true.)
235 ! case ('from_species')
236 ! decay_fraction = 1 - exp(-dt / eff_decay_time)
237
238 ! if (dt > 1e-6_dp * photoi_decay_time) then
239 ! decay_rate = decay_fraction / dt
240 ! else
241 ! decay_rate = 1 / photoi_decay_time
242 ! end if
243
244 ! call af_loop_box_arg(tree, photoionization_rate_from_species, &
245 ! [photoi_eta * quench_fac * decay_rate, 1-decay_fraction], .true.)
246 ! end select
247
248 ! if (phmc_physical_photons) then
249 ! call phe_mc_set_src(tree, ST_rng, i_rhs, &
250 ! i_photo, ST_cylindrical, dt)
251 ! else
252 ! call phe_mc_set_src(tree, ST_rng, i_rhs, &
253 ! i_photo, ST_cylindrical)
254 ! end if
255
256 ! end subroutine photoe_set_src
257
258 !> Sets the photoionization_rate
259 subroutine photoionization_rate_from_alpha(box, coeff)
260 use m_streamer
261 use m_lookup_table
263 use m_gas
264 type(box_t), intent(inout) :: box
265 real(dp), intent(in) :: coeff(:)
266 integer :: ijk, nc
267 real(dp) :: fld, td, alpha, mobility, tmp, gas_dens
268 type(lt_loc_t) :: loc
269
270 nc = box%n_cell
271
272 do kji_do(1,nc)
273 fld = box%cc(ijk, i_electric_fld)
274
275 if (gas_constant_density) then
276 gas_dens = gas_number_density
277 else
278 gas_dens = box%cc(ijk, i_gas_dens)
279 end if
280
281 td = fld * si_to_townsend / gas_dens
282 loc = lt_get_loc(td_tbl, td)
283 ! No normalization required: (alpha/N) * (mu/N)
284 alpha = lt_get_col_at_loc(td_tbl, td_alpha, loc)
285 mobility = lt_get_col_at_loc(td_tbl, td_mobility, loc)
286
287 tmp = fld * mobility * alpha * box%cc(ijk, i_electron) * coeff(1)
288 if (tmp < 0) tmp = 0
289 box%cc(ijk, i_rhs) = tmp
290 end do; close_do
291 end subroutine photoionization_rate_from_alpha
292
293 !> Sets the photoionization_rate
294 subroutine photoionization_rate_from_species(box, coeff)
295 use m_streamer
296 use m_lookup_table
298 use m_gas
299 type(box_t), intent(inout) :: box
300 real(dp), intent(in) :: coeff(:)
301 integer :: nc
302 real(dp) :: source_factor, decay_factor
303
304 nc = box%n_cell
305 source_factor = coeff(1)
306 decay_factor = coeff(2)
307
308 box%cc(dtimes(1:nc), i_rhs) = source_factor * &
309 box%cc(dtimes(1:nc), i_excited_species)
310 box%cc(dtimes(1:nc), i_excited_species) = decay_factor * &
311 box%cc(dtimes(1:nc), i_excited_species)
312 end subroutine photoionization_rate_from_species
313
314end module m_photoi
Module for handling chemical reactions.
elemental integer function, public species_index(name)
Find index of a species, return -1 if not found.
Module that stores parameters related to the gas.
Definition m_gas.f90:2
elemental integer function, public gas_index(name)
Find index of a gas component, return -1 if not found.
Definition m_gas.f90:285
real(dp), dimension(:), allocatable, public, protected gas_fractions
Definition m_gas.f90:24
integer, public, protected i_gas_dens
Definition m_gas.f90:45
real(dp), parameter, public si_to_townsend
Definition m_gas.f90:39
real(dp), public, protected gas_pressure
Definition m_gas.f90:18
logical, public, protected gas_constant_density
Whether the gas has a constant density.
Definition m_gas.f90:12
real(dp), public, protected gas_number_density
Definition m_gas.f90:33
Module for photoionization with the Helmholtz approximation.
subroutine, public photoi_helmh_compute(tree, i_photo)
subroutine, public photoi_helmh_bc(box, nb, iv, coords, bc_val, bc_type)
subroutine, public photoi_helmh_initialize(tree, cfg, is_used, eta)
Initialize options for Helmholtz photoionization.
Module that provides routines for Monte Carlo photoionization.
subroutine, public phmc_set_src(tree, rng, i_src, i_photo, use_cyl, dt)
Set the source term due to photoionization. At most phmc_num_photons discrete photons are produced.
subroutine, public phmc_initialize(cfg, is_used, source_type)
Initialize photoionization parameters.
logical, public, protected phmc_physical_photons
Whether physical photons are used.
Top-module for photoionization, which can make use of different methods.
Definition m_photoi.f90:2
integer, public, protected photoi_species_index
Index of species ionized by photoionization (in list of chemical species)
Definition m_photoi.f90:31
subroutine, public photoi_set_src(tree, dt)
Sets the photoionization.
Definition m_photoi.f90:154
integer, public, protected photoe_per_steps
Update photoemission every N time step.
Definition m_photoi.f90:56
logical, public, protected photoe_enabled
Whether photoemission is enabled.
Definition m_photoi.f90:19
logical, public, protected photoi_enabled
Whether photoionization is enabled.
Definition m_photoi.f90:16
integer, public, protected i_photo
Optional variable (when using photoionization)
Definition m_photoi.f90:59
subroutine, public photoi_initialize(tree, cfg)
Initialize photoionization parameters.
Definition m_photoi.f90:69
integer, public, protected photoi_per_steps
Update photoionization every N time step.
Definition m_photoi.f90:53
This module contains several pre-defined variables like:
Definition m_streamer.f90:6
logical, public, protected st_cylindrical
Whether cylindrical coordinates are used.
integer, public, protected i_electron
Index of electron density.
integer, public, protected i_rhs
Index of source term Poisson.
integer, public, protected i_electric_fld
Index of electric field norm.
type(rng_t), public st_rng
Random number generator.
Module that provides routines for reading in arbritrary transport data.
type(lt_t), public, protected td_tbl
integer, parameter, public td_alpha
Ionization coefficient.
integer, parameter, public td_mobility
Electron mobility.
Module with basic types.
Definition m_types.f90:2
character(len= *), parameter undefined_str
Undefined string.
Definition m_types.f90:10
Module that contains physical and numerical constants.
real(dp), parameter uc_torr_to_bar