2 program space_plasma_2d
8 integer,
parameter :: i_cs_ion = 1
9 integer,
parameter :: i_cs = 2
10 integer,
parameter :: i_o = 3
11 integer,
parameter :: i_o_min = 4
12 integer,
parameter :: i_cs_ion_old = 5
13 integer,
parameter :: i_cs_old = 6
14 integer,
parameter :: i_o_old = 7
15 integer,
parameter :: i_o_min_old = 8
16 integer,
parameter :: i_ne = 9
18 integer,
parameter :: i_output(5) = [i_cs_ion, i_cs, i_o, i_o_min, i_ne]
21 integer,
parameter :: box_size = 10
22 real(dp),
parameter :: domain_len = 1.0e4_dp
23 real(dp),
parameter :: dr = domain_len / box_size
24 integer,
parameter :: min_refinement_lvl = 5
25 integer,
parameter :: max_refinement_lvl = 7
28 real(dp) :: dt_adapt = 5.0e-1_dp
29 real(dp) :: dt_output = 1.0_dp
30 real(dp) :: end_time = 3600.0_dp
33 real(dp),
parameter :: dc_cs_ion_parallel = 4.2e3_dp
34 real(dp),
parameter :: dc_cs_ion_perpendicular = 4.2e3_dp
35 real(dp),
parameter :: dc_cs = 2.5e4_dp
36 real(dp),
parameter :: k_attachment = 0.0e-3_dp
37 real(dp),
parameter :: k_recombination = 0.0e-3_dp
38 real(dp),
parameter :: k_photoionization = 0.0e-4_dp
39 real(dp),
parameter :: initial_cs_density = 1.e24_dp
40 real(dp),
parameter :: initial_ionization_fraction = 0.01e0_dp
41 real(dp),
parameter :: initial_o_density = 1e11_dp
42 real(dp),
parameter :: initial_sigma = 50.0_dp
44 real(dp) :: max_diffusion_coeff
46 type(ref_info_t) :: refine_info
47 integer :: ix_list(2, 1)
48 integer :: time_steps, output_cnt
49 integer :: i, n, n_steps
52 character(len=100) :: fname
54 print *,
"Running space_plasma_2d" 55 print *,
"Number of threads", af_get_max_threads()
63 r_min=[-0.5_dp, -0.5_dp] * domain_len, &
64 cc_names=[
character(len=10) ::
"Cs_ion",
"Cs",
"O",
"O_min", &
65 "Cs_ion_old",
"Cs_old",
"O_old",
"O_min_old",
"ne"])
68 call a2_set_cc_methods(tree, i_cs_ion, a2_bc_neumann_zero, a2_gc_interp_lim)
69 call a2_set_cc_methods(tree, i_cs, a2_bc_neumann_zero, a2_gc_interp_lim)
70 call a2_set_cc_methods(tree, i_o, a2_bc_neumann_zero, a2_gc_interp_lim)
71 call a2_set_cc_methods(tree, i_o_min, a2_bc_neumann_zero, a2_gc_interp_lim)
72 call a2_set_cc_methods(tree, i_ne, a2_bc_neumann_zero, a2_gc_interp_lim)
75 ix_list(:, 1) = [1, 1]
78 call a2_set_base(tree, 1, ix_list)
84 call a2_loop_box(tree, set_initial_condition)
85 call a2_adjust_refinement(tree, &
89 if (refine_info%n_add == 0)
exit 92 call a2_gc_tree(tree, i_cs_ion, a2_gc_interp_lim, a2_bc_neumann_zero)
93 call a2_gc_tree(tree, i_cs, a2_gc_interp_lim, a2_bc_neumann_zero)
95 call a2_print_info(tree)
99 max_diffusion_coeff = max(dc_cs_ion_parallel, dc_cs_ion_perpendicular, &
104 time_steps = time_steps + 1
105 dr_min = a2_min_dr(tree)
108 dt = 0.25_dp * minval(dr_min)**2 / max_diffusion_coeff
112 if (k_attachment > 0.0_dp) dt = min(dt, &
113 & 0.5_dp/(k_attachment*initial_cs_density + epsilon(1.0_dp)))
114 if (k_recombination > 0.0_dp) dt = min(dt, &
115 & 0.5_dp/(k_recombination*initial_cs_density + epsilon(1.0_dp)))
116 if (k_photoionization > 0.0_dp) dt = min(dt, &
117 & 0.5_dp/(k_photoionization + epsilon(1.0_dp)))
119 print *,
"dt = ", dt,
"time_steps = ", time_steps,
"time is", time
122 n_steps = ceiling(dt_adapt/dt)
123 dt = dt_adapt / n_steps
125 if (output_cnt * dt_output <= time)
then 126 output_cnt = output_cnt + 1
127 write(fname,
"(A,I0)")
"space_plasma_2d_", output_cnt
128 call a2_gc_tree(tree, i_cs_ion, a2_gc_interp_lim, a2_bc_neumann_zero)
129 call a2_gc_tree(tree, i_cs, a2_gc_interp_lim, a2_bc_neumann_zero)
130 call a2_gc_tree(tree, i_o, a2_gc_interp_lim, a2_bc_neumann_zero)
131 call a2_gc_tree(tree, i_o_min, a2_gc_interp_lim, a2_bc_neumann_zero)
132 call a2_gc_tree(tree, i_ne, a2_gc_interp_lim, a2_bc_neumann_zero)
134 call a2_write_silo(tree, trim(fname), output_cnt, time, &
135 ixs_cc=i_output, dir=
"output")
137 write(fname,
"(A,I0)")
"space_plasma_2d_x_", output_cnt
138 call a2_write_line(tree, trim(fname), i_output, &
139 [0.0_dp, 0.0_dp], [0.5_dp*domain_len, 0.0_dp], 1024, dir=
"output")
140 write(fname,
"(A,I0)")
"space_plasma_2d_y_", output_cnt
141 call a2_write_line(tree, trim(fname), i_output, &
142 [0.0_dp, 0.0_dp], [0.0_dp, 0.5_dp*domain_len], 1024, dir=
"output")
145 if (time > end_time)
exit 149 call a2_tree_copy_cc(tree, i_cs_ion, i_cs_ion_old)
150 call a2_tree_copy_cc(tree, i_cs, i_cs_old)
151 call a2_tree_copy_cc(tree, i_o, i_o_old)
152 call a2_tree_copy_cc(tree, i_o_min, i_o_min_old)
157 call a2_loop_boxes(tree, get_fluxes)
160 call a2_consistent_fluxes(tree, [i_cs_ion, i_cs])
163 call a2_loop_box_arg(tree, update_solution, [dt])
166 call a2_restrict_tree(tree, i_cs_ion)
167 call a2_restrict_tree(tree, i_cs)
171 call a2_loop_box(tree, average_solution)
176 call a2_gc_tree(tree, i_cs_ion, a2_gc_interp_lim, a2_bc_neumann_zero)
177 call a2_gc_tree(tree, i_cs, a2_gc_interp_lim, a2_bc_neumann_zero)
179 call a2_adjust_refinement(tree, refine_routine, refine_info, 1)
185 subroutine refine_routine(box, cell_flags)
186 type(box2_t),
intent(in) :: box
187 integer,
intent(out) :: cell_flags(box%n_cell, box%n_cell)
193 do j = 1, nc;
do i = 1, nc
194 diff = abs(box%cc(i+1, j, i_cs_ion) + &
195 box%cc(i-1, j, i_cs_ion) + &
196 box%cc(i, j+1, i_cs_ion) + &
197 box%cc(i, j-1, i_cs_ion) - &
198 4 * box%cc(i, j, i_cs_ion)) * box%dr / &
199 (initial_cs_density * initial_ionization_fraction)
201 if (box%lvl < min_refinement_lvl .or. diff > 0.1_dp &
202 .and. box%lvl < max_refinement_lvl)
then 203 cell_flags(i, j) = af_do_ref
204 else if (diff < 0.01_dp)
then 205 cell_flags(i, j) = af_rm_ref
207 cell_flags(i, j) = af_keep_ref
210 end subroutine refine_routine
213 subroutine set_initial_condition(box)
214 type(box2_t),
intent(inout) :: box
216 real(dp) :: distance, density
219 do j = 0, nc+1;
do i = 0, nc+1
220 distance = norm2(a2_r_cc(box, [i, j]))
221 density = exp(-0.5_dp * distance**2/initial_sigma**2)
223 box%cc(i, j, i_cs_ion) = initial_ionization_fraction * density * initial_cs_density
224 box%cc(i, j, i_cs) = (1 - initial_ionization_fraction) * density * initial_cs_density
225 box%cc(i, j, i_o) = initial_o_density
227 end subroutine set_initial_condition
229 subroutine get_fluxes(boxes, id)
231 type(box2_t),
intent(inout) :: boxes(:)
232 integer,
intent(in) :: id
235 real(dp),
allocatable :: diff_coeff(:, :, :)
237 nc = boxes(id)%n_cell
238 inv_dx = 1/boxes(id)%dr
240 allocate(diff_coeff(1:nc+1, 1:nc+1, 2))
242 call a2_gc_box(boxes, id, i_cs_ion, a2_gc_interp_lim, a2_bc_neumann_zero)
243 call a2_gc_box(boxes, id, i_cs, a2_gc_interp_lim, a2_bc_neumann_zero)
245 diff_coeff(:, :, 1) = dc_cs_ion_parallel
246 diff_coeff(:, :, 2) = dc_cs_ion_perpendicular
247 call flux_diff_2d(boxes(id)%cc(:, :, i_cs_ion), diff_coeff, inv_dx, nc, 1)
248 boxes(id)%fc(:, :, :, i_cs_ion) = diff_coeff
250 diff_coeff(:, :, :) = dc_cs
251 call flux_diff_2d(boxes(id)%cc(:, :, i_cs), diff_coeff, inv_dx, nc, 1)
252 boxes(id)%fc(:, :, :, i_cs) = diff_coeff
254 end subroutine get_fluxes
257 subroutine update_solution(box, dt)
258 type(box2_t),
intent(inout) :: box
259 real(dp),
intent(in) :: dt(:)
260 real(dp) :: inv_dr, recombination, photoionization
261 real(dp) :: attachment, electron_density
269 electron_density = box%cc(i, j, i_cs_ion) - box%cc(i, j, i_o_min)
270 box%cc(i, j, i_ne) = electron_density
272 recombination = dt(1) * k_recombination * box%cc(i, j, i_cs_ion)**2
273 photoionization = dt(1) * k_photoionization * box%cc(i, j, i_cs)
274 box%cc(i, j, i_cs_ion) = box%cc(i, j, i_cs_ion) - recombination + photoionization
275 box%cc(i, j, i_cs) = box%cc(i, j, i_cs) + recombination - photoionization
277 attachment = dt(1) * k_attachment * box%cc(i, j, i_o) * electron_density
278 box%cc(i, j, i_o) = box%cc(i, j, i_o) - attachment
279 box%cc(i, j, i_o_min) = box%cc(i, j, i_o_min) + attachment
282 box%cc(i, j, i_cs_ion) = box%cc(i, j, i_cs_ion) + dt(1) * inv_dr * ( &
283 box%fc(i, j, 1, i_cs_ion) - box%fc(i+1, j, 1, i_cs_ion) + &
284 box%fc(i, j, 2, i_cs_ion) - box%fc(i, j+1, 2, i_cs_ion))
285 box%cc(i, j, i_cs) = box%cc(i, j, i_cs) + dt(1) * inv_dr * ( &
286 box%fc(i, j, 1, i_cs) - box%fc(i+1, j, 1, i_cs) + &
287 box%fc(i, j, 2, i_cs) - box%fc(i, j+1, 2, i_cs))
290 end subroutine update_solution
293 subroutine average_solution(box)
294 type(box2_t),
intent(inout) :: box
296 box%cc(:, :, :) = 0.5_dp * (box%cc(:, :, :) + &
298 end subroutine average_solution
300 end program space_plasma_2d
Module containing a couple simple flux schemes for scalar advection/diffusion problems.
Module which contains all Afivo modules, so that a user does not have to include them separately...