12 subroutine subr_add_vars(box, new_vars, n_var)
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
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
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
39 if (
present(dir))
then 42 if (dir(i:i) ==
"/")
then 43 out_name = trim(dir) // trim(filename)
45 out_name = trim(dir) //
"/" // trim(filename)
51 end subroutine a3_prepend_directory
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
61 call a3_prepend_directory(trim(filename) //
".dat", dir, fname)
63 open(newunit=my_unit, file=trim(fname), form=
'unformatted', &
64 access=
'stream', status=
'replace')
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
78 write(my_unit) tree%cc_names(:)
79 write(my_unit) tree%fc_names(:)
81 write(my_unit) lbound(tree%lvls, 1)
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
87 write(my_unit)
size(tree%lvls(lvl)%leaves)
88 write(my_unit) tree%lvls(lvl)%leaves
90 write(my_unit)
size(tree%lvls(lvl)%parents)
91 write(my_unit) tree%lvls(lvl)%parents
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
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
113 print *,
"a3_write_tree: written " // trim(fname)
114 end subroutine a3_write_tree
117 subroutine a3_read_tree(tree, filename)
119 type(
a3_t),
intent(out) :: tree
120 character(len=*),
intent(in) :: filename
121 integer :: my_unit, lvl, n, id
123 open(newunit=my_unit, file=trim(filename), form=
'unformatted', &
124 access=
'stream', status=
'old', action=
'read')
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
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(:)
144 allocate(tree%lvls(lvl:tree%lvl_limit))
146 do lvl = lbound(tree%lvls, 1), tree%highest_lvl
148 allocate(tree%lvls(lvl)%ids(n))
149 read(my_unit) tree%lvls(lvl)%ids
152 allocate(tree%lvls(lvl)%leaves(n))
153 read(my_unit) tree%lvls(lvl)%leaves
156 allocate(tree%lvls(lvl)%parents(n))
157 read(my_unit) tree%lvls(lvl)%parents
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))
166 allocate(tree%boxes(tree%highest_id))
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
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)
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
191 end subroutine a3_read_tree
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
203 do lvl = 1, tree_to%highest_lvl
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
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))
222 end subroutine a3_tree_copy_variable
225 subroutine a3_write_line(tree, filename, ivs, r_min, r_max, n_points, dir)
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
235 integer,
parameter :: my_unit = 100
236 character(len=400) :: fname
238 real(dp) :: r(3), dr_vec(3)
239 real(dp),
allocatable :: line_data(:, :)
242 dr_vec = (r_max - r_min) / max(1, n_points-1)
244 allocate(line_data(n_cc+3, 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)
254 call a3_prepend_directory(trim(filename) //
".txt", dir, fname)
257 open(my_unit, file=trim(fname), action=
"write")
258 write(my_unit,
'(A)', advance=
"no")
"# x y z" 260 write(my_unit,
'(A)', advance=
"no")
" "//trim(tree%cc_names(ivs(i)))
262 write(my_unit,
'(A)')
"" 266 write(my_unit, *) line_data(:, i)
270 end subroutine a3_write_line
275 subroutine a3_write_plane(tree, filename, ivs, r_min, r_max, n_pixels, dir)
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
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(:, :, :)
295 dim_unused = minloc(abs(dvec), 1)
297 select case (dim_unused)
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)]
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)]
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]
312 allocate(pixel_data(n_cc, n_pixels(1), n_pixels(2)))
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)
324 write(fmt_string,
'(A,I0,A)')
'(', n_pixels(1),
'E16.8)' 327 call a3_prepend_directory(trim(filename) //
".vtk", dir, fname)
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)
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, :, :)
345 end subroutine a3_write_plane
349 subroutine a3_write_vtk(tree, filename, n_cycle, time, ixs_cc, dir, &
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(:)
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
369 real(dp),
allocatable :: coords(:), cc_vars(:,:)
370 integer,
allocatable :: offsets(:), connects(:)
371 integer,
allocatable :: cell_types(:), icc_val(:)
373 character(len=400) :: fname
374 character(len=100),
allocatable :: var_names(:)
375 real(dp),
allocatable :: cc(:, :, :, :)
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)
383 if (
present(add_names) .neqv.
present(add_vars)) &
384 stop
"a3_write_vtk: both arguments (add_names, add_vars) needed" 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)" 391 icc_val = [(i, i = 1, tree%n_var_cell)]
396 allocate(var_names(n_cc+n_add))
397 var_names(1:n_cc) = tree%cc_names(icc_val)
399 if (
present(add_names))
then 400 var_names(n_cc+1:n_cc+n_add) = add_names(:)
405 nodes_per_box = bn**3
406 cells_per_box = bc**3
408 allocate(cc(0:bc+1, 0:bc+1, 0:bc+1, n_cc + n_add))
411 do lvl = 1, tree%highest_lvl
412 n_grids = n_grids +
size(tree%lvls(lvl)%leaves)
414 n_nodes = nodes_per_box * n_grids
415 n_cells = cells_per_box * n_grids
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))
427 do lvl = 1, tree%highest_lvl
428 do n = 1,
size(tree%lvls(lvl)%leaves)
429 id = tree%lvls(lvl)%leaves(n)
431 cell_ix = (ig-1) * cells_per_box
432 node_ix = (ig-1) * nodes_per_box
434 cc(:, :, :, 1:n_cc) = tree%boxes(id)%cc(:, :, :, icc_val)
436 if (
present(add_vars))
then 437 call add_vars(tree%boxes(id), &
438 cc(:, :, :, n_cc+1:n_cc+n_add), n_add)
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
455 n_ix = node_ix + (k-1) * bn2 + &
457 c_ix = cell_ix + (k-1) * bc**2 + &
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]
470 call a3_prepend_directory(trim(filename) //
".vtu", dir, fname)
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.)
478 do n = 1, n_cc + n_add
479 call vtk_var_r8_xml(vtkf, trim(var_names(n)), cc_vars(:, n), n_cells)
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
491 subroutine a3_write_silo(tree, filename, n_cycle, time, ixs_cc, dir, &
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(:)
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
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)
528 if (
present(add_names) .neqv.
present(add_vars)) &
529 stop
"a3_write_vtk: both arguments (add_names, add_vars) needed" 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)" 536 icc_val = [(i, i = 1, tree%n_var_cell)]
541 allocate(var_names(n_cc+n_add))
542 var_names(1:n_cc) = tree%cc_names(icc_val)
544 if (
present(add_names))
then 545 var_names(n_cc+1:n_cc+n_add) = add_names(:)
550 do lvl = 1, tree%highest_lvl
551 n_grids_max = n_grids_max +
size(tree%lvls(lvl)%leaves)
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))
560 allocate(cc(0:nc+1, 0:nc+1, 0:nc+1, n_cc + n_add))
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)
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
577 allocate(box_list(1,1,1))
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 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)
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 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)
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 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)
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 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)
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 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)
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 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)
690 if (nx == nx_prev .and. ny == ny_prev .and. nz == nz_prev)
exit 695 id = box_list(1, 1, 1)
696 lo_bnd = a3_phys_boundary(tree%boxes, id, a3_low_neighbs)
698 id = box_list(nx, ny, nz)
699 hi_bnd = a3_phys_boundary(tree%boxes, id, a3_high_neighbs)
702 where (.not. lo_bnd) lo = lo - 1
704 hi = [nx, ny, nz] * nc
705 where (.not. hi_bnd) hi = hi + 1
708 allocate(var_data(lo(1):hi(1), lo(2):hi(2), lo(3):hi(3), n_cc+n_add))
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)
722 where ([ix, iy, iz] == 1 .and. .not. lo_bnd) blo = 0
725 where ([ix, iy, iz] == [nx, ny, nz] &
726 .and. .not. hi_bnd) bhi = nc+1
728 vlo = blo + ([ix, iy, iz]-1) * nc
729 vhi = bhi + ([ix, iy, iz]-1) * nc
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), :)
737 id = box_list(1, 1, 1)
738 dr = tree%boxes(id)%dr
739 r_min = tree%boxes(id)%r_min - (1 - lo) * dr
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 // &
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])
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)
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)
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
This module contains routines for writing output files with Afivo. The Silo format should probably be...
This module contains wrapper functions to simplify writing Silo files.
The basic building block of afivo: a box with cell-centered and face centered data, and information about its position, neighbors, children etc.
This file is a modification of code found in Lib_VTK_IO.
Type which stores all the boxes and levels, as well as some information about the number of boxes...
This module contains the core routines of Afivo, namely those that deal with initializing and changin...
This module contains routines related to interpolation, which can interpolate 'to' the grid and 'from...
This module contains the basic types and constants that are used in the 3-dimensional version of Afiv...