afivo-streamer 1.1
1D/2D/3D streamer simulations with AMR
Loading...
Searching...
No Matches
m_dielectric.f90
Go to the documentation of this file.
1!> Module with settings and routines to handle dielectrics
2!>
3!> @todo Make sure species densities are initially zero inside the dielectric
4!> @todo Use special prolongation for multigrid when there are surface charges
6#include "../afivo/src/cpp_macros.h"
7 use m_af_all
8 use m_streamer
9 use m_types
10
11 implicit none
12 private
13
14 ! @todo maybe don't hardcode this?
15 integer, parameter, public :: i_photon_flux = 1
16 integer, parameter, public :: i_surf_dens = 2
17
18 !> To store dielectric surface
19 type(surfaces_t), public :: diel
20
21 ! Output surface related information
22 logical, public, protected :: surface_output = .false.
23
24 ! Maximum travel distance for testing boundary intersection
25 real(dp), protected :: photon_step_length = 1.0e-3_dp
26
27 !> Secondary electron emission coefficient for positive ion impact
28 real(dp), protected :: gamma_se_ion = 0.1_dp
29
30 !> Secondary electron emission coefficient for high energy photons
31 real(dp), protected :: gamma_se_ph_highenergy = 0.1_dp
32
33 !> Secondary electron emission coefficient for low energy photons
34 real(dp), protected :: gamma_se_ph_lowenergy = 0.1_dp
35
36 !> Assume photons are not absorbed for photoemission computation
37 logical :: photons_no_absorption = .false.
38
39 !> Preset surface charge numbers
40 integer, protected :: n_surface_charge
41
42 !> Preset surface charge
43 real(dp), allocatable, protected :: preset_charge(:)
44
45 !> Preset surface charge distribution
46 real(dp), allocatable, protected :: preset_charge_distribution(:)
47
48 public :: dielectric_initialize
53
54contains
55
56 subroutine dielectric_initialize(tree, cfg)
57 use m_config
58 type(af_t), intent(in) :: tree
59 type(cfg_t), intent(inout) :: cfg
60
61 call cfg_add_get(cfg, "dielectric%photon_step_length", &
62 photon_step_length, &
63 "Maximum travel distance for testing boundary intersection")
64 call cfg_add_get(cfg, "dielectric%gamma_se_ph_highenergy", &
65 gamma_se_ph_highenergy, &
66 "Secondary electron emission coefficient for high energy photons")
67 call cfg_add_get(cfg, "dielectric%gamma_se_ph_lowenergy", &
68 gamma_se_ph_lowenergy, &
69 "Secondary electron emission coefficient for low energy photons")
70 call cfg_add_get(cfg, "dielectric%gamma_se_ion", &
71 gamma_se_ion, &
72 "Secondary electron emission coefficient for positive ion impact")
73 call cfg_add_get(cfg, "dielectric%photons_no_absorption", &
74 photons_no_absorption, &
75 "Assume photons are not absorbed for photoemission computation")
76 call cfg_add(cfg, "dielectric%preset_charge", [0.0_dp], &
77 "preset nonuniform surface charge", dynamic_size=.true.)
78 call cfg_add(cfg, "dielectric%preset_charge_distribution", [0.0_dp], &
79 "The distribution of nonuniform surface charge", dynamic_size=.true.)
80 call cfg_get_size(cfg, "dielectric%preset_charge", n_surface_charge)
81 allocate(preset_charge(n_surface_charge))
82 allocate(preset_charge_distribution(n_surface_charge))
83 call cfg_get(cfg, "dielectric%preset_charge", preset_charge)
84 call cfg_get(cfg, "dielectric%preset_charge_distribution", preset_charge_distribution)
85 preset_charge_distribution = preset_charge_distribution * st_domain_len(ndim)
86
87 call cfg_add_get(cfg, "dielectric%write", &
88 surface_output, "Output surface related information")
89
90 end subroutine dielectric_initialize
91
92 !> Update charge on dielectric surface based on particle fluxes. In case of
93 !> secondary emission, also update the electron density next to the surface.
94 subroutine dielectric_update_surface_charge(box, surface, dt, n_prev, &
95 s_prev, w_prev, s_out)
97 use m_streamer
98 type(box_t), intent(inout) :: box
99 type(surface_t), intent(inout) :: surface
100 real(dp), intent(in) :: dt !< Time step
101 integer, intent(in) :: n_prev !< Number of previous states
102 integer, intent(in) :: s_prev(n_prev) !< Previous states
103 real(dp), intent(in) :: w_prev(n_prev) !< Weights of previous states
104 integer, intent(in) :: s_out !< Output state
105#if NDIM == 2
106 integer :: i
107 real(dp) :: se_flux(box%n_cell)
108#endif
109 integer :: nc
110 real(dp) :: dr
111
112 nc = box%n_cell
113 dr = box%dr(af_neighb_dim(surface%direction))
114
115 select case (surface%direction)
116#if NDIM == 2
117 case (af_neighb_lowx)
118 do i = 1, nc
119 surface%sd(i, i_surf_dens+s_out) = &
120 sum(w_prev * surface%sd(i, i_surf_dens+s_prev)) - &
121 dt * sum(box%fc(1, i, 1, flux_variables) * flux_species_charge)
122 end do
123
124 if (size(flux_pos_ion) > 0 .and. gamma_se_ion > 0.0_dp) then
125 ! Compute secondary emission flux
126 se_flux = -gamma_se_ion * sum(box%fc(1, 1:nc, 1, flux_pos_ion), dim=2)
127 box%cc(1, 1:nc, i_electron+s_out) = &
128 box%cc(1, 1:nc, i_electron+s_out) + dt * se_flux / dr
129 surface%sd(:, i_surf_dens+s_out) = surface%sd(:, i_surf_dens+s_out) + &
130 dt * se_flux
131 end if
132 case (af_neighb_highx)
133 do i = 1, nc
134 surface%sd(i, i_surf_dens+s_out) = &
135 sum(w_prev * surface%sd(i, i_surf_dens+s_prev)) + &
136 dt * sum(box%fc(nc+1, i, 1, flux_variables) * flux_species_charge)
137 end do
138
139 if (size(flux_pos_ion) > 0 .and. gamma_se_ion > 0.0_dp) then
140 ! Compute secondary emission flux
141 se_flux = gamma_se_ion * sum(box%fc(nc+1, 1:nc, 1, flux_pos_ion), dim=2)
142 box%cc(nc, 1:nc, i_electron+s_out) = &
143 box%cc(nc, 1:nc, i_electron+s_out) + dt * se_flux / dr
144 surface%sd(:, i_surf_dens+s_out) = surface%sd(:, i_surf_dens+s_out) + &
145 dt * se_flux
146 end if
147 case (af_neighb_lowy)
148 do i = 1, nc
149 surface%sd(i, i_surf_dens+s_out) = &
150 sum(w_prev * surface%sd(i, i_surf_dens+s_prev)) - &
151 dt * sum(box%fc(i, 1, 2, flux_variables) * flux_species_charge)
152 end do
153
154 if (size(flux_pos_ion) > 0 .and. gamma_se_ion > 0.0_dp) then
155 ! Compute secondary emission flux
156 se_flux = -gamma_se_ion * sum(box%fc(1:nc, 1, 2, flux_pos_ion), dim=2)
157 box%cc(1:nc, 1, i_electron+s_out) = &
158 box%cc(1:nc, 1, i_electron+s_out) + dt * se_flux / dr
159 surface%sd(:, i_surf_dens+s_out) = surface%sd(:, i_surf_dens+s_out) + &
160 dt * se_flux
161 end if
162 case (af_neighb_highy)
163 do i = 1, nc
164 surface%sd(i, i_surf_dens+s_out) = &
165 sum(w_prev * surface%sd(i, i_surf_dens+s_prev)) + &
166 dt * sum(box%fc(i, nc+1, 2, flux_variables) * flux_species_charge)
167 end do
168
169 if (size(flux_pos_ion) > 0 .and. gamma_se_ion > 0.0_dp) then
170 ! Compute secondary emission flux
171 se_flux = gamma_se_ion * sum(box%fc(1:nc, nc+1, 2, flux_pos_ion), dim=2)
172 box%cc(1:nc, nc, i_electron+s_out) = &
173 box%cc(1:nc, nc, i_electron+s_out) + dt * se_flux / dr
174 surface%sd(:, i_surf_dens+s_out) = surface%sd(:, i_surf_dens+s_out) + &
175 dt * se_flux
176 end if
177#elif NDIM == 3
178 case default
179 error stop
180#endif
181 end select
183
184 subroutine dielectric_photon_emission(box, surface, dt, s_out)
186 use m_streamer
187 type(box_t), intent(inout) :: box
188 type(surface_t), intent(inout) :: surface
189 real(dp), intent(in) :: dt !< Time step
190 integer, intent(in) :: s_out !< Output state
191 integer :: nc
192 real(dp) :: dr
193
194 nc = box%n_cell
195 dr = box%dr(af_neighb_dim(surface%direction))
196
197 select case (surface%direction)
198#if NDIM == 2
199 case (af_neighb_lowx)
200 where (box%fc(1, 1:nc, 1, electric_fld) < 0.0_dp)
201 box%cc(1, 1:nc, i_electron+s_out) = &
202 box%cc(1, 1:nc, i_electron+s_out) + &
203 surface%sd(:, i_photon_flux) * dt / dr
204 surface%sd(:, i_surf_dens+s_out) = surface%sd(:, i_surf_dens+s_out) + &
205 surface%sd(:, i_photon_flux) * dt * uc_elem_charge
206 end where
207 case (af_neighb_highx)
208 where (box%fc(nc, 1:nc, 1, electric_fld) > 0.0_dp)
209 box%cc(nc, 1:nc, i_electron+s_out) = &
210 box%cc(nc, 1:nc, i_electron+s_out) + &
211 surface%sd(:, i_photon_flux) * dt / dr
212 surface%sd(:, i_surf_dens+s_out) = surface%sd(:, i_surf_dens+s_out) + &
213 surface%sd(:, i_photon_flux) * dt * uc_elem_charge
214 end where
215 case (af_neighb_lowy)
216 where (box%fc(1:nc, 1, 2, electric_fld) < 0.0_dp)
217 box%cc(1:nc, 1, i_electron+s_out) = &
218 box%cc(1:nc, 1, i_electron+s_out) + &
219 surface%sd(:, i_photon_flux) * dt / dr
220 surface%sd(:, i_surf_dens+s_out) = surface%sd(:, i_surf_dens+s_out) + &
221 surface%sd(:, i_photon_flux) * dt * uc_elem_charge
222 end where
223 case (af_neighb_highy)
224 where (box%fc(1:nc, nc, 2, electric_fld) > 0.0_dp)
225 box%cc(1:nc, nc, i_electron+s_out) = &
226 box%cc(1:nc, nc, i_electron+s_out) + &
227 surface%sd(:, i_photon_flux) * dt / dr
228 surface%sd(:, i_surf_dens+s_out) = surface%sd(:, i_surf_dens+s_out) + &
229 surface%sd(:, i_photon_flux) * dt * uc_elem_charge
230 end where
231#elif NDIM == 3
232 case default
233 error stop
234#endif
235 end select
236
237 end subroutine dielectric_photon_emission
238
239 !> Determine whether and where photons hit a dielectric, and change their
240 !> absorption location to the first cell inside the surface. If
241 !> photons_no_absorption is true, assume that photons are not absorbed by the
242 !> gas (so extrapolate their path).
243 subroutine dielectric_photon_absorption(tree, xyz_start, xyz_end, n_dim, &
244 n_photons, photon_weight)
245 use m_af_types
246 use m_af_interp
247 use m_streamer
248 type(af_t), intent(in) :: tree
249 integer, intent(in) :: n_dim
250 integer, intent(in) :: n_photons
251 real(dp), intent(in) :: xyz_start(3, n_photons)
252 real(dp), intent(inout) :: xyz_end(3, n_photons)
253 real(dp), intent(in) :: photon_weight
254 real(dp) :: xyz(n_dim), dvec(n_dim)
255 real(dp) :: dvec_small(n_dim), dvec_large(n_dim)
256 real(dp) :: xyz_gas(n_dim), xyz_nogas(n_dim)
257 real(dp) :: xyz_middle(n_dim), eps(1)
258 real(dp) :: travel_distance
259 integer :: n, n_steps, n_steps_extra, i, k, n_bisect
260 logical :: success
261
262 ! Determine the number of bisection steps to find the first cell inside the
263 ! dielectric, given a photon step length <= photon_step_length
264 n_bisect = -ceiling(&
265 log(af_min_dr(tree)/photon_step_length) / log(2.0_dp))
266
267 if (photons_no_absorption) then
268 n_steps_extra = ceiling(norm2(st_domain_len) / photon_step_length)
269 else
270 n_steps_extra = 0
271 end if
272
273 do n = 1, n_photons
274 xyz = xyz_start(1:n_dim, n)
275 dvec = xyz_end(1:n_dim, n) - xyz_start(1:n_dim, n)
276 travel_distance = norm2(dvec)
277
278 ! Large photon step length
279 dvec_large = (dvec/travel_distance) * photon_step_length
280
281 n_steps = ceiling(travel_distance/photon_step_length)
282 ! Normalize direction vector to right length. Possible TODO: near the
283 ! boundary of the domain, a photon can fly out crossing on a small
284 ! piece of a dielectric.
285 dvec_small = dvec / n_steps
286
287 do i = 1, n_steps + n_steps_extra
288 if (i <= n_steps) then
289 dvec = dvec_small
290 else
291 dvec = dvec_large
292 end if
293
294 xyz = xyz + dvec
295
296 ! If outside, stop
297 if (any(xyz < st_domain_origin .or. &
298 xyz > st_domain_origin + st_domain_len)) then
299 exit
300 end if
301
302 ! Get dielectric permittivity
303 eps = af_interp0(tree, xyz, [i_eps], success)
304 if (.not. success) error stop "photon unexpectedly outside domain"
305
306 ! If epsilon changes, start doing a search for the intersection point
307 if (eps(1) > 1.0_dp) then
308 ! Perform bisection to locate first cell inside dielectric
309 xyz_gas = xyz - dvec
310 xyz_nogas = xyz
311
312 do k = 1, n_bisect
313 xyz_middle = 0.5_dp * (xyz_gas + xyz_nogas)
314 eps = af_interp0(tree, xyz_middle, [i_eps], success)
315 if (.not. success) error stop "photon unexpectedly outside domain"
316
317 if (eps(1) > 1.0_dp) then
318 xyz_nogas = xyz_middle
319 else
320 xyz_gas = xyz_middle
321 end if
322 end do
323
324 if (i <= n_steps) then
325 ! The photon was absorbed within its normal travel path
326 xyz_end(1:n_dim, n) = -1e50_dp
327 call add_to_surface_photons(tree, xyz_nogas, photon_weight, &
328 gamma_se_ph_highenergy)
329 end if
330 call add_to_surface_photons(tree, xyz_nogas, photon_weight, &
331 gamma_se_ph_lowenergy)
332 exit
333 end if
334 end do
335 end do
336 end subroutine dielectric_photon_absorption
337
338 subroutine add_to_surface_photons(tree, xyz, w, frac)
339 type(af_t), intent(in) :: tree
340 real(dp), intent(in) :: xyz(ndim)
341 real(dp), intent(in) :: w
342 real(dp), intent(in) :: frac
343 integer :: ix, ix_cell(ndim-1)
344 real(dp) :: area
345
346 call surface_get_surface_cell(tree, diel, xyz, ix, ix_cell)
347 area = product(diel%surfaces(ix)%dr)
348
349#if NDIM == 2
350 diel%surfaces(ix)%sd(ix_cell(1), i_photon_flux) = &
351 diel%surfaces(ix)%sd(ix_cell(1), i_photon_flux) &
352 + frac * w / area
353#else
354 error stop
355#endif
356 end subroutine add_to_surface_photons
357
359 integer :: n
360
361 do n = 1, diel%max_ix
362 if (diel%surfaces(n)%in_use) then
363#if NDIM == 1
364 diel%surfaces(n)%sd(i_photon_flux) = 0.0_dp
365#elif NDIM == 2
366 diel%surfaces(n)%sd(:, i_photon_flux) = 0.0_dp
367#elif NDIM == 3
368 diel%surfaces(n)%sd(:, :, i_photon_flux) = 0.0_dp
369#endif
370 end if
371 end do
372 end subroutine dielectric_reset_photons
373
374end module m_dielectric
Module with settings and routines to handle dielectrics.
integer, parameter, public i_surf_dens
logical, public, protected surface_output
subroutine, public dielectric_initialize(tree, cfg)
type(surfaces_t), public diel
To store dielectric surface.
subroutine, public dielectric_reset_photons()
subroutine, public dielectric_photon_emission(box, surface, dt, s_out)
subroutine, public dielectric_update_surface_charge(box, surface, dt, n_prev, s_prev, w_prev, s_out)
Update charge on dielectric surface based on particle fluxes. In case of secondary emission,...
subroutine, public dielectric_photon_absorption(tree, xyz_start, xyz_end, n_dim, n_photons, photon_weight)
Determine whether and where photons hit a dielectric, and change their absorption location to the fir...
integer, parameter, public i_photon_flux
This module contains several pre-defined variables like:
Definition m_streamer.f90:6
integer, dimension(:), allocatable, public, protected flux_species_charge
List of the charges of the flux species.
integer, public, protected i_eps
Index can be set to include a dielectric.
integer, dimension(:), allocatable, public, protected flux_pos_ion
List of positive ion fluxes (useful for secondary emission)
integer, dimension(:), allocatable, public, protected flux_variables
List of all flux variables (face-centered index)
integer, public, protected i_electron
Index of electron density.
integer, public, protected electric_fld
Index of electric field vector.
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.
Module with basic types.
Definition m_types.f90:2
Module that contains physical and numerical constants.
real(dp), parameter uc_elem_charge