afivo-streamer 1.1
1D/2D/3D streamer simulations with AMR
Loading...
Searching...
No Matches
m_transport_data.f90
Go to the documentation of this file.
1!> Module that provides routines for reading in arbritrary transport data
3 use m_lookup_table
4 use m_types
6 use m_af_types
7
8 implicit none
9 private
10
11 ! ** Indices of transport data **
12 integer, parameter, public :: td_mobility = 1 !< Electron mobility
13 integer, parameter, public :: td_diffusion = 2 !< Electron diffusion constant
14 integer, parameter, public :: td_alpha = 3 !< Ionization coefficient
15 integer, parameter, public :: td_eta = 4 !< Attachment coefficient
16
17 !> Electron energy in eV (used with chemistry)
18 integer, protected, public :: td_energy_ev = -1
19
20 ! Table with transport data vs electric field
21 type(lt_t), public, protected :: td_tbl
22
23 ! Table with transport data vs electron energy
24 type(lt_t), public, protected :: td_ee_tbl
25
26 !> Electron mobility as a function of energy
27 integer, protected, public :: td_ee_mobility = 1
28
29 !> Electron diffusion coefficient as a function of energy
30 integer, protected, public :: td_ee_diffusion = 2
31
32 !> Electron energy loss
33 integer, protected, public :: td_ee_loss = 3
34
35 !> Field as a function of energy
36 integer, protected, public :: td_ee_field = 4
37
38 !> Whether old style transport data is used (alpha, eta, mu, D vs V/m)
39 logical, public, protected :: td_old_style = .false.
40
41 !> Maximal energy (eV) in input data (automatically updated)
42 real(dp), public, protected :: td_max_ev = 20.0_dp
43
44 ! @todo move this to separate ion module
45 type ion_transport_t
46 integer :: n_mobile_ions ! Number of mobile ions
47 real(dp), allocatable :: mobilities(:) ! Mobility of the ions
48 character(len=af_nlen), allocatable :: names(:) ! Names of the ions
49 end type ion_transport_t
50
51 type(ion_transport_t), public :: transport_data_ions
52
53 !> Secondary electron emission yield for positive ions
54 real(dp), public, protected :: ion_se_yield = 0.0_dp
55
57
58contains
59
60 !> Initialize the transport coefficients
62 use m_config
63 use m_table_data
64 use m_gas
66 use m_model
67 type(cfg_t), intent(inout) :: cfg
68 character(len=string_len) :: td_file = undefined_str
69 real(dp), allocatable :: xx(:), yy(:)
70 real(dp), allocatable :: energy_ev(:), field_td(:)
71 real(dp) :: dummy_real(0), max_td, max_ev, rel_err
72 character(len=10) :: dummy_string(0)
73 integer :: n
74
75 call cfg_add_get(cfg, "input_data%file", td_file, &
76 "Input file with transport (and reaction) data")
77 if (td_file == undefined_str) error stop "input_data%file undefined"
78
79 call cfg_add_get(cfg, "input_data%old_style", td_old_style, &
80 "Use old style transport data (alpha, eta, mu, D vs V/m)")
81
82 print *, 'Approximate relative lookup table interpolation errors:'
83
84 ! Fill table with data
85 if (td_old_style) then
86 if (.not. gas_constant_density) &
87 error stop "Old style transport used with varying gas density"
89 error stop "Old style transport used with energy equation"
90
91 call table_from_file(td_file, "efield[V/m]_vs_mu[m2/Vs]", xx, yy)
93 yy = yy * gas_number_density
94
95 ! Create a lookup table for the model coefficients
96 if (table_max_townsend < 0) then
97 max_td = xx(size(xx))
98 else
99 max_td = table_max_townsend
100 end if
101
102 td_tbl = lt_create(table_min_townsend, max_td, table_size, &
104
105 call table_set_column(td_tbl, td_mobility, xx, yy, rel_err)
106 write(*, '(A30,F12.4)') 'Mobility:', rel_err
107
108 call table_from_file(td_file, "efield[V/m]_vs_dif[m2/s]", xx, yy)
110 yy = yy * gas_number_density
111 call table_set_column(td_tbl, td_diffusion, xx, yy, rel_err)
112 write(*, '(A30,F12.4)') 'Diffusion coefficient:', rel_err
113
114 call table_from_file(td_file, "efield[V/m]_vs_alpha[1/m]", &
115 xx, yy)
117 yy = yy / gas_number_density
118 call table_set_column(td_tbl, td_alpha, xx, yy, rel_err)
119 write(*, '(A30,F12.4)') 'Ionization coefficient:', rel_err
120
121 call table_from_file(td_file, "efield[V/m]_vs_eta[1/m]", &
122 xx, yy)
124 yy = yy / gas_number_density
125 call table_set_column(td_tbl, td_eta, xx, yy, rel_err)
126 write(*, '(A30,F12.4)') 'Attachment coefficient:', rel_err
127 else
128 call table_from_file(td_file, "Mobility *N (1/m/V/s)", xx, yy)
129
130 ! Create a lookup table for the model coefficients
131 if (table_max_townsend < 0) then
132 max_td = xx(size(xx))
133 else
134 max_td = table_max_townsend
135 end if
136
137 td_tbl = lt_create(table_min_townsend, max_td, &
139
140 call table_set_column(td_tbl, td_mobility, xx, yy, rel_err)
141 write(*, '(A30,F12.4)') 'Mobility:', rel_err
142
143 call table_from_file(td_file, "Diffusion coefficient *N (1/m/s)", &
144 xx, yy)
145 call table_set_column(td_tbl, td_diffusion, xx, yy, rel_err)
146 write(*, '(A30,F12.4)') 'Diffusion coefficient:', rel_err
147
148 call table_from_file(td_file, "Townsend ioniz. coef. alpha/N (m2)", &
149 xx, yy)
150 call table_set_column(td_tbl, td_alpha, xx, yy, rel_err)
151 write(*, '(A30,F12.4)') 'Ionization coefficient:', rel_err
152
153 call table_from_file(td_file, "Townsend attach. coef. eta/N (m2)", &
154 xx, yy)
155 call table_set_column(td_tbl, td_eta, xx, yy, rel_err)
156 write(*, '(A30,F12.4)') 'Attachment coefficient:', rel_err
157
158 td_energy_ev = 5
159 call table_from_file(td_file, "Mean energy (eV)", &
160 xx, yy)
162 td_max_ev = yy(size(yy))
163 end if
164
166 call table_from_file(td_file, "Mean energy (eV)", field_td, energy_ev)
167 max_ev = energy_ev(size(energy_ev))
168 td_ee_tbl = lt_create(0.0_dp, max_ev, table_size, 4, table_xspacing)
169
170 call table_from_file(td_file, "Mobility *N (1/m/V/s)", xx, yy)
171 if (.not. same_data(xx, field_td)) &
172 error stop "Same reduced field table required in all input data"
173
174 ! Mobility as a function of energy
175 call table_set_column(td_ee_tbl, td_ee_mobility, energy_ev, yy)
176
177 ! Energy loss is mu E^2 as a function of energy. Prepend a zero, since at
178 ! zero energy there can be no energy loss.
179 yy = yy * xx**2 * townsend_to_si**2 * gas_number_density
181 [0.0_dp, energy_ev], [0.0_dp, yy])
182
183 call table_from_file(td_file, "Diffusion coefficient *N (1/m/s)", xx, yy)
184 if (.not. same_data(xx, field_td)) &
185 error stop "Same reduced field table required in all input data"
186
187 ! Also prepend a zero, since at zero energy there can be no diffusion
189 [0.0_dp, energy_ev], [0.0_dp, yy])
190
192 [0.0_dp, energy_ev], [0.0_dp, xx])
193 end if
194
195 call cfg_add(cfg, "input_data%mobile_ions", dummy_string, &
196 "List of ions that are considered mobile", .true.)
197 call cfg_add(cfg, "input_data%ion_mobilities", dummy_real, &
198 "List of ion mobilities (m^2/Vs) at 1 bar, 300 K", .true.)
199
200 call cfg_get_size(cfg, "input_data%mobile_ions", n)
201
202 transport_data_ions%n_mobile_ions = n
203 allocate(transport_data_ions%names(n))
204 allocate(transport_data_ions%mobilities(n))
205
206 call cfg_get(cfg, "input_data%mobile_ions", transport_data_ions%names)
207 call cfg_get(cfg, "input_data%ion_mobilities", &
208 transport_data_ions%mobilities)
209
210 if (any(transport_data_ions%mobilities < 0)) &
211 error stop "Ion mobilities should be given as positive numbers"
212
213 ! Scale ion mobilities with gas number density at 300 K and 1 bar
214 transport_data_ions%mobilities = transport_data_ions%mobilities * &
215 (1e5_dp / (uc_boltzmann_const * 300))
216
217 call cfg_add_get(cfg, "input_data%ion_se_yield", ion_se_yield, &
218 "Secondary electron emission yield for positive ions")
219
220 end subroutine transport_data_initialize
221
222 !> Check whether data is the same
223 pure logical function same_data(x1, x2)
224 real(dp), intent(in) :: x1(:), x2(:)
225
226 if (size(x1) == size(x2)) then
227 same_data = minval(abs(x1-x2)) < tiny_real
228 else
229 same_data = .false.
230 end if
231 end function same_data
232
233end module m_transport_data
Module that stores parameters related to the gas.
Definition m_gas.f90:2
real(dp), parameter, public townsend_to_si
Definition m_gas.f90:42
real(dp), parameter, public si_to_townsend
Definition m_gas.f90:39
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 to set the type of model.
Definition m_model.f90:2
logical, public, protected model_has_energy_equation
Whether the model has an energy equation.
Definition m_model.f90:20
Module for cubic spline interpolation.
Module with settings and routines for tabulated data.
subroutine, public table_set_column(tbl, i_col, x, y, max_err)
Interpolate data and store in lookup table.
real(dp), public, protected table_max_townsend
Maximum field (Td) for lookup tables.
integer, public, protected table_xspacing
X-spacing for lookup table.
integer, public, protected table_size
How large lookup tables should be.
subroutine, public table_from_file(file_name, data_name, x_data, y_data)
Routine to read in tabulated data from a file.
real(dp), public, protected table_min_townsend
Minimum field (Td) for lookup tables.
Module that provides routines for reading in arbritrary transport data.
real(dp), public, protected td_max_ev
Maximal energy (eV) in input data (automatically updated)
subroutine, public transport_data_initialize(cfg)
Initialize the transport coefficients.
real(dp), public, protected ion_se_yield
Secondary electron emission yield for positive ions.
type(lt_t), public, protected td_tbl
integer, parameter, public td_diffusion
Electron diffusion constant.
integer, parameter, public td_eta
Attachment coefficient.
integer, public, protected td_ee_field
Field as a function of energy.
integer, public, protected td_ee_diffusion
Electron diffusion coefficient as a function of energy.
integer, public, protected td_energy_ev
Electron energy in eV (used with chemistry)
integer, public, protected td_ee_mobility
Electron mobility as a function of energy.
integer, parameter, public td_alpha
Ionization coefficient.
logical, public, protected td_old_style
Whether old style transport data is used (alpha, eta, mu, D vs V/m)
integer, parameter, public td_mobility
Electron mobility.
type(lt_t), public, protected td_ee_tbl
integer, public, protected td_ee_loss
Electron energy loss.
type(ion_transport_t), public transport_data_ions
Module with basic types.
Definition m_types.f90:2
character(len= *), parameter undefined_str
Undefined string.
Definition m_types.f90:10
real(dp), parameter tiny_real
Small number.
Definition m_types.f90:19
Module that contains physical and numerical constants.
real(dp), parameter uc_boltzmann_const