6#include "../afivo/src/cpp_macros.h"
19 type(surfaces_t),
public ::
diel
25 real(dp),
protected :: photon_step_length = 1.0e-3_dp
28 real(dp),
protected :: gamma_se_ion = 0.1_dp
31 real(dp),
protected :: gamma_se_ph_highenergy = 0.1_dp
34 real(dp),
protected :: gamma_se_ph_lowenergy = 0.1_dp
37 logical :: photons_no_absorption = .false.
40 integer,
protected :: n_surface_charge
43 real(dp),
allocatable,
protected :: preset_charge(:)
46 real(dp),
allocatable,
protected :: preset_charge_distribution(:)
58 type(af_t),
intent(in) :: tree
59 type(cfg_t),
intent(inout) :: cfg
61 call cfg_add_get(cfg,
"dielectric%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", &
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)
87 call cfg_add_get(cfg,
"dielectric%write", &
95 s_prev, w_prev, s_out)
98 type(box_t),
intent(inout) :: box
99 type(surface_t),
intent(inout) :: surface
100 real(dp),
intent(in) :: dt
101 integer,
intent(in) :: n_prev
102 integer,
intent(in) :: s_prev(n_prev)
103 real(dp),
intent(in) :: w_prev(n_prev)
104 integer,
intent(in) :: s_out
107 real(dp) :: se_flux(box%n_cell)
113 dr = box%dr(af_neighb_dim(surface%direction))
115 select case (surface%direction)
117 case (af_neighb_lowx)
120 sum(w_prev * surface%sd(i,
i_surf_dens+s_prev)) - &
124 if (
size(
flux_pos_ion) > 0 .and. gamma_se_ion > 0.0_dp)
then
126 se_flux = -gamma_se_ion * sum(box%fc(1, 1:nc, 1,
flux_pos_ion), dim=2)
128 box%cc(1, 1:nc,
i_electron+s_out) + dt * se_flux / dr
132 case (af_neighb_highx)
135 sum(w_prev * surface%sd(i,
i_surf_dens+s_prev)) + &
139 if (
size(
flux_pos_ion) > 0 .and. gamma_se_ion > 0.0_dp)
then
141 se_flux = gamma_se_ion * sum(box%fc(nc+1, 1:nc, 1,
flux_pos_ion), dim=2)
143 box%cc(nc, 1:nc,
i_electron+s_out) + dt * se_flux / dr
147 case (af_neighb_lowy)
150 sum(w_prev * surface%sd(i,
i_surf_dens+s_prev)) - &
154 if (
size(
flux_pos_ion) > 0 .and. gamma_se_ion > 0.0_dp)
then
156 se_flux = -gamma_se_ion * sum(box%fc(1:nc, 1, 2,
flux_pos_ion), dim=2)
158 box%cc(1:nc, 1,
i_electron+s_out) + dt * se_flux / dr
162 case (af_neighb_highy)
165 sum(w_prev * surface%sd(i,
i_surf_dens+s_prev)) + &
169 if (
size(
flux_pos_ion) > 0 .and. gamma_se_ion > 0.0_dp)
then
171 se_flux = gamma_se_ion * sum(box%fc(1:nc, nc+1, 2,
flux_pos_ion), dim=2)
173 box%cc(1:nc, nc,
i_electron+s_out) + dt * se_flux / dr
187 type(box_t),
intent(inout) :: box
188 type(surface_t),
intent(inout) :: surface
189 real(dp),
intent(in) :: dt
190 integer,
intent(in) :: s_out
195 dr = box%dr(af_neighb_dim(surface%direction))
197 select case (surface%direction)
199 case (af_neighb_lowx)
207 case (af_neighb_highx)
215 case (af_neighb_lowy)
223 case (af_neighb_highy)
244 n_photons, photon_weight)
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
264 n_bisect = -ceiling(&
265 log(af_min_dr(tree)/photon_step_length) / log(2.0_dp))
267 if (photons_no_absorption)
then
268 n_steps_extra = ceiling(norm2(
st_domain_len) / photon_step_length)
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)
279 dvec_large = (dvec/travel_distance) * photon_step_length
281 n_steps = ceiling(travel_distance/photon_step_length)
285 dvec_small = dvec / n_steps
287 do i = 1, n_steps + n_steps_extra
288 if (i <= n_steps)
then
303 eps = af_interp0(tree, xyz, [
i_eps], success)
304 if (.not. success) error stop
"photon unexpectedly outside domain"
307 if (eps(1) > 1.0_dp)
then
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"
317 if (eps(1) > 1.0_dp)
then
318 xyz_nogas = xyz_middle
324 if (i <= n_steps)
then
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)
330 call add_to_surface_photons(tree, xyz_nogas, photon_weight, &
331 gamma_se_ph_lowenergy)
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)
346 call surface_get_surface_cell(tree,
diel, xyz, ix, ix_cell)
347 area = product(
diel%surfaces(ix)%dr)
356 end subroutine add_to_surface_photons
361 do n = 1,
diel%max_ix
362 if (
diel%surfaces(n)%in_use)
then
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:
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 that contains physical and numerical constants.
real(dp), parameter uc_elem_charge