afivo-streamer 1.1
1D/2D/3D streamer simulations with AMR
Loading...
Searching...
No Matches
m_photoi_helmh.f90
Go to the documentation of this file.
1!> Module for photoionization with the Helmholtz approximation
2!>
3!> The equations solved are nabla^2 phi_i - lambda_i^2 * phi_i = f, where f is
4!> the photon production term, and there can be modes i = 1, ..., N. The photon
5!> absorption term is then given by sum(c_i * phi_i).
6!>
7!> For the case N=2, the following coefficients can be used:
8!> lambdas = 4425.36_dp, 750.06_dp 1/(m bar)
9!> coeffs = 337555.5_dp, 19972.0_dp 1/(m bar)^2
10!>
11!> TODO: look up values for the case N=3
13#include "../afivo/src/cpp_macros.h"
14 use m_af_all
15 use m_streamer
16
17 implicit none
18 private
19
20 type(mg_t), allocatable :: mg_helm(:) ! Multigrid option struct
21
22 !> Maximum number of FMG cycles to perform to update each mode
23 integer, parameter :: max_fmg_cycles = 10
24
25 !> Maximum residual relative to max(|rhs|)
26 real(dp) :: max_rel_residual = 1.0d-2
27
28 !> Number of Helmholtz modes to include
29 integer :: n_modes = 2
30 !> Lambdas to use for lpl(phi) - lambda*phi = f; unit 1/(m bar)
31 real(dp), allocatable :: lambdas(:)
32 !> Weights corresponding to the lambdas; unit 1/(m bar)^2
33 real(dp), allocatable :: coeffs(:)
34
35 integer, allocatable :: i_modes(:)
36
38 public :: photoi_helmh_compute
39 public :: photoi_helmh_bc
40
41contains
42
43 !> Initialize options for Helmholtz photoionization
44 subroutine photoi_helmh_initialize(tree, cfg, is_used, eta)
45 use m_config
47 use m_gas
48 type(af_t), intent(inout) :: tree
49 type(cfg_t), intent(inout) :: cfg
50 logical, intent(in) :: is_used !< Whether the module is used
51 real(dp), intent(in) :: eta !< Efficiency
52 integer :: n, ix
53 character(len=12) :: name
54 character(len=12) :: author = "Bourdon-3"
55 real(dp) :: frac_o2, dummy(0)
56
57 !< [helmholtz_parameters]
58 call cfg_add_get(cfg, "photoi_helmh%author", author, &
59 "Can be Bourdon-3 (default), Bourdon-2, Luque or custom")
60 call cfg_add(cfg, "photoi_helmh%lambdas", dummy, &
61 "Lambdas to use in Helmholtz eq; unit 1/(m bar)", .true.)
62 call cfg_add(cfg, "photoi_helmh%coeffs", dummy, &
63 "Weights corresponding to the lambdas; unit 1/(m bar)^2", .true.)
64 call cfg_add_get(cfg, "photoi_helmh%max_rel_residual", max_rel_residual, &
65 "Maximum residual for Helmholtz solver, relative to max(|rhs|)")
66 !< [helmholtz_parameters]
67
68 ! Exit here if the module is not used
69 if (.not. is_used) return
70
71 ! Whether oxygen is required is tested below, the idea being that we will in
72 ! the future add photoionization cases for other gases
73 ix = gas_index("O2")
74 if (ix /= -1) then
75 frac_o2 = gas_fractions(ix)
76 else
77 frac_o2 = 0.0_dp ! No oxygen
78 end if
79
80 select case (author)
81 case ("Luque")
82 if (frac_o2 <= 0.0_dp) error stop "Photoionization: no oxygen present"
83 n_modes = 2
84 lambdas = [4425.38_dp, 750.06_dp]
85 coeffs = [337557.38_dp, 19972.14_dp]
86
87 ! Convert to correct units by multiplying with pressure in bar
88 lambdas = lambdas * (frac_o2/0.2_dp) * gas_pressure ! 1/m
89 coeffs = coeffs * ((frac_o2/0.2_dp) * gas_pressure)**2 ! 1/m^2
90
91 ! Note that for Luque photoi_eta must be 1.0 (since we must not multiply
92 ! coeffs of Luque by photoi_eta)
93 if (abs(eta - 1.0_dp) > 0) &
94 error stop "With Luque photoionization, photoi%eta should be 1.0"
95 case ("Bourdon-2")
96 if (frac_o2 <= 0.0_dp) error stop "Photoionization: no oxygen present"
97 !> Bourdon two terms lambdas in SI units are: [7305.62,44081.25]
98 !> Bourdon two terms coeffs in SI units are: [11814508.38,998607256]
99 n_modes = 2
100 lambdas = [7305.62_dp, 44081.25_dp]
101 coeffs = [11814508.38_dp, 998607256.0_dp]
102
103 ! Convert to correct units by multiplying with pressure in bar
104 lambdas = lambdas * frac_o2 * gas_pressure ! 1/m
105 ! Important note: in the case of Bourdon coeffs must be multiplied by
106 ! photoi_eta, however we do not multiply it here but it is considered in
107 ! set_photoionization_rate calculation as [photoi_eta * quench_fac]
108 ! please check m_photoi.f90
109 coeffs = coeffs * (frac_o2 * gas_pressure)**2 ! 1/m^2
110 case ("Bourdon-3")
111 if (frac_o2 <= 0.0_dp) error stop "Photoionization: no oxygen present"
112 !> Bourdon three terms lambdas in SI units are: [4147.85 10950.93 66755.67]
113 !> bourdon three terms coeffs in SI units are: [ 1117314.935 28692377.5 2748842283 ]
114 n_modes = 3
115 lambdas = [4147.85_dp, 10950.93_dp, 66755.67_dp]
116 coeffs = [1117314.935_dp, 28692377.5_dp, 2748842283.0_dp]
117
118 ! Convert to correct units by multiplying with pressure in bar
119 lambdas = lambdas * frac_o2 * gas_pressure ! 1/m
120 ! Important note: in the case of Bourdon coeffs must be multiplied by
121 ! photoi_eta, however we do not multiply it here but it is considered in
122 ! set_photoionization_rate calculation as [photoi_eta * quench_fac]
123 ! please check m_photoi.f90
124 coeffs = coeffs * (frac_o2 * gas_pressure)**2 ! 1/m^2
125 case ("custom")
126 call cfg_get_size(cfg, "photoi_helmh%lambdas", n_modes)
127 if (n_modes < 1) error stop "Custom photoionization lambdas and coeffs missing."
128 allocate(lambdas(n_modes))
129 allocate(coeffs(n_modes))
130 call cfg_get(cfg, "photoi_helmh%lambdas", lambdas)
131 call cfg_get(cfg, "photoi_helmh%coeffs", coeffs)
132 ! Convert to correct units by multiplying with pressure in bar, but
133 ! perform no other normalization.
134 lambdas = lambdas * gas_pressure ! 1/m
135 coeffs = coeffs * gas_pressure**2 ! 1/m^2
136 case default
137 print *, "Unknown photoi_helmh_author: ", trim(author)
138 error stop
139 end select
140
141 ! Add required variables
142 allocate(i_modes(n_modes))
143 do n = 1, n_modes
144 write(name, "(A,I0)") "helmh_", n
145 call af_add_cc_variable(tree, trim(name), write_out=.false., ix=i_modes(n))
146 end do
147
148 ! Now set the multigrid options
149 allocate(mg_helm(n_modes))
150
151 do n = 1, n_modes
152 mg_helm(n)%i_phi = i_modes(n)
153 mg_helm(n)%i_rhs = i_rhs
154 mg_helm(n)%i_tmp = i_tmp
155 mg_helm(n)%sides_bc => photoi_helmh_bc
156 mg_helm(n)%helmholtz_lambda = lambdas(n)**2
157 mg_helm(n)%operator_type = mg_normal_operator
158 mg_helm(n)%prolongation_type = mg_prolong_linear
159 end do
160 end subroutine photoi_helmh_initialize
161
162 subroutine photoi_helmh_compute(tree, i_photo)
163 type(af_t), intent(inout) :: tree
164 integer, intent(in) :: i_photo
165
166 integer :: n, lvl, i, id
167 real(dp) :: residu, max_rhs
168
169 call af_tree_clear_cc(tree, i_photo)
170
171 call af_tree_maxabs_cc(tree, mg_helm(1)%i_rhs, max_rhs)
172 max_rhs = max(max_rhs, sqrt(epsilon(1.0_dp)))
173
174 do n = 1, n_modes
175 if (.not. mg_helm(n)%initialized) then
176 if (n > 1) then
177 ! Re-use prolongation stencil
178 mg_helm(n)%prolongation_key = mg_helm(1)%prolongation_key
179 end if
180
181 call mg_init(tree, mg_helm(n))
182 end if
183
184 do i = 1, max_fmg_cycles
185 call mg_fas_fmg(tree, mg_helm(n), .true., .true.)
186 call af_tree_maxabs_cc(tree, mg_helm(n)%i_tmp, residu)
187 ! print *, n, i, residu/max_rhs
188 if (residu/max_rhs < max_rel_residual) exit
189 end do
190
191 !$omp parallel private(lvl, i, id)
192 do lvl = 1, tree%highest_lvl
193 !$omp do
194 do i = 1, size(tree%lvls(lvl)%leaves)
195 id = tree%lvls(lvl)%leaves(i)
196 tree%boxes(id)%cc(dtimes(:), i_photo) = &
197 tree%boxes(id)%cc(dtimes(:), i_photo) - &
198 coeffs(n) * tree%boxes(id)%cc(dtimes(:), i_modes(n))
199 end do
200 !$omp end do
201 end do
202 !$omp end parallel
203 end do
204 end subroutine photoi_helmh_compute
205
206 !> @todo Think about good (and efficient) boundary conditions for Helmholtz
207 !> equations, see also Bourdon et al. PSST 2017. Setting a Dirichlet zero b.c.
208 !> is inaccurate if the streamer gets close to that boundary, otherwise it
209 !> should be quite reasonable.
210 subroutine photoi_helmh_bc(box, nb, iv, coords, bc_val, bc_type)
211 type(box_t), intent(in) :: box
212 integer, intent(in) :: nb
213 integer, intent(in) :: iv
214 real(dp), intent(in) :: coords(ndim, box%n_cell**(ndim-1))
215 real(dp), intent(out) :: bc_val(box%n_cell**(ndim-1))
216 integer, intent(out) :: bc_type
217 integer :: nc
218
219 nc = box%n_cell
220
221 if (af_neighb_dim(nb) == ndim) then
222 bc_type = af_bc_dirichlet
223 bc_val = 0.0_dp
224 else
225 bc_type = af_bc_neumann
226 bc_val = 0.0_dp
227 end if
228 end subroutine photoi_helmh_bc
229
230end module m_photoi_helmh
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
real(dp), public, protected gas_pressure
Definition m_gas.f90:18
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.
This module contains several pre-defined variables like:
Definition m_streamer.f90:6
integer, public, protected i_rhs
Index of source term Poisson.
integer, public, protected i_tmp
Index of temporary variable.
Module that contains physical and numerical constants.