Afivo  0.3
space_plasma_2d_v2.f90
1 
2 program space_plasma_2d
3  use m_a2_all
4 
5  implicit none
6 
7  ! Cell-centered variables
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
17 
18  integer, parameter :: i_output(5) = [i_cs_ion, i_cs, i_o, i_o_min, i_ne]
19 
20  ! Domain
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
26 
27  ! Time steps
28  real(dp) :: dt_adapt = 5.0e-1_dp !60.0_dp
29  real(dp) :: dt_output = 1.0_dp
30  real(dp) :: end_time = 3600.0_dp
31 
32  ! Physical parameters
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
43 
44  real(dp) :: max_diffusion_coeff
45  type(a2_t) :: tree
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
50  real(dp) :: dt, time
51  real(dp) :: dr_min(2)
52  character(len=100) :: fname
53 
54  print *, "Running space_plasma_2d"
55  print *, "Number of threads", af_get_max_threads()
56 
57  ! Initialize tree
58  call a2_init(tree, & ! Tree to initialize
59  box_size, & ! A box contains box_size**DIM cells
60  n_var_cell=9, & ! Number of cell-centered variables
61  n_var_face=2, & ! Number of face-centered variables
62  dr=dr, & ! Distance between cells on base level
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"]) ! Variable names
66 
67  ! Set default methods
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)
73 
74  ! Set index of box
75  ix_list(:, 1) = [1, 1]
76 
77  ! Create the base mesh
78  call a2_set_base(tree, 1, ix_list)
79 
80  output_cnt = 0
81  time = 0
82 
83  do
84  call a2_loop_box(tree, set_initial_condition)
85  call a2_adjust_refinement(tree, & ! tree
86  refine_routine, & ! Refinement function
87  refine_info, & ! Information about refinement
88  1) ! Buffer width (in cells)
89  if (refine_info%n_add == 0) exit
90  end do
91 
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)
94 
95  call a2_print_info(tree)
96 
97  time_steps = 0
98 
99  max_diffusion_coeff = max(dc_cs_ion_parallel, dc_cs_ion_perpendicular, &
100  dc_cs)
101 
102  ! Starting simulation
103  do
104  time_steps = time_steps + 1
105  dr_min = a2_min_dr(tree)
106 
107  ! Limit time step for diffusion
108  dt = 0.25_dp * minval(dr_min)**2 / max_diffusion_coeff
109 
110  !********************************************************
111  !Anbang modified to include different mechanisms later on
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)))
118  ! dt = min(dt, 1.e-5_dp)
119  print *, "dt = ", dt, "time_steps = ", time_steps, "time is", time
120  !********************************************************
121 
122  n_steps = ceiling(dt_adapt/dt)
123  dt = dt_adapt / n_steps
124 
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)
133 
134  call a2_write_silo(tree, trim(fname), output_cnt, time, &
135  ixs_cc=i_output, dir="output")
136 
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")
143  end if
144 
145  if (time > end_time) exit
146 
147  do n = 1, n_steps
148  ! Copy previous solution
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)
153 
154  ! Explicit trapezoidal rule. First take two forward Euler steps over dt
155  do i = 1, 2
156  ! Call procedure get_fluxes for each id in tree, giving the list of boxes
157  call a2_loop_boxes(tree, get_fluxes)
158 
159  ! Restrict fluxes from children to parents on refinement boundaries.
160  call a2_consistent_fluxes(tree, [i_cs_ion, i_cs])
161 
162  ! Call procedure update_solution (see below) for each box in tree, with argument dt
163  call a2_loop_box_arg(tree, update_solution, [dt])
164 
165  ! Restrict variables i_Cs_ion to all parent boxes
166  call a2_restrict_tree(tree, i_cs_ion)
167  call a2_restrict_tree(tree, i_cs)
168  end do
169 
170  ! Now take average of phi_old and phi (this is the explicit trapezoidal rule)
171  call a2_loop_box(tree, average_solution)
172  time = time + dt
173  end do
174 
175  ! Fill ghost cells before refinement
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)
178 
179  call a2_adjust_refinement(tree, refine_routine, refine_info, 1)
180  end do
181 
182 contains
183 
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)
188  real(dp) :: diff
189  integer :: i, j, nc
190 
191  nc = box%n_cell
192 
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)
200 
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
206  else
207  cell_flags(i, j) = af_keep_ref
208  end if
209  end do; end do
210  end subroutine refine_routine
211 
213  subroutine set_initial_condition(box)
214  type(box2_t), intent(inout) :: box
215  integer :: i, j, nc
216  real(dp) :: distance, density
217 
218  nc = box%n_cell
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)
222 
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
226  end do; end do
227  end subroutine set_initial_condition
228 
229  subroutine get_fluxes(boxes, id)
230  use m_flux_schemes
231  type(box2_t), intent(inout) :: boxes(:)
232  integer, intent(in) :: id
233  integer :: nc
234  real(dp) :: inv_dx
235  real(dp), allocatable :: diff_coeff(:, :, :)
236 
237  nc = boxes(id)%n_cell
238  inv_dx = 1/boxes(id)%dr
239 
240  allocate(diff_coeff(1:nc+1, 1:nc+1, 2))
241 
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)
244 
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
249 
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
253 
254  end subroutine get_fluxes
255 
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
262  integer :: i, j, nc
263 
264  nc = box%n_cell
265  inv_dr = 1/box%dr
266 
267  do j = 1, nc
268  do i = 1, nc
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
271 
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
276 
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
280 
281  ! Fluxes
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))
288  end do
289  end do
290  end subroutine update_solution
291 
293  subroutine average_solution(box)
294  type(box2_t), intent(inout) :: box
295 
296  box%cc(:, :, :) = 0.5_dp * (box%cc(:, :, :) + &
297  box%cc(:, :, :))
298  end subroutine average_solution
299 
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...
Definition: m_a2_all.f90:4