Afivo  0.3
poisson_benchmark_2d.f90

This program can be used to benchmark the multigrid routines. For simplicity, it does not compare results with a known solution.

1 
6 program poisson_benchmark_2d
7  use m_a2_all
8 
9  implicit none
10 
11  integer, parameter :: n_boxes_base = 1
12  integer, parameter :: n_var_cell = 3
13  integer, parameter :: i_phi = 1
14  integer, parameter :: i_rhs = 2
15  integer, parameter :: i_tmp = 3
16 
17  type(a2_t) :: tree
18  type(ref_info_t) :: ref_info
19  integer :: mg_iter, n_args
20  integer :: n_cell, n_iterations, max_ref_lvl
21  integer :: ix_list(2, n_boxes_base)
22  real(dp) :: dr, time, runtime
23  character(len=100) :: fname, arg_string
24  type(mg2_t) :: mg
25  integer :: count_rate,t_start, t_end
26 
27  print *, "Running poisson_benchmark_2d"
28  print *, "Number of threads", af_get_max_threads()
29 
30  ! Get box size and mesh size from command line argument
31  n_args = command_argument_count()
32 
33  if (n_args >= 1) then
34  call get_command_argument(1, arg_string)
35  read(arg_string, *) n_cell
36  else
37  print *, "No arguments specified, using default values"
38  print *, "Usage: ./poisson_benchmark_2d n_cell max_ref_lvl runtime(s)"
39  n_cell = 16
40  end if
41 
42  if (n_args >= 2) then
43  call get_command_argument(2, arg_string)
44  read(arg_string, *) max_ref_lvl
45  else
46  max_ref_lvl = 4
47  end if
48 
49  if (n_args >= 3) then
50  call get_command_argument(3, arg_string)
51  read(arg_string, *) runtime
52  if (runtime < 1e-3_dp) stop "Run time should be > 1e-3 seconds"
53  else
54  runtime = 10
55  end if
56 
57  print *, "Box size: ", n_cell
58  print *, "Max refinement lvl: ", max_ref_lvl
59  print *, "Run time (s): ", runtime
60 
61  dr = 1.0_dp / n_cell
62 
63  ! Initialize tree
64  call a2_init(tree, & ! Tree to initialize
65  n_cell, & ! A box contains box_size**DIM cells
66  n_var_cell, & ! Number of cell-centered variables
67  0, & ! Number of face-centered variables
68  dr, & ! Distance between cells on base level
69  coarsen_to=2, & ! Add coarsened levels for multigrid
70  cc_names=["phi", "rhs", "tmp"]) ! Variable names
71 
72  ! Set up geometry. These indices are used to define the coordinates of a box,
73  ! by default the box at [1,1] touches the origin (x,y) = (0,0)
74  ix_list(:, 1) = [1, 1] ! Set index of box 1
75 
76  ! Create the base mesh, using the box indices and their neighbor information
77  call a2_set_base(tree, 1, ix_list)
78 
79  call system_clock(t_start, count_rate)
80  do
81  ! For each box, set the initial conditions
82  call a2_loop_box(tree, set_init_cond)
83 
84  ! This updates the refinement of the tree, by at most one level per call.
85  ! The second argument is a subroutine that is called for each box that can
86  ! be refined or derefined, and it should set refinement flags. Information
87  ! about the changes in refinement are returned in the third argument.
88  call a2_adjust_refinement(tree, ref_routine, ref_info)
89 
90  ! If no new boxes have been added, exit the loop
91  if (ref_info%n_add == 0) exit
92  end do
93  call system_clock(t_end, count_rate)
94 
95  write(*,"(A,Es10.3,A)") " Wall-clock time generating AMR grid: ", &
96  (t_end-t_start) / real(count_rate,dp), " seconds"
97 
98  call a2_print_info(tree)
99 
100  ! Set the multigrid options.
101  mg%i_phi = i_phi ! Solution variable
102  mg%i_rhs = i_rhs ! Right-hand side variable
103  mg%i_tmp = i_tmp ! Variable for temporary space
104  mg%sides_bc => a2_bc_dirichlet_zero ! Method for boundary conditions
105 
106  ! Initialize the multigrid options. This performs some basics checks and sets
107  ! default values where necessary.
108  ! This routine does not initialize the multigrid variables i_phi, i_rhs
109  ! and i_tmp. These variables will be initialized at the first call of mg2_fas_fmg
110  call mg2_init_mg(mg)
111 
112  ! Warm-up call
113  call mg2_fas_fmg(tree, mg, .false., mg_iter>1)
114 
115  ! Test how long cycles take to determine the number of cycles
116  n_iterations = 1000
117  call system_clock(t_start, count_rate)
118  do mg_iter = 1, n_iterations
119  call mg2_fas_fmg(tree, mg, .false., mg_iter>1)
120  call system_clock(t_end, count_rate)
121  time = (t_end-t_start) / real(count_rate, dp)
122  if (time > 0.2_dp * runtime) exit
123  end do
124 
125  n_iterations = ceiling((runtime/time) * mg_iter)
126 
127  ! Do the actual benchmarking
128  call system_clock(t_start, count_rate)
129  do mg_iter = 1, n_iterations
130  ! Perform a FAS-FMG cycle (full approximation scheme, full multigrid). The
131  ! third argument controls whether the residual is stored in i_tmp. The
132  ! fourth argument controls whether to improve the current solution.
133  call mg2_fas_fmg(tree, mg, .false., mg_iter>1)
134 
135  ! This uses a V-cycle instead of an FMG-cycle
136  ! call mg2_fas_vcycle(tree, mg, .false.)
137 
138  ! If uncommented, this writes Silo output files containing the
139  ! cell-centered values of the leaves of the tree
140  ! write(fname, "(A,I0)") "poisson_benchmark_2d_", mg_iter
141  ! call a2_write_silo(tree, trim(fname), dir="output")
142  end do
143  call system_clock(t_end, count_rate)
144 
145  time = (t_end-t_start) / real(count_rate, dp)
146  write(*, "(A,I0,A,E10.3,A)") &
147  " Wall-clock time after ", n_iterations, &
148  " iterations: ", time, " seconds"
149  write(*, "(A,E10.3,A)") " Per iteration: ", time/n_iterations, " seconds"
150 
151  ! This writes a Silo output file containing the cell-centered values of the
152  ! leaves of the tree (the boxes not covered by refinement).
153  ! fname = "poisson_benchmark_2d"
154  ! call a2_write_silo(tree, trim(fname), dir="output")
155 
156  ! This call is not really necessary here, but cleaning up the data in a tree
157  ! is important if your program continues with other tasks.
158  call a2_destroy(tree)
159 
160 contains
161 
162  ! Set refinement flags for box
163  subroutine ref_routine(box, cell_flags)
164  type(box2_t), intent(in) :: box ! A list of all boxes in the tree
165  integer, intent(out) :: cell_flags(box%n_cell, box%n_cell)
166 
167  ! Fully refine up to max_ref_lvl
168  if (box%lvl < max_ref_lvl) then
169  cell_flags = af_do_ref
170  else
171  cell_flags = af_keep_ref
172  end if
173  end subroutine ref_routine
174 
175  ! This routine sets the initial conditions for each box
176  subroutine set_init_cond(box)
177  type(box2_t), intent(inout) :: box
178  integer :: nc
179 
180  nc = box%n_cell
181  box%cc(1:nc, 1:nc, i_rhs) = 1.0_dp
182  end subroutine set_init_cond
183 
184 end program poisson_benchmark_2d