afivo-streamer 1.1
1D/2D/3D streamer simulations with AMR
Loading...
Searching...
No Matches
m_init_cond.f90
Go to the documentation of this file.
1!> Module to help setting up initial conditions
3#include "../afivo/src/cpp_macros.h"
4 use m_streamer
5 use m_af_all
7 use m_types
8
9 implicit none
10 private
11
12 ! Type to store initial conditions in
13 type initcnd_t
14 real(dp) :: background_density
15 real(dp) :: stochastic_density
16 integer :: n_cond
17 real(dp), allocatable :: seed_r0(:, :)
18 real(dp), allocatable :: seed_r1(:, :)
19 real(dp), allocatable :: seed_density(:)
20 real(dp), allocatable :: seed_density2(:)
21 integer, allocatable :: seed_charge_type(:)
22 real(dp), allocatable :: seed_width(:)
23 character(string_len), allocatable :: seed_falloff(:)
24 integer, allocatable :: seed1_species(:) !< Custom seed 1 species
25 integer, allocatable :: background_species(:) !< Custom background species
26 end type initcnd_t
27
28 ! This will contain the initial conditions
29 type(initcnd_t), protected, public :: init_conds
30
31 public :: init_cond_initialize
32 public :: init_cond_set_box
34
35contains
36
37 !> Set the initial conditions from the configuration
38 subroutine init_cond_initialize(tree, cfg)
39 use m_config
40 type(af_t), intent(in) :: tree !< Tree
41 type(cfg_t), intent(inout) :: cfg !< Settings
42
43 integer :: n, n_cond, varsize, empty_int(0)
44 real(dp) :: empty_real(0)
45 real(dp), allocatable :: tmp_vec(:)
46 character(len=name_len) :: empty_string(0)
47 character(len=name_len), allocatable :: seed_species(:)
48 character(len=name_len), allocatable :: background_species(:)
49 type(initcnd_t) :: ic
50
51 call cfg_add(cfg, "background_density", 0.0_dp, &
52 "The background ion and electron density (1/m3)")
53 call cfg_add(cfg, "stochastic_density", 0.0_dp, &
54 "Stochastic background density (1/m3)")
55 call cfg_add(cfg, "seed_density", empty_real, &
56 "Initial density of the seed (1/m3)", .true.)
57 call cfg_add(cfg, "seed_rel_r0", empty_real, &
58 "The relative start position of the initial seed", .true.)
59 call cfg_add(cfg, "seed_rel_r1", empty_real, &
60 "The relative end position of the initial seed", .true.)
61 call cfg_add(cfg, "seed_charge_type", empty_int, &
62 "Type of seed: neutral (0), ions (1) or electrons (-1)", .true.)
63 call cfg_add(cfg, "seed_width", empty_real, &
64 "Seed width (m)", .true.)
65 call cfg_add(cfg, "seed_falloff", empty_string, &
66 "Fall-off type for seed (sigmoid, gaussian, smoothstep, step, laser)", .true.)
67 call cfg_add(cfg, "seed1_species", empty_string, &
68 "Names of custom species for the first seed", .true.)
69 call cfg_add(cfg, "background_species", empty_string, &
70 "Names of custom species for the background density", .true.)
71
72 call cfg_get_size(cfg, "seed_density", n_cond)
73 ic%n_cond = n_cond
74
75 call cfg_get_size(cfg, "seed_rel_r0", varsize)
76 if (varsize /= ndim * n_cond) &
77 stop "seed_rel_r0 variable has incompatible size"
78
79 call cfg_get_size(cfg, "seed_rel_r1", varsize)
80 if (varsize /= ndim * n_cond) &
81 stop "seed_rel_r1 variable has incompatible size"
82
83 call cfg_get_size(cfg, "seed_charge_type", varsize)
84 if (varsize /= n_cond) &
85 stop "seed_charge_type variable has incompatible size"
86
87 call cfg_get_size(cfg, "seed_width", varsize)
88 if (varsize /= n_cond) &
89 stop "seed_width variable has incompatible size"
90
91 allocate(ic%seed_density(n_cond))
92 allocate(ic%seed_density2(n_cond))
93 allocate(ic%seed_charge_type(n_cond))
94 allocate(ic%seed_r0(ndim, n_cond))
95 allocate(ic%seed_r1(ndim, n_cond))
96 allocate(ic%seed_width(n_cond))
97 allocate(ic%seed_falloff(n_cond))
98
99 allocate(tmp_vec(ndim * n_cond))
100 call cfg_get(cfg, "seed_rel_r0", tmp_vec)
101 ic%seed_r0 = reshape(tmp_vec, [ndim, n_cond])
102 call cfg_get(cfg, "seed_rel_r1", tmp_vec)
103 ic%seed_r1 = reshape(tmp_vec, [ndim, n_cond])
104
105 do n = 1, n_cond
106 ic%seed_r0(:, n) = ic%seed_r0(:, n) * st_domain_len + st_domain_origin
107 ic%seed_r1(:, n) = ic%seed_r1(:, n) * st_domain_len + st_domain_origin
108 end do
109
110 call cfg_get(cfg, "background_density", ic%background_density)
111 call cfg_get(cfg, "stochastic_density", ic%stochastic_density)
112 call cfg_get(cfg, "seed_density", ic%seed_density)
113 call cfg_get(cfg, "seed_charge_type", ic%seed_charge_type)
114 call cfg_get(cfg, "seed_width", ic%seed_width)
115 call cfg_get(cfg, "seed_falloff", ic%seed_falloff)
116
117 ! Keep density at endpoint the same by default
118 call cfg_add(cfg, "seed_density2", ic%seed_density, &
119 "Initial density of the seed at other endpoint (1/m3)")
120 call cfg_get(cfg, "seed_density2", ic%seed_density2)
121
122 call cfg_get_size(cfg, "seed1_species", varsize)
123 if (varsize > 0) then
124 allocate(seed_species(varsize))
125 allocate(ic%seed1_species(varsize))
126 call cfg_get(cfg, "seed1_species", seed_species)
127 do n = 1, varsize
128 ic%seed1_species(n) = af_find_cc_variable(tree, seed_species(n))
129 end do
130 end if
131
132 call cfg_get_size(cfg, "background_species", varsize)
133 if (varsize > 0) then
134 allocate(background_species(varsize))
135 allocate(ic%background_species(varsize))
136 call cfg_get(cfg, "background_species", background_species)
137 do n = 1, varsize
138 ic%background_species(n) = af_find_cc_variable(tree, background_species(n))
139 end do
140 end if
141
142 init_conds = ic
143
144 end subroutine init_cond_initialize
145
146 !> Add a stochastic background density to the electrons and ions. Note: this
147 !> routine temporarily uses variable i_rhs
149 use m_af_ghostcell, only: af_bc_neumann_zero
150 use m_af_prolong
151 type(af_t), intent(inout) :: tree
152 integer :: my_lvl, lvl, i, id
153
154 if (init_conds%stochastic_density <= 0.0_dp) return
155
156 ! Determine at which level to create the background density. This is the
157 ! highest level that is fully refined
158 do my_lvl = 1, tree%highest_lvl
159 if (size(tree%lvls(my_lvl)%leaves) > 0) exit
160 end do
161
162 ! Use i_rhs to store the stochastic density at this level
163 call af_tree_clear_cc(tree, i_rhs)
164 !$omp do private(id)
165 do i = 1, size(tree%lvls(my_lvl)%ids)
166 id = tree%lvls(my_lvl)%ids(i)
167 call set_stochastic_density(tree%boxes(id))
168 end do
169 !$omp end do
170
171 ! Prolong to finer levels. The coarser (hidden) levels are set at the end.
172 do lvl = my_lvl, tree%highest_lvl-1
173 do i = 1, size(tree%lvls(lvl)%parents)
174 id = tree%lvls(lvl)%parents(i)
175 call af_gc_box(tree, id, [i_rhs])
176 end do
177
178 do i = 1, size(tree%lvls(lvl)%parents)
179 id = tree%lvls(lvl)%parents(i)
180 call af_prolong_linear_from(tree%boxes, id, i_rhs, add=.true.)
181 end do
182
183 end do
184
185 ! Finally, add the stochastic density to the electrons and ions
186 do lvl = my_lvl, tree%highest_lvl
187 do i = 1, size(tree%lvls(lvl)%ids)
188 id = tree%lvls(lvl)%ids(i)
189 call af_box_add_cc(tree%boxes(id), i_rhs, i_electron)
190 call af_box_add_cc(tree%boxes(id), i_rhs, i_1pos_ion)
191 end do
192 end do
193
194 ! Restrict and fill ghost cells
195 call af_restrict_tree(tree, [i_electron, i_1pos_ion])
196 call af_gc_tree(tree, [i_electron, i_1pos_ion])
197
198 end subroutine init_cond_stochastic_density
199
200 subroutine set_stochastic_density(box)
201 use omp_lib
202 use m_streamer, only: st_prng
203 type(box_t), intent(inout) :: box
204 integer :: proc_id, ijk
205 real(dp) :: density
206
207 proc_id = 1+omp_get_thread_num()
208
209 do kji_do(1,box%n_cell)
210 density = st_prng%rngs(proc_id)%unif_01() * &
211 init_conds%stochastic_density
212 box%cc(ijk, i_rhs) = density
213 end do; close_do
214 end subroutine set_stochastic_density
215
216 !> Sets the initial condition
217 subroutine init_cond_set_box(box)
218 use m_geometry
219 use m_gas
221 use m_streamer
222 type(box_t), intent(inout) :: box
223 integer :: ijk, n, nc
224 real(dp) :: rr(ndim)
225 real(dp) :: density
226
227 nc = box%n_cell
228
229 if (allocated(init_conds%background_species)) then
230 box%cc(dtimes(:), init_conds%background_species) = &
231 init_conds%background_density
232 else
233 box%cc(dtimes(:), i_electron) = init_conds%background_density
234 box%cc(dtimes(:), i_1pos_ion) = init_conds%background_density
235 end if
236
237 do kji_do(0,nc+1)
238 rr = af_r_cc(box, [ijk])
239
240 if (gas_dynamics) then
241 if (associated(user_gas_density)) then
242 box%cc(ijk, i_gas_dens) = user_gas_density(box, ijk)
243 else
244 ! Start with a constant gas number density
245 box%cc(ijk, i_gas_dens) = gas_number_density
246 end if
247
248 ! Initialize Euler variables: density, momentum, energy
249 box%cc(ijk, gas_vars(i_rho)) = box%cc(ijk, i_gas_dens) * &
251 box%cc(ijk, gas_vars(i_mom)) = 0.0_dp
252 box%cc(ijk, gas_vars(i_e)) = &
253 gas_pressure * 1e5_dp / (gas_euler_gamma - 1) + &
254 0.5_dp * sum(box%cc(ijk, gas_vars(i_mom))**2) / &
255 box%cc(ijk, gas_vars(i_rho))
256 end if
257
258 do n = 1, init_conds%n_cond
259 density = gm_density_line(rr, init_conds%seed_r0(:, n), &
260 init_conds%seed_r1(:, n), &
261 init_conds%seed_density(n), init_conds%seed_density2(n), ndim, &
262 init_conds%seed_width(n), &
263 init_conds%seed_falloff(n))
264
265 if (n == 1 .and. allocated(init_conds%seed1_species)) then
266 box%cc(ijk, init_conds%seed1_species) = &
267 box%cc(ijk, init_conds%seed1_species) + density
268 else
269 ! Add electrons and/or ions depending on the seed charge type
270 select case (init_conds%seed_charge_type(n))
271 case (-1)
272 box%cc(ijk, i_electron) = box%cc(ijk, i_electron) + density
273 case (0)
274 box%cc(ijk, i_1pos_ion) = box%cc(ijk, i_1pos_ion) + density
275 box%cc(ijk, i_electron) = box%cc(ijk, i_electron) + density
276 case (1)
277 box%cc(ijk, i_1pos_ion) = box%cc(ijk, i_1pos_ion) + density
278 case default
279 error stop "Invalid seed_charge_type"
280 end select
281 end if
282 end do
283
284 if (st_use_electrode) then
285 if (box%cc(ijk, i_lsf) <= 0) then
286 box%cc(ijk, all_densities) = 0.0_dp
287 end if
288 end if
289 end do; close_do
290
291 end subroutine init_cond_set_box
292
293end module m_init_cond
Module for handling chemical reactions.
Module that stores parameters related to the gas.
Definition m_gas.f90:2
real(dp), public, protected gas_molecular_weight
Definition m_gas.f90:48
real(dp), public, protected gas_euler_gamma
Definition m_gas.f90:63
logical, public, protected gas_dynamics
Whether the gas dynamics are simulated.
Definition m_gas.f90:15
integer, public, protected i_gas_dens
Definition m_gas.f90:45
integer, dimension(ndim), parameter, public i_mom
Definition m_gas.f90:85
real(dp), public, protected gas_pressure
Definition m_gas.f90:18
integer, dimension(n_vars_euler), public, protected gas_vars
Definition m_gas.f90:69
integer, parameter, public i_e
Definition m_gas.f90:91
integer, parameter, public i_rho
Definition m_gas.f90:83
real(dp), public, protected gas_number_density
Definition m_gas.f90:33
Module that provides routines for geometric operations and calculations. Methods and types have a pre...
Definition m_geometry.f90:3
real(dp) function, public gm_density_line(r, r0, r1, n_0, n_1, n_dim, width, falloff_t)
Module to help setting up initial conditions.
subroutine, public init_cond_stochastic_density(tree)
Add a stochastic background density to the electrons and ions. Note: this routine temporarily uses va...
type(initcnd_t), public, protected init_conds
subroutine, public init_cond_set_box(box)
Sets the initial condition.
subroutine, public init_cond_initialize(tree, cfg)
Set the initial conditions from the configuration.
This module contains several pre-defined variables like:
Definition m_streamer.f90:6
logical, public, protected st_use_electrode
Whether to include an electrode.
integer, public, protected i_lsf
Index can be set to include an electrode.
integer, public, protected i_electron
Index of electron density.
integer, public, protected i_rhs
Index of source term Poisson.
integer, public, protected i_1pos_ion
Index of first positive ion species.
real(dp), dimension(ndim), public, protected st_domain_len
Domain length per dimension.
real(dp), dimension(ndim), public, protected st_domain_origin
Origin of domain.
integer, dimension(:), allocatable, public, protected all_densities
Index of all densities that evolve in time.
type(prng_t), public st_prng
Parallel random number generator.
Module with basic types.
Definition m_types.f90:2
This module contains all the methods that users can customize.
procedure(gas_dens_func), pointer user_gas_density
To set a user-defined gas number density.