Afivo  0.3
m_a3_output.f90
1 
4 module m_a3_output
5 
6  use m_a3_types
7 
8  implicit none
9  private
10 
11  abstract interface
12  subroutine subr_add_vars(box, new_vars, n_var)
13  import
14  type(box3_t), intent(in) :: box
15  integer, intent(in) :: n_var
16  real(dp) :: new_vars(0:box%n_cell+1, 0:box%n_cell+1, &
17  0:box%n_cell+1, n_var)
18  end subroutine subr_add_vars
19  end interface
20 
21  public :: a3_prepend_directory
22  public :: a3_write_tree
23  public :: a3_read_tree
24  public :: a3_tree_copy_variable
25  public :: a3_write_vtk
26  public :: a3_write_silo
27  public :: a3_write_line
28  public :: a3_write_plane
29 
30 contains
31 
32  subroutine a3_prepend_directory(filename, dir, out_name)
33  character(len=*), intent(in) :: filename
34  character(len=*), optional, intent(in) :: dir
35  character(len=*), intent(inout) :: out_name
36  integer :: i
37 
38  ! Construct file name
39  if (present(dir)) then
40  i = len_trim(dir)
41  if (i > 0) then
42  if (dir(i:i) == "/") then ! Dir has trailing slash
43  out_name = trim(dir) // trim(filename)
44  else
45  out_name = trim(dir) // "/" // trim(filename)
46  end if
47  end if
48  else
49  out_name = filename
50  end if
51  end subroutine a3_prepend_directory
52 
54  subroutine a3_write_tree(tree, filename, dir)
55  type(a3_t), intent(in) :: tree
56  character(len=*), intent(in) :: filename
57  character(len=*), optional, intent(in) :: dir
58  integer :: my_unit, lvl, id
59  character(len=400) :: fname
60 
61  call a3_prepend_directory(trim(filename) // ".dat", dir, fname)
62 
63  open(newunit=my_unit, file=trim(fname), form='unformatted', &
64  access='stream', status='replace')
65 
66  write(my_unit) tree%ready
67  write(my_unit) tree%lvl_limit
68  write(my_unit) tree%box_limit
69  write(my_unit) tree%highest_lvl
70  write(my_unit) tree%highest_id
71  write(my_unit) tree%n_cell
72  write(my_unit) tree%n_var_cell
73  write(my_unit) tree%n_var_face
74  write(my_unit) tree%coord_t
75  write(my_unit) tree%r_base(:)
76  write(my_unit) tree%dr_base
77 
78  write(my_unit) tree%cc_names(:)
79  write(my_unit) tree%fc_names(:)
80 
81  write(my_unit) lbound(tree%lvls, 1) ! Will become 1 in future
82 
83  do lvl = lbound(tree%lvls, 1), tree%highest_lvl
84  write(my_unit) size(tree%lvls(lvl)%ids)
85  write(my_unit) tree%lvls(lvl)%ids
86 
87  write(my_unit) size(tree%lvls(lvl)%leaves)
88  write(my_unit) tree%lvls(lvl)%leaves
89 
90  write(my_unit) size(tree%lvls(lvl)%parents)
91  write(my_unit) tree%lvls(lvl)%parents
92  end do
93 
94  do id = 1, tree%highest_id
95  write(my_unit) tree%boxes(id)%in_use
96  if (.not. tree%boxes(id)%in_use) cycle
97 
98  write(my_unit) tree%boxes(id)%n_cell
99  write(my_unit) tree%boxes(id)%lvl
100  write(my_unit) tree%boxes(id)%tag
101  write(my_unit) tree%boxes(id)%ix
102  write(my_unit) tree%boxes(id)%parent
103  write(my_unit) tree%boxes(id)%children
104  write(my_unit) tree%boxes(id)%neighbors
105  write(my_unit) tree%boxes(id)%dr
106  write(my_unit) tree%boxes(id)%r_min
107  write(my_unit) tree%boxes(id)%coord_t
108  write(my_unit) tree%boxes(id)%cc
109  write(my_unit) tree%boxes(id)%fc
110  end do
111 
112  close(my_unit)
113  print *, "a3_write_tree: written " // trim(fname)
114  end subroutine a3_write_tree
115 
117  subroutine a3_read_tree(tree, filename)
118  use m_a3_core, only: a3_init_box
119  type(a3_t), intent(out) :: tree
120  character(len=*), intent(in) :: filename
121  integer :: my_unit, lvl, n, id
122 
123  open(newunit=my_unit, file=trim(filename), form='unformatted', &
124  access='stream', status='old', action='read')
125 
126  read(my_unit) tree%ready
127  read(my_unit) tree%lvl_limit
128  read(my_unit) tree%box_limit
129  read(my_unit) tree%highest_lvl
130  read(my_unit) tree%highest_id
131  read(my_unit) tree%n_cell
132  read(my_unit) tree%n_var_cell
133  read(my_unit) tree%n_var_face
134  read(my_unit) tree%coord_t
135  read(my_unit) tree%r_base(:)
136  read(my_unit) tree%dr_base
137 
138  allocate(tree%cc_names(tree%n_var_cell))
139  allocate(tree%fc_names(tree%n_var_face))
140  read(my_unit) tree%cc_names(:)
141  read(my_unit) tree%fc_names(:)
142 
143  read(my_unit) lvl
144  allocate(tree%lvls(lvl:tree%lvl_limit))
145 
146  do lvl = lbound(tree%lvls, 1), tree%highest_lvl
147  read(my_unit) n
148  allocate(tree%lvls(lvl)%ids(n))
149  read(my_unit) tree%lvls(lvl)%ids
150 
151  read(my_unit) n
152  allocate(tree%lvls(lvl)%leaves(n))
153  read(my_unit) tree%lvls(lvl)%leaves
154 
155  read(my_unit) n
156  allocate(tree%lvls(lvl)%parents(n))
157  read(my_unit) tree%lvls(lvl)%parents
158  end do
159 
160  do lvl = tree%highest_lvl+1, tree%lvl_limit
161  allocate(tree%lvls(lvl)%ids(0))
162  allocate(tree%lvls(lvl)%leaves(0))
163  allocate(tree%lvls(lvl)%parents(0))
164  end do
165 
166  allocate(tree%boxes(tree%highest_id))
167 
168  do id = 1, tree%highest_id
169  read(my_unit) tree%boxes(id)%in_use
170  if (.not. tree%boxes(id)%in_use) cycle
171 
172  ! Some boxes can have a different size
173  read(my_unit) tree%boxes(id)%n_cell
174  call a3_init_box(tree%boxes(id), tree%boxes(id)%n_cell, &
175  tree%n_var_cell, tree%n_var_face)
176 
177  read(my_unit) tree%boxes(id)%lvl
178  read(my_unit) tree%boxes(id)%tag
179  read(my_unit) tree%boxes(id)%ix
180  read(my_unit) tree%boxes(id)%parent
181  read(my_unit) tree%boxes(id)%children
182  read(my_unit) tree%boxes(id)%neighbors
183  read(my_unit) tree%boxes(id)%dr
184  read(my_unit) tree%boxes(id)%r_min
185  read(my_unit) tree%boxes(id)%coord_t
186  read(my_unit) tree%boxes(id)%cc
187  read(my_unit) tree%boxes(id)%fc
188  end do
189 
190  close(my_unit)
191  end subroutine a3_read_tree
192 
193  subroutine a3_tree_copy_variable(tree_from, ivs_from, tree_to, ivs_to)
195  type(a3_t), intent(in) :: tree_from
196  integer, intent(in) :: ivs_from(:)
197  type(a3_t), intent(inout) :: tree_to
198  integer, intent(in) :: ivs_to(:)
199  integer :: lvl, id, n, nc, i, j, k
200  real(dp) :: rr(3)
201 
202  !$omp parallel private(lvl, id, n, nc, i, j, k, rr)
203  do lvl = 1, tree_to%highest_lvl
204  !$omp do
205  do n = 1, size(tree_to%lvls(lvl)%leaves)
206  id = tree_to%lvls(lvl)%leaves(n)
207  nc = tree_to%boxes(id)%n_cell
208  do k = 1, nc
209  do j = 1, nc
210  do i = 1, nc
211  rr = a3_r_cc(tree_to%boxes(id), [i, j, k])
212  tree_to%boxes(id)%cc(i, j, k, ivs_to) = &
213  a3_interp1(tree_from, rr, [ivs_from], size(ivs_from))
214  end do
215  end do
216  end do
217  end do
218  !$omp end do
219  end do
220  !$omp end parallel
221 
222  end subroutine a3_tree_copy_variable
223 
225  subroutine a3_write_line(tree, filename, ivs, r_min, r_max, n_points, dir)
226  use m_a3_interp, only: a3_interp1
227  type(a3_t), intent(in) :: tree
228  character(len=*), intent(in) :: filename
229  integer, intent(in) :: ivs(:)
230  real(dp), intent(in) :: r_min(3)
231  real(dp), intent(in) :: r_max(3)
232  integer, intent(in) :: n_points
233  character(len=*), optional, intent(in) :: dir
234 
235  integer, parameter :: my_unit = 100
236  character(len=400) :: fname
237  integer :: i, n_cc
238  real(dp) :: r(3), dr_vec(3)
239  real(dp), allocatable :: line_data(:, :)
240 
241  n_cc = size(ivs)
242  dr_vec = (r_max - r_min) / max(1, n_points-1)
243 
244  allocate(line_data(n_cc+3, n_points))
245 
246  !$omp parallel do private(r)
247  do i = 1, n_points
248  r = r_min + (i-1) * dr_vec
249  line_data(1:3, i) = r
250  line_data(3+1:3+n_cc, i) = a3_interp1(tree, r, ivs, n_cc)
251  end do
252  !$omp end parallel do
253 
254  call a3_prepend_directory(trim(filename) // ".txt", dir, fname)
255 
256  ! Write header
257  open(my_unit, file=trim(fname), action="write")
258  write(my_unit, '(A)', advance="no") "# x y z"
259  do i = 1, n_cc
260  write(my_unit, '(A)', advance="no") " "//trim(tree%cc_names(ivs(i)))
261  end do
262  write(my_unit, '(A)') ""
263 
264  ! Write data
265  do i = 1, n_points
266  write(my_unit, *) line_data(:, i)
267  end do
268 
269  close(my_unit)
270  end subroutine a3_write_line
271 
275  subroutine a3_write_plane(tree, filename, ivs, r_min, r_max, n_pixels, dir)
276  use m_a3_interp, only: a3_interp1
277  type(a3_t), intent(in) :: tree
278  character(len=*), intent(in) :: filename
279  integer, intent(in) :: ivs(:)
280  real(dp), intent(in) :: r_min(3)
281  real(dp), intent(in) :: r_max(3)
282  integer, intent(in) :: n_pixels(2)
283  character(len=*), optional, intent(in) :: dir
284 
285  integer, parameter :: my_unit = 100
286  character(len=100) :: fmt_string
287  character(len=400) :: fname
288  integer :: i, j, n_cc, dim_unused, n_points(3)
289  real(dp) :: r(3), dvec(3)
290  real(dp) :: v1(3), v2(3)
291  real(dp), allocatable :: pixel_data(:, :, :)
292 
293  n_cc = size(ivs)
294  dvec = r_max - r_min
295  dim_unused = minloc(abs(dvec), 1)
296 
297  select case (dim_unused)
298  case (1)
299  v1 = [0.0_dp, dvec(2), 0.0_dp] / (n_pixels(1) - 1)
300  v2 = [0.0_dp, 0.0_dp, dvec(3)] / (n_pixels(2) - 1)
301  n_points = [1, n_pixels(1), n_pixels(2)]
302  case (2)
303  v1 = [dvec(1), 0.0_dp, 0.0_dp] / (n_pixels(1) - 1)
304  v2 = [0.0_dp, 0.0_dp, dvec(3)] / (n_pixels(2) - 1)
305  n_points = [n_pixels(1), 1, n_pixels(2)]
306  case (3)
307  v1 = [dvec(1), 0.0_dp, 0.0_dp] / (n_pixels(1) - 1)
308  v2 = [0.0_dp, dvec(2), 0.0_dp] / (n_pixels(2) - 1)
309  n_points = [n_pixels(1), n_pixels(2), 1]
310  end select
311 
312  allocate(pixel_data(n_cc, n_pixels(1), n_pixels(2)))
313 
314  !$omp parallel do private(i, r)
315  do j = 1, n_pixels(2)
316  do i = 1, n_pixels(1)
317  r = r_min + (i-1) * v1 + (j-1) * v2
318  pixel_data(:, i, j) = a3_interp1(tree, r, ivs, n_cc)
319  end do
320  end do
321  !$omp end parallel do
322 
323  ! Construct format string. Write one row at a time
324  write(fmt_string, '(A,I0,A)') '(', n_pixels(1), 'E16.8)'
325 
326  ! Construct file name
327  call a3_prepend_directory(trim(filename) // ".vtk", dir, fname)
328 
329  open(my_unit, file=trim(fname), action="write")
330  write(my_unit, '(A)') "# vtk DataFile Version 2.0"
331  write(my_unit, '(A)') trim(filename)
332  write(my_unit, '(A)') "ASCII"
333  write(my_unit, '(A)') "DATASET STRUCTURED_POINTS"
334  write(my_unit, '(A,3I10)') "DIMENSIONS ", n_points
335  write(my_unit, '(A,3E16.8)') "ORIGIN ", r_min
336  write(my_unit, '(A,3E16.8)') "SPACING ", v1 + v2
337  write(my_unit, '(A,2I0)') "POINT_DATA ", product(n_points)
338  do i = 1, n_cc
339  write(my_unit, '(A)') "SCALARS " // &
340  trim(tree%cc_names(ivs(i))) // " double 1"
341  write(my_unit, '(A)') "LOOKUP_TABLE default"
342  write(my_unit, trim(fmt_string)) pixel_data(i, :, :)
343  end do
344  close(my_unit)
345  end subroutine a3_write_plane
346 
349  subroutine a3_write_vtk(tree, filename, n_cycle, time, ixs_cc, dir, &
350  add_vars, add_names)
351  use m_vtk
352 
353  type(a3_t), intent(in) :: tree
354  character(len=*), intent(in) :: filename
355  integer, intent(in), optional :: n_cycle
356  real(dp), intent(in), optional :: time
357  integer, intent(in), optional :: ixs_cc(:)
358  character(len=*), optional, intent(in) :: dir
359  procedure(subr_add_vars), optional :: add_vars
360  character(len=*), intent(in), optional :: add_names(:)
361 
362  integer :: lvl, bc, bn, n, n_cells, n_nodes
363  integer :: ig, i, j, id, n_ix, c_ix, n_grids
364  integer :: cell_ix, node_ix, n_cycle_val
365  integer :: n_cc, n_add
366  integer, parameter :: n_ch = a3_num_children
367  integer :: nodes_per_box, cells_per_box
368  real(dp) :: time_val
369  real(dp), allocatable :: coords(:), cc_vars(:,:)
370  integer, allocatable :: offsets(:), connects(:)
371  integer, allocatable :: cell_types(:), icc_val(:)
372  type(vtk_t) :: vtkf
373  character(len=400) :: fname
374  character(len=100), allocatable :: var_names(:)
375  real(dp), allocatable :: cc(:, :, :, :)
376  integer :: k, bn2
377 
378  if (.not. tree%ready) stop "Tree not ready"
379  time_val = 0.0_dp; if (present(time)) time_val = time
380  n_cycle_val = 0; if (present(n_cycle)) n_cycle_val = n_cycle
381  n_add = 0; if (present(add_names)) n_add = size(add_names)
382 
383  if (present(add_names) .neqv. present(add_vars)) &
384  stop "a3_write_vtk: both arguments (add_names, add_vars) needed"
385 
386  if (present(ixs_cc)) then
387  if (maxval(ixs_cc) > tree%n_var_cell .or. &
388  minval(ixs_cc) < 1) stop "a3_write_vtk: wrong indices given (ixs_cc)"
389  icc_val = ixs_cc
390  else
391  icc_val = [(i, i = 1, tree%n_var_cell)]
392  end if
393 
394  n_cc = size(icc_val)
395 
396  allocate(var_names(n_cc+n_add))
397  var_names(1:n_cc) = tree%cc_names(icc_val)
398 
399  if (present(add_names)) then
400  var_names(n_cc+1:n_cc+n_add) = add_names(:)
401  end if
402 
403  bc = tree%n_cell ! number of Box Cells
404  bn = tree%n_cell + 1 ! number of Box Nodes
405  nodes_per_box = bn**3
406  cells_per_box = bc**3
407 
408  allocate(cc(0:bc+1, 0:bc+1, 0:bc+1, n_cc + n_add))
409 
410  n_grids = 0
411  do lvl = 1, tree%highest_lvl
412  n_grids = n_grids + size(tree%lvls(lvl)%leaves)
413  end do
414  n_nodes = nodes_per_box * n_grids
415  n_cells = cells_per_box * n_grids
416 
417  allocate(coords(3 * n_nodes))
418  allocate(cc_vars(n_cells, n_cc+n_add))
419  allocate(offsets(cells_per_box * n_grids))
420  allocate(cell_types(cells_per_box * n_grids))
421  allocate(connects(n_ch * cells_per_box * n_grids))
422 
423  bn2 = bn**2
424  cell_types = 11 ! VTK voxel type
425 
426  ig = 0
427  do lvl = 1, tree%highest_lvl
428  do n = 1, size(tree%lvls(lvl)%leaves)
429  id = tree%lvls(lvl)%leaves(n)
430  ig = ig + 1
431  cell_ix = (ig-1) * cells_per_box
432  node_ix = (ig-1) * nodes_per_box
433 
434  cc(:, :, :, 1:n_cc) = tree%boxes(id)%cc(:, :, :, icc_val)
435 
436  if (present(add_vars)) then
437  call add_vars(tree%boxes(id), &
438  cc(:, :, :, n_cc+1:n_cc+n_add), n_add)
439  end if
440 
441  do k = 1, bn
442  do j = 1, bn
443  do i = 1, bn
444  n_ix = 3 * (node_ix + (k-1) * bn2 + (j-1) * bn + i)
445  coords(n_ix-2:n_ix) = tree%boxes(id)%r_min + &
446  [i-1,j-1,k-1] * tree%boxes(id)%dr
447  end do
448  end do
449  end do
450 
451  do k = 1, bc
452  do j = 1, bc
453  do i = 1, bc
454  ! In vtk, indexing starts at 0, so subtract 1
455  n_ix = node_ix + (k-1) * bn2 + &
456  (j-1) * bn + i - 1
457  c_ix = cell_ix + (k-1) * bc**2 + &
458  (j-1) * bc + i
459  cc_vars(c_ix, :) = cc(i, j, k, :)
460  offsets(c_ix) = 8 * c_ix
461  connects(n_ch*(c_ix-1)+1:n_ch*c_ix) = &
462  [n_ix, n_ix+1, n_ix+bn, n_ix+bn+1, &
463  n_ix+bn2, n_ix+bn2+1, n_ix+bn2+bn, n_ix+bn2+bn+1]
464  end do
465  end do
466  end do
467  end do
468  end do
469 
470  call a3_prepend_directory(trim(filename) // ".vtu", dir, fname)
471 
472  call vtk_ini_xml(vtkf, trim(fname), 'UnstructuredGrid')
473  call vtk_dat_xml(vtkf, "UnstructuredGrid", .true.)
474  call vtk_unstr_geo_xml(vtkf, coords, n_nodes, n_cells, 3, n_cycle_val, time_val)
475  call vtk_unstr_con_xml(vtkf, connects, offsets, cell_types, n_cells)
476  call vtk_dat_xml(vtkf, "CellData", .true.)
477 
478  do n = 1, n_cc + n_add
479  call vtk_var_r8_xml(vtkf, trim(var_names(n)), cc_vars(:, n), n_cells)
480  end do
481 
482  call vtk_dat_xml(vtkf, "CellData", .false.)
483  call vtk_unstr_geo_xml_close(vtkf)
484  call vtk_dat_xml(vtkf, "UnstructuredGrid", .false.)
485  call vtk_end_xml(vtkf)
486  print *, "a3_write_vtk: written " // trim(fname)
487  end subroutine a3_write_vtk
488 
491  subroutine a3_write_silo(tree, filename, n_cycle, time, ixs_cc, dir, &
492  add_vars, add_names)
494 
495  type(a3_t), intent(in) :: tree
496  character(len=*) :: filename
497  integer, intent(in), optional :: n_cycle
498  real(dp), intent(in), optional :: time
499  integer, intent(in), optional :: ixs_cc(:)
500  character(len=*), optional, intent(in) :: dir
501  procedure(subr_add_vars), optional :: add_vars
502  character(len=*), intent(in), optional :: add_names(:)
503 
504  character(len=*), parameter :: grid_name = "gg", block_prefix = "blk_"
505  character(len=*), parameter :: amr_name = "mesh", meshdir = "data"
506  character(len=100), allocatable :: grid_list(:), grid_list_block(:)
507  character(len=100), allocatable :: var_list(:, :), var_names(:)
508  character(len=400) :: fname
509  integer :: lvl, i, id, i_grid, iv, nc, n_grids_max
510  integer :: n_cc, n_add, dbix
511  integer :: nx, ny, nx_prev, ny_prev, ix, iy
512  integer :: n_cycle_val
513  integer :: lo(3), hi(3), vlo(3), vhi(3)
514  integer :: blo(3), bhi(3)
515  logical :: lo_bnd(3), hi_bnd(3)
516  integer, allocatable :: ids(:), nb_ids(:), icc_val(:)
517  logical, allocatable :: box_done(:)
518  real(dp) :: dr(3), r_min(3), time_val
519  integer, allocatable :: box_list(:,:,:), new_box_list(:,:,:)
520  real(dp), allocatable :: var_data(:,:,:,:), cc(:, :, :, :)
521  integer :: nz, nz_prev, iz
522 
523  if (.not. tree%ready) stop "Tree not ready"
524  time_val = 0.0_dp; if (present(time)) time_val = time
525  n_cycle_val = 0; if (present(n_cycle)) n_cycle_val = n_cycle
526  n_add = 0; if (present(add_names)) n_add = size(add_names)
527 
528  if (present(add_names) .neqv. present(add_vars)) &
529  stop "a3_write_vtk: both arguments (add_names, add_vars) needed"
530 
531  if (present(ixs_cc)) then
532  if (maxval(ixs_cc) > tree%n_var_cell .or. &
533  minval(ixs_cc) < 1) stop "a3_write_silo: wrong indices given (ixs_cc)"
534  icc_val = ixs_cc
535  else
536  icc_val = [(i, i = 1, tree%n_var_cell)]
537  end if
538 
539  n_cc = size(icc_val)
540 
541  allocate(var_names(n_cc+n_add))
542  var_names(1:n_cc) = tree%cc_names(icc_val)
543 
544  if (present(add_names)) then
545  var_names(n_cc+1:n_cc+n_add) = add_names(:)
546  end if
547 
548  nc = tree%n_cell
549  n_grids_max = 0
550  do lvl = 1, tree%highest_lvl
551  n_grids_max = n_grids_max + size(tree%lvls(lvl)%leaves)
552  end do
553 
554  allocate(grid_list(n_grids_max))
555  allocate(grid_list_block(n_grids_max))
556  allocate(var_list(n_cc+n_add, n_grids_max))
557  allocate(box_done(tree%highest_id))
558  box_done = .false.
559 
560  allocate(cc(0:nc+1, 0:nc+1, 0:nc+1, n_cc + n_add))
561 
562  call a3_prepend_directory(trim(filename) // ".silo", dir, fname)
563  call silo_create_file(trim(fname), dbix)
564  call silo_set_time_varying(dbix)
565  call silo_mkdir(dbix, meshdir)
566  i_grid = 0
567 
568  do lvl = 1, tree%highest_lvl
569  do i = 1, size(tree%lvls(lvl)%leaves)
570  id = tree%lvls(lvl)%leaves(i)
571  if (box_done(id)) cycle
572 
573  i_grid = i_grid + 1
574 
575  ! Find largest rectangular box including id and other leaves that
576  ! haven't been written yet
577  allocate(box_list(1,1,1))
578  box_list(1,1,1) = id
579  nx = 1
580  ny = 1
581  nz = 1
582 
583  do
584  nx_prev = nx
585  ny_prev = ny
586  nz_prev = nz
587 
588  ! Check whether we can extend to the -x direction
589  ids = pack(box_list(1, :, :), .true.)
590  nb_ids = tree%boxes(ids)%neighbors(a3_neighb_lowx)
591  if (all(nb_ids > af_no_box)) then
592  if (.not. any(box_done(nb_ids)) .and. &
593  tree%boxes(nb_ids(1))%ix(1) < tree%boxes(ids(1))%ix(1) .and. &
594  .not. any(a3_has_children(tree%boxes(nb_ids)))) then
595  nx = nx + 1
596  allocate(new_box_list(nx, ny, nz))
597  new_box_list(1, :, :) = reshape(nb_ids, [ny, nz])
598  new_box_list(2:, :, :) = box_list
599  box_list = new_box_list
600  box_done(nb_ids) = .true.
601  deallocate(new_box_list)
602  end if
603  end if
604 
605  ! Check whether we can extend to the +x direction
606  ids = pack(box_list(nx, :, :), .true.)
607  nb_ids = tree%boxes(ids)%neighbors(a3_neighb_highx)
608  if (all(nb_ids > af_no_box)) then
609  if (.not. any(box_done(nb_ids)) .and. &
610  tree%boxes(nb_ids(1))%ix(1) > tree%boxes(ids(1))%ix(1) .and. &
611  .not. any(a3_has_children(tree%boxes(nb_ids)))) then
612  nx = nx + 1
613  allocate(new_box_list(nx, ny, nz))
614  new_box_list(nx, :, :) = reshape(nb_ids, [ny, nz])
615  new_box_list(1:nx-1, :, :) = box_list
616  box_list = new_box_list
617  box_done(nb_ids) = .true.
618  deallocate(new_box_list)
619  end if
620  end if
621 
622  ! Check whether we can extend to the -y direction
623  ids = pack(box_list(:, 1, :), .true.)
624  nb_ids = tree%boxes(ids)%neighbors(a3_neighb_lowy)
625  if (all(nb_ids > af_no_box)) then
626  if (.not. any(box_done(nb_ids)) .and. &
627  tree%boxes(nb_ids(1))%ix(2) < tree%boxes(ids(1))%ix(2) .and. &
628  .not. any(a3_has_children(tree%boxes(nb_ids)))) then
629  ny = ny + 1
630  allocate(new_box_list(nx, ny, nz))
631  new_box_list(:, 1, :) = reshape(nb_ids, [nx, nz])
632  new_box_list(:, 2:, :) = box_list
633  box_list = new_box_list
634  box_done(nb_ids) = .true.
635  deallocate(new_box_list)
636  end if
637  end if
638 
639  ! Check whether we can extend to the +y direction
640  ids = pack(box_list(:, ny, :), .true.)
641  nb_ids = tree%boxes(ids)%neighbors(a3_neighb_highy)
642  if (all(nb_ids > af_no_box)) then
643  if (.not. any(box_done(nb_ids)) .and. &
644  tree%boxes(nb_ids(1))%ix(2) > tree%boxes(ids(1))%ix(2) .and. &
645  .not. any(a3_has_children(tree%boxes(nb_ids)))) then
646  ny = ny + 1
647  allocate(new_box_list(nx, ny, nz))
648  new_box_list(:, ny, :) = reshape(nb_ids, [nx, nz])
649  new_box_list(:, 1:ny-1, :) = box_list
650  box_list = new_box_list
651  box_done(nb_ids) = .true.
652  deallocate(new_box_list)
653  end if
654  end if
655 
656  ! Check whether we can extend to the -z direction
657  ids = pack(box_list(:, :, 1), .true.)
658  nb_ids = tree%boxes(ids)%neighbors(a3_neighb_lowz)
659  if (all(nb_ids > af_no_box)) then
660  if (.not. any(box_done(nb_ids)) .and. &
661  tree%boxes(nb_ids(1))%ix(3) < tree%boxes(ids(1))%ix(3) .and. &
662  .not. any(a3_has_children(tree%boxes(nb_ids)))) then
663  nz = nz + 1
664  allocate(new_box_list(nx, ny, nz))
665  new_box_list(:, :, 1) = reshape(nb_ids, [nx, ny])
666  new_box_list(:, :, 2:) = box_list
667  box_list = new_box_list
668  box_done(nb_ids) = .true.
669  deallocate(new_box_list)
670  end if
671  end if
672 
673  ! Check whether we can extend to the +z direction
674  ids = pack(box_list(:, :, nz), .true.)
675  nb_ids = tree%boxes(ids)%neighbors(a3_neighb_highz)
676  if (all(nb_ids > af_no_box)) then
677  if (.not. any(box_done(nb_ids)) .and. &
678  tree%boxes(nb_ids(1))%ix(3) > tree%boxes(ids(1))%ix(3) .and. &
679  .not. any(a3_has_children(tree%boxes(nb_ids)))) then
680  nz = nz + 1
681  allocate(new_box_list(nx, ny, nz))
682  new_box_list(:, :, nz) = reshape(nb_ids, [nx, ny])
683  new_box_list(:, :, 1:nz-1) = box_list
684  box_list = new_box_list
685  box_done(nb_ids) = .true.
686  deallocate(new_box_list)
687  end if
688  end if
689 
690  if (nx == nx_prev .and. ny == ny_prev .and. nz == nz_prev) exit
691  end do
692 
693  ! Check for (periodic) boundaries (this could give problems for
694  ! complex geometries, e.g. a triangle block)
695  id = box_list(1, 1, 1)
696  lo_bnd = a3_phys_boundary(tree%boxes, id, a3_low_neighbs)
697 
698  id = box_list(nx, ny, nz)
699  hi_bnd = a3_phys_boundary(tree%boxes, id, a3_high_neighbs)
700 
701  lo(:) = 1
702  where (.not. lo_bnd) lo = lo - 1
703 
704  hi = [nx, ny, nz] * nc
705  where (.not. hi_bnd) hi = hi + 1
706 
707  ! Include ghost cells around internal boundaries
708  allocate(var_data(lo(1):hi(1), lo(2):hi(2), lo(3):hi(3), n_cc+n_add))
709 
710  do iz = 1, nz
711  do ix = 1, nx
712  do iy = 1, ny
713  id = box_list(ix, iy, iz)
714  cc(:, :, :, 1:n_cc) = tree%boxes(id)%cc(:, :, :, icc_val)
715  if (present(add_vars)) then
716  call add_vars(tree%boxes(id), &
717  cc(:, :, :, n_cc+1:n_cc+n_add), n_add)
718  end if
719 
720  ! Include ghost cells on internal block boundaries
721  blo = 1
722  where ([ix, iy, iz] == 1 .and. .not. lo_bnd) blo = 0
723 
724  bhi = nc
725  where ([ix, iy, iz] == [nx, ny, nz] &
726  .and. .not. hi_bnd) bhi = nc+1
727 
728  vlo = blo + ([ix, iy, iz]-1) * nc
729  vhi = bhi + ([ix, iy, iz]-1) * nc
730 
731  var_data(vlo(1):vhi(1), vlo(2):vhi(2), vlo(3):vhi(3), :) = &
732  cc(blo(1):bhi(1), blo(2):bhi(2), blo(3):bhi(3), :)
733  end do
734  end do
735  end do
736 
737  id = box_list(1, 1, 1)
738  dr = tree%boxes(id)%dr
739  r_min = tree%boxes(id)%r_min - (1 - lo) * dr
740 
741  write(grid_list(i_grid), "(A,I0)") meshdir // '/' // grid_name, i_grid
742  call silo_add_grid(dbix, grid_list(i_grid), 3, &
743  hi - lo + 2, r_min, dr, 1-lo, hi-[nx, ny, nz]*nc)
744  write(grid_list_block(i_grid), "(A,I0)") meshdir // '/' // block_prefix // &
745  grid_name, i_grid
746  call silo_add_grid(dbix, grid_list_block(i_grid), 3, [nx+1, ny+1, nz+1], &
747  tree%boxes(id)%r_min, nc*dr, [0, 0, 0], [0, 0, 0])
748 
749  do iv = 1, n_cc+n_add
750  write(var_list(iv, i_grid), "(A,I0)") meshdir // '/' // &
751  trim(var_names(iv)) // "_", i_grid
752  call silo_add_var(dbix, var_list(iv, i_grid), grid_list(i_grid), &
753  pack(var_data(:, :, :, iv), .true.), hi-lo+1)
754  end do
755 
756  deallocate(var_data)
757  deallocate(box_list)
758 
759  end do
760  end do
761 
762  call silo_set_mmesh_grid(dbix, amr_name, grid_list(1:i_grid), &
763  n_cycle_val, time_val)
764  do iv = 1, n_cc+n_add
765  call silo_set_mmesh_var(dbix, trim(var_names(iv)), amr_name, &
766  var_list(iv, 1:i_grid), n_cycle_val, time_val)
767  end do
768 
769  call silo_set_mmesh_grid(dbix, block_prefix // amr_name, &
770  grid_list_block(1:i_grid), n_cycle_val, time_val)
771  call silo_close_file(dbix)
772  print *, "a3_write_silo: written " // trim(fname)
773  end subroutine a3_write_silo
774 
775 end module m_a3_output
This module contains routines for writing output files with Afivo. The Silo format should probably be...
Definition: m_a3_output.f90:4
This module contains wrapper functions to simplify writing Silo files.
Definition: m_write_silo.f90:3
The basic building block of afivo: a box with cell-centered and face centered data, and information about its position, neighbors, children etc.
Definition: m_a3_types.f90:109
This file is a modification of code found in Lib_VTK_IO.
Definition: m_vtk.f90:9
Type which stores all the boxes and levels, as well as some information about the number of boxes...
Definition: m_a3_types.f90:131
This module contains the core routines of Afivo, namely those that deal with initializing and changin...
Definition: m_a3_core.f90:4
This module contains routines related to interpolation, which can interpolate &#39;to&#39; the grid and &#39;from...
Definition: m_a3_interp.f90:5
This module contains the basic types and constants that are used in the 3-dimensional version of Afiv...
Definition: m_a3_types.f90:5