11 public :: a3_set_cc_methods
16 public :: a3_resize_box_storage
17 public :: a3_adjust_refinement
18 public :: a3_consistent_fluxes
23 subroutine a3_init(tree, n_cell, n_var_cell, n_var_face, dr, r_min, &
24 lvl_limit, n_boxes, coarsen_to, coord, cc_names, fc_names, mem_limit_gb)
25 type(
a3_t),
intent(inout) :: tree
26 integer,
intent(in) :: n_cell
27 integer,
intent(in) :: n_var_cell
28 integer,
intent(in) :: n_var_face
29 real(dp),
intent(in) :: dr
31 real(dp),
intent(in),
optional :: r_min(3)
34 integer,
intent(in),
optional :: coarsen_to
36 integer,
intent(in),
optional :: lvl_limit
38 integer,
intent(in),
optional :: n_boxes
39 integer,
intent(in),
optional :: coord
40 real(dp),
intent(in),
optional :: mem_limit_gb
43 character(len=*),
intent(in),
optional :: cc_names(:)
45 character(len=*),
intent(in),
optional :: fc_names(:)
47 integer :: lvl_limit_a, n_boxes_a, coarsen_to_a
48 real(dp) :: r_min_a(3), gb_limit
49 integer :: n, lvl, min_lvl, coord_a, box_bytes
52 lvl_limit_a = 30;
if (
present(lvl_limit)) lvl_limit_a = lvl_limit
53 n_boxes_a = 1000;
if (
present(n_boxes)) n_boxes_a = n_boxes
54 coarsen_to_a = -1;
if (
present(coarsen_to)) coarsen_to_a = coarsen_to
55 r_min_a = 0.0_dp;
if (
present(r_min)) r_min_a = r_min
56 coord_a = af_xyz;
if (
present(coord)) coord_a = coord
57 gb_limit = 16;
if (
present(mem_limit_gb)) gb_limit = mem_limit_gb
59 if (tree%ready) stop
"a3_init: tree was already initialized" 60 if (n_cell < 2) stop
"a3_init: n_cell should be >= 2" 61 if (btest(n_cell, 0)) stop
"a3_init: n_cell should be even" 62 if (n_var_cell <= 0) stop
"a3_init: n_var_cell should be > 0" 63 if (n_var_face < 0) stop
"a3_init: n_var_face should be >= 0" 64 if (n_boxes_a <= 0) stop
"a3_init: n_boxes should be > 0" 65 if (lvl_limit_a <= 0) stop
"a3_init: lvl_limit should be > 0" 66 if (gb_limit <= 0) stop
"a3_init: mem_limit_gb should be > 0" 67 if (coord_a == af_cyl) stop
"a3_init: cannot have 3d cyl coords" 69 allocate(tree%boxes(n_boxes_a))
71 if (coarsen_to_a > 0)
then 74 min_lvl = 1 - nint(log(
real(n_cell, dp)/coarsen_to_a)/log(2.0_dp))
76 if (2**(1-min_lvl) * coarsen_to_a /= n_cell) &
77 stop
"a3_init: cannot coarsen to given value" 83 allocate(tree%lvls(min_lvl:lvl_limit_a+1))
85 do lvl = min_lvl, lvl_limit_a+1
86 allocate(tree%lvls(lvl)%ids(0))
87 allocate(tree%lvls(lvl)%leaves(0))
88 allocate(tree%lvls(lvl)%parents(0))
92 tree%n_var_cell = n_var_cell
93 tree%n_var_face = n_var_face
96 tree%lvl_limit = lvl_limit_a
99 tree%coord_t = coord_a
102 box_bytes = a3_box_bytes(n_cell, n_var_cell, n_var_face)
103 tree%box_limit = nint(gb_limit * 2.0_dp**30 / box_bytes)
106 allocate(tree%cc_names(n_var_cell))
107 allocate(tree%fc_names(n_var_face))
109 if (
present(cc_names))
then 110 if (
size(cc_names) /= n_var_cell) &
111 stop
"a3_init: size(cc_names) /= n_var_cell" 112 tree%cc_names = cc_names
115 write(tree%cc_names(n),
"(A,I0)")
"cc_var", n
119 if (
present(fc_names))
then 120 if (
size(fc_names) /= n_var_face) &
121 stop
"a3_init: size(fc_names) /= n_var_face" 122 tree%fc_names = fc_names
125 write(tree%fc_names(n),
"(A,I0)")
"flux", n
130 allocate(tree%cc_methods(n_var_cell))
131 allocate(tree%has_cc_method(n_var_cell))
132 tree%has_cc_method(:) = .false.
133 allocate(tree%cc_method_vars(0))
134 end subroutine a3_init
137 subroutine a3_set_cc_methods(tree, iv, bc, rb, prolong, restrict)
141 type(
a3_t),
intent(inout) :: tree
142 integer,
intent(in) :: iv
148 tree%cc_methods(iv)%bc => bc
150 if (
present(rb))
then 151 tree%cc_methods(iv)%rb => rb
153 tree%cc_methods(iv)%rb => a3_gc_interp
156 if (
present(prolong))
then 157 tree%cc_methods(iv)%prolong => prolong
159 tree%cc_methods(iv)%prolong => a3_prolong_linear
162 if (
present(restrict))
then 163 tree%cc_methods(iv)%restrict => restrict
165 tree%cc_methods(iv)%restrict => a3_restrict_box
168 tree%has_cc_method(iv) = .true.
169 n =
size(tree%cc_method_vars)
170 tree%cc_method_vars = [(tree%cc_method_vars(i), i=1,n), iv]
171 end subroutine a3_set_cc_methods
175 subroutine a3_destroy(tree)
176 type(
a3_t),
intent(inout) :: tree
178 if (.not. tree%ready) stop
"a3_destroy: Tree not fully initialized" 179 deallocate(tree%boxes)
180 deallocate(tree%lvls)
181 deallocate(tree%cc_names)
182 deallocate(tree%fc_names)
183 deallocate(tree%cc_methods)
184 deallocate(tree%has_cc_method)
185 deallocate(tree%cc_method_vars)
189 end subroutine a3_destroy
197 subroutine a3_set_base(tree, n_boxes, ix_list, nb_list)
199 type(
a3_t),
intent(inout) :: tree
201 integer,
intent(in) :: n_boxes
203 integer,
intent(in) :: ix_list(3, n_boxes)
205 integer,
intent(inout),
optional :: nb_list(a3_num_neighbors, n_boxes)
206 integer :: n, id, nb, nb_id
207 integer :: ix(3), lvl, offset
208 integer :: ix_min(3), ix_max(3), nb_ix(3)
209 integer :: nb_used(a3_num_neighbors, size(ix_list, 2))
210 integer,
allocatable :: id_array(:, :, :)
212 if (n_boxes < 1) stop
"a3_set_base: need at least one box" 213 if (any(ix_list < 1)) stop
"a3_set_base: need all ix_list > 0" 214 if (tree%highest_id > 0) stop
"a3_set_base: this tree already has boxes" 215 if (.not.
allocated(tree%lvls)) stop
"a3_set_base: tree not initialized" 217 if (
present(nb_list))
then 227 ix_min(n) = minval(ix_list(n, :)) - 1
228 ix_max(n) = maxval(ix_list(n, :)) + 1
231 allocate(id_array(ix_min(1):ix_max(1), &
232 ix_min(2):ix_max(2), ix_min(3):ix_max(3)))
239 id_array(ix(1), ix(2), ix(3)) = id
246 do nb = 1, a3_num_neighbors
248 nb_ix = ix + a3_neighb_dix(:, nb)
249 nb_id = id_array(nb_ix(1), nb_ix(2), nb_ix(3))
251 if (nb_id /= af_no_box)
then 253 nb_used(nb, id) = nb_id
256 nb_id = nb_used(nb, id)
258 if (nb_id > af_no_box)
then 260 nb_used(a3_neighb_rev(nb), nb_id) = id
261 else if (nb_id == af_no_box)
then 264 nb_used(nb, id) = af_phys_boundary
271 if (any(nb_used == af_no_box)) stop
"a3_set_base: unresolved neighbors" 274 if (n_boxes >
size(tree%boxes(:)))
then 275 call a3_resize_box_storage(tree, n_boxes)
279 do lvl = lbound(tree%lvls, 1), 1
280 deallocate(tree%lvls(lvl)%ids)
281 allocate(tree%lvls(lvl)%ids(n_boxes))
283 call get_free_ids(tree, tree%lvls(lvl)%ids)
284 offset = tree%lvls(lvl)%ids(1) - 1
287 id = tree%lvls(lvl)%ids(n)
289 tree%boxes(id)%lvl = lvl
290 tree%boxes(id)%ix = ix
291 tree%boxes(id)%dr = tree%dr_base * 0.5_dp**(lvl-1)
292 tree%boxes(id)%r_min = tree%r_base + &
293 (ix - 1) * tree%dr_base * tree%n_cell
294 tree%boxes(id)%n_cell = tree%n_cell / (2**(1-lvl))
295 tree%boxes(id)%coord_t = tree%coord_t
297 tree%boxes(id)%parent = af_no_box
298 tree%boxes(id)%children(:) = af_no_box
301 where (nb_used(:, n) > af_no_box)
302 tree%boxes(id)%neighbors = nb_used(:, n) + offset
304 tree%boxes(id)%neighbors = nb_used(:, n)
307 tree%boxes(id)%neighbor_mat = af_no_box
309 call a3_init_box(tree%boxes(id), tree%boxes(id)%n_cell, &
310 tree%n_var_cell, tree%n_var_face)
314 deallocate(tree%lvls(lvl)%leaves)
315 allocate(tree%lvls(lvl)%leaves(n_boxes))
316 tree%lvls(lvl)%leaves = tree%lvls(lvl)%ids
318 deallocate(tree%lvls(lvl)%parents)
319 allocate(tree%lvls(lvl)%parents(n_boxes))
320 tree%lvls(lvl)%parents = tree%lvls(lvl)%ids
323 if (lvl > lbound(tree%lvls, 1))
then 324 tree%boxes(tree%lvls(lvl-1)%ids)%children(1) = &
326 tree%boxes(tree%lvls(lvl)%ids)%parent = &
332 do lvl = lbound(tree%lvls, 1), 1
334 id = tree%lvls(lvl)%ids(n)
335 call set_neighbor_mat(tree%boxes, id)
342 end subroutine a3_set_base
344 subroutine set_neighbor_mat(boxes, id)
345 type(
box3_t),
intent(inout) :: boxes(:)
346 integer,
intent(in) :: id
347 integer :: i, j, k, directions(3), ndir, nb_id
349 do k = -1, 1;
do j = -1, 1;
do i = -1, 1
350 if (boxes(id)%neighbor_mat(i, j, k) /= af_no_box) cycle
356 directions(ndir) = a3_neighb_lowx + (i + 1)/2
361 directions(ndir) = a3_neighb_lowy + (j + 1)/2
366 directions(ndir) = a3_neighb_lowz + (k + 1)/2
369 boxes(id)%neighbor_mat(i, j, k) = &
370 find_neighb_id(boxes, id, directions(1:ndir))
372 nb_id = boxes(id)%neighbor_mat(i, j, k)
374 if (nb_id > af_no_box)
then 375 boxes(nb_id)%neighbor_mat(-i, -j, -k) = id
377 end do; end do; end do
379 end subroutine set_neighbor_mat
383 pure function find_neighb_id(boxes, id, nbs)
result(nb_id)
384 type(box3_t),
intent(in) :: boxes(:)
385 integer,
intent(in) :: id
386 integer,
intent(in) :: nbs(:)
387 integer :: i, j, k, nb, nb_id
388 integer :: nbs_perm(size(nbs))
392 if (
size(nbs) == 0)
then 401 k = 1 + mod(i + j - 2,
size(nbs))
404 nb_id = boxes(nb_id)%neighbors(nb)
405 if (nb_id <= af_no_box)
exit 408 if (nb_id > af_no_box)
exit 414 if (
size(nbs) == 3 .and. nb_id <= af_no_box)
then 415 nbs_perm = nbs([2,1,3])
421 k = 1 + mod(i + j - 2,
size(nbs))
424 nb_id = boxes(nb_id)%neighbors(nb)
425 if (nb_id <= af_no_box)
exit 428 if (nb_id > af_no_box)
exit 432 end function find_neighb_id
435 subroutine a3_tidy_up(tree, max_hole_frac, n_clean_min)
437 type(a3_t),
intent(inout) :: tree
439 real(dp),
intent(in) :: max_hole_frac
441 integer,
intent(in) :: n_clean_min
442 real(dp) :: hole_frac
443 integer :: n, lvl, id, n_clean, i, j, k
444 integer :: highest_id, n_used, n_stored, n_used_lvl
445 integer,
allocatable :: ixs_sort(:), ixs_map(:)
446 type(box3_t),
allocatable :: boxes_cpy(:)
447 integer(morton_k),
allocatable :: mortons(:)
449 if (.not. tree%ready) stop
"Tree not ready" 450 if (max_hole_frac < 0) stop
"a3_tidy_up: need max_hole_frac >= 0" 451 if (n_clean_min < 0) stop
"a3_tidy_up: need n_clean_min >= 0" 453 highest_id = tree%highest_id
454 n_used = a3_num_boxes_used(tree)
455 hole_frac = 1 - n_used /
real(highest_id, dp)
456 n_clean = nint(hole_frac * highest_id)
458 if (hole_frac > max_hole_frac .and. n_clean >= n_clean_min)
then 459 allocate(boxes_cpy(n_used))
460 allocate(ixs_map(0:highest_id))
464 do lvl = lbound(tree%lvls, 1), tree%highest_lvl
465 n_used_lvl =
size(tree%lvls(lvl)%ids)
466 allocate(mortons(n_used_lvl))
467 allocate(ixs_sort(n_used_lvl))
470 id = tree%lvls(lvl)%ids(n)
472 mortons(n) = morton_from_ix3(tree%boxes(id)%ix-1)
475 call morton_rank(mortons, ixs_sort)
476 tree%lvls(lvl)%ids = tree%lvls(lvl)%ids(ixs_sort)
479 id = tree%lvls(lvl)%ids(n)
480 boxes_cpy(n_stored + n) = tree%boxes(id)
481 ixs_map(tree%lvls(lvl)%ids(n)) = n_stored + n
484 tree%lvls(lvl)%ids = [(n_stored+n, n=1,n_used_lvl)]
485 call set_leaves_parents(boxes_cpy, tree%lvls(lvl))
486 n_stored = n_stored + n_used_lvl
493 boxes_cpy(n)%parent = ixs_map(boxes_cpy(n)%parent)
494 boxes_cpy(n)%children = ixs_map(boxes_cpy(n)%children)
495 where (boxes_cpy(n)%neighbors > af_no_box)
496 boxes_cpy(n)%neighbors = ixs_map(boxes_cpy(n)%neighbors)
499 do k = -1, 1;
do j = -1, 1;
do i = -1, 1
500 if (boxes_cpy(n)%neighbor_mat(i, j, k) > af_no_box)
then 501 boxes_cpy(n)%neighbor_mat(i, j, k) = &
502 ixs_map(boxes_cpy(n)%neighbor_mat(i, j, k))
504 end do; end do; end do
507 tree%boxes(1:n_used) = boxes_cpy
508 do n = n_used+1, highest_id
509 if (tree%boxes(n)%in_use)
then 511 call clear_box(tree%boxes(n))
515 tree%highest_id = n_used
518 end subroutine a3_tidy_up
521 subroutine set_leaves_parents(boxes, level)
522 type(box3_t),
intent(in) :: boxes(:)
523 type(lvl_t),
intent(inout) :: level
524 integer :: i, id, i_leaf, i_parent
525 integer :: n_parents, n_leaves
527 n_parents = count(a3_has_children(boxes(level%ids)))
528 n_leaves =
size(level%ids) - n_parents
530 if (n_parents /=
size(level%parents))
then 531 deallocate(level%parents)
532 allocate(level%parents(n_parents))
535 if (n_leaves /=
size(level%leaves))
then 536 deallocate(level%leaves)
537 allocate(level%leaves(n_leaves))
542 do i = 1,
size(level%ids)
544 if (a3_has_children(boxes(id)))
then 545 i_parent = i_parent + 1
546 level%parents(i_parent) = id
549 level%leaves(i_leaf) = id
552 end subroutine set_leaves_parents
556 subroutine a3_init_box(box, n_cell, n_cc, n_fc)
557 type(box3_t),
intent(inout) :: box
558 integer,
intent(in) :: n_cell
559 integer,
intent(in) :: n_cc
560 integer,
intent(in) :: n_fc
564 allocate(box%cc(0:n_cell+1, 0:n_cell+1, 0:n_cell+1, n_cc))
565 allocate(box%fc(n_cell+1, n_cell+1, n_cell+1, 3, n_fc))
570 end subroutine a3_init_box
573 subroutine clear_box(box)
574 type(box3_t),
intent(inout) :: box
580 end subroutine clear_box
583 subroutine set_neighbs_3d(boxes, id)
584 type(box3_t),
intent(inout) :: boxes(:)
585 integer,
intent(in) :: id
586 integer :: nb, nb_id, i, j, k
588 do k = -1, 1;
do j = -1, 1;
do i = -1, 1
589 if (boxes(id)%neighbor_mat(i, j, k) == af_no_box)
then 590 nb_id = find_neighb_3d(boxes, id, [i, j, k])
591 if (nb_id > af_no_box)
then 592 boxes(id)%neighbor_mat(i, j, k) = nb_id
593 boxes(nb_id)%neighbor_mat(-i, -j, -k) = id
596 end do; end do; end do
598 do nb = 1, a3_num_neighbors
599 if (boxes(id)%neighbors(nb) == af_no_box)
then 600 nb_id = boxes(id)%neighbor_mat(a3_neighb_dix(1, nb), &
601 a3_neighb_dix(2, nb), a3_neighb_dix(3, nb))
602 if (nb_id > af_no_box)
then 603 boxes(id)%neighbors(nb) = nb_id
604 boxes(nb_id)%neighbors(a3_neighb_rev(nb)) = id
608 end subroutine set_neighbs_3d
611 function find_neighb_3d(boxes, id, dix)
result(nb_id)
612 type(box3_t),
intent(in) :: boxes(:)
613 integer,
intent(in) :: id
614 integer,
intent(in) :: dix(3)
615 integer :: nb_id, p_id, c_ix, dix_c(3)
617 p_id = boxes(id)%parent
618 c_ix = a3_ix_to_ichild(boxes(id)%ix)
622 where ((dix == -1) .eqv. a3_child_low(:, c_ix))
628 p_id = boxes(p_id)%neighbor_mat(dix_c(1), dix_c(2), dix_c(3))
630 if (p_id <= af_no_box)
then 633 c_ix = a3_ix_to_ichild(boxes(id)%ix + dix)
634 nb_id = boxes(p_id)%children(c_ix)
636 end function find_neighb_3d
639 subroutine a3_resize_box_storage(tree, new_size)
640 type(a3_t),
intent(inout) :: tree
641 integer,
intent(in) :: new_size
642 type(box3_t),
allocatable :: boxes_cpy(:)
644 if (.not. tree%ready) stop
"a3_resize_box_storage: Tree not ready" 645 if (new_size < tree%highest_id) &
646 stop
"a3_resize_box_storage: Cannot shrink tree" 649 allocate(boxes_cpy(new_size))
650 boxes_cpy(1:tree%highest_id) = tree%boxes(1:tree%highest_id)
653 deallocate(tree%boxes)
656 call move_alloc(boxes_cpy, tree%boxes)
657 end subroutine a3_resize_box_storage
665 subroutine a3_adjust_refinement(tree, ref_subr, ref_info, ref_buffer, keep_buffer)
666 type(a3_t),
intent(inout) :: tree
667 procedure(a3_subr_ref) :: ref_subr
668 type(ref_info_t),
intent(inout) :: ref_info
669 integer,
intent(in),
optional :: ref_buffer
670 logical,
intent(in),
optional :: keep_buffer
671 integer :: lvl, id, i, c_ids(a3_num_children)
672 integer :: highest_id_prev, highest_id_req
673 integer,
allocatable :: ref_flags(:)
674 integer :: num_new_boxes, total_num_boxes
675 integer :: new_size, ref_buffer_val
676 logical :: keep_buffer_val
678 if (.not. tree%ready) stop
"Tree not ready" 681 if (
present(ref_buffer)) ref_buffer_val = ref_buffer
682 keep_buffer_val = .false.
683 if (
present(keep_buffer)) keep_buffer_val = keep_buffer
685 if (ref_buffer_val < 0) &
686 error stop
"a3_adjust_refinement: ref_buffer < 0" 687 if (ref_buffer_val > tree%n_cell) &
688 error stop
"a3_adjust_refinement: ref_buffer > tree%n_cell" 692 call a3_tidy_up(tree, 0.5_dp, 1000)
694 highest_id_prev = tree%highest_id
695 allocate(ref_flags(highest_id_prev))
698 call consistent_ref_flags(tree, ref_flags, ref_subr, &
699 ref_buffer_val, keep_buffer_val)
702 num_new_boxes = a3_num_children * count(ref_flags == af_refine)
705 total_num_boxes = a3_num_boxes_used(tree) + num_new_boxes
707 if (total_num_boxes > tree%box_limit)
then 708 print *,
"a3_adjust_refinement: exceeding memory limit" 709 write(*,
'(A,E12.2)')
" memory_limit (GByte): ", &
710 tree%box_limit * 0.5_dp**30 * &
711 a3_box_bytes(tree%n_cell, tree%n_var_cell, tree%n_var_face)
712 print *,
"memory_limit (boxes): ", tree%box_limit
713 print *,
"required number of boxes: ", total_num_boxes
714 print *,
"You can increase the memory limit in your call to a3_init" 715 print *,
"by setting mem_limit_gb to a higher value (in GBytes)" 720 highest_id_req = highest_id_prev + num_new_boxes
721 if (highest_id_req >
size(tree%boxes))
then 722 new_size = 2 * highest_id_req
723 call a3_resize_box_storage(tree, new_size)
726 do lvl = 1, tree%lvl_limit-1
727 do i = 1,
size(tree%lvls(lvl)%ids)
728 id = tree%lvls(lvl)%ids(i)
730 if (id > highest_id_prev)
then 732 else if (ref_flags(id) == af_refine)
then 734 call get_free_ids(tree, c_ids)
735 call add_children(tree%boxes, id, c_ids, &
736 tree%n_var_cell, tree%n_var_face)
737 else if (ref_flags(id) == af_derefine)
then 739 call auto_restrict(tree, id)
740 call remove_children(tree%boxes, id)
745 call set_leaves_parents(tree%boxes, tree%lvls(lvl))
748 call set_child_ids(tree%lvls(lvl)%parents, &
749 tree%lvls(lvl+1)%ids, tree%boxes)
752 do i = 1,
size(tree%lvls(lvl+1)%ids)
753 id = tree%lvls(lvl+1)%ids(i)
754 if (id > highest_id_prev)
call set_neighbs_3d(tree%boxes, id)
757 if (
size(tree%lvls(lvl+1)%ids) == 0)
exit 760 tree%highest_lvl = lvl
765 lvl = min(lvl+1, tree%lvl_limit)
766 call set_leaves_parents(tree%boxes, tree%lvls(lvl))
769 call set_ref_info(tree, ref_flags, ref_info)
771 call auto_prolong(tree, ref_info)
773 end subroutine a3_adjust_refinement
776 subroutine auto_restrict(tree, id)
777 type(a3_t),
intent(inout) :: tree
778 integer,
intent(in) :: id
779 integer :: iv, i_ch, ch_id
781 if (.not. any(tree%has_cc_method(:)))
return 783 do iv = 1, tree%n_var_cell
784 if (tree%has_cc_method(iv))
then 785 do i_ch = 1, a3_num_children
786 ch_id = tree%boxes(id)%children(i_ch)
787 call tree%cc_methods(iv)%restrict(tree%boxes(ch_id), &
792 end subroutine auto_restrict
795 subroutine auto_prolong(tree, ref_info)
797 type(a3_t),
intent(inout) :: tree
798 type(ref_info_t),
intent(in) :: ref_info
799 integer :: lvl, i, n, iv, id, p_id
802 if (.not. any(tree%has_cc_method(:)) .or. ref_info%n_add == 0)
then 807 do lvl = 1, tree%highest_lvl
809 do i = 1,
size(ref_info%lvls(lvl)%add)
810 id = ref_info%lvls(lvl)%add(i)
811 p_id = tree%boxes(id)%parent
813 do n = 1,
size(tree%cc_method_vars)
814 iv = tree%cc_method_vars(n)
815 call tree%cc_methods(iv)%prolong(tree%boxes(p_id), &
822 do i = 1,
size(ref_info%lvls(lvl)%add)
823 id = ref_info%lvls(lvl)%add(i)
824 call a3_gc_box(tree, id, [tree%cc_method_vars])
829 end subroutine auto_prolong
832 subroutine set_ref_info(tree, ref_flags, ref_info)
833 type(a3_t),
intent(in) :: tree
834 integer,
intent(in) :: ref_flags(:)
835 type(ref_info_t),
intent(inout) :: ref_info
836 integer :: id, lvl, n, n_ch
837 integer,
allocatable :: ref_count(:), drf_count(:)
839 n_ch = a3_num_children
840 ref_info%n_add = n_ch * count(ref_flags == af_refine)
841 ref_info%n_rm = n_ch * count(ref_flags == af_derefine)
844 if (
allocated(ref_info%lvls))
deallocate(ref_info%lvls)
845 allocate(ref_info%lvls(tree%highest_lvl+1))
846 allocate(ref_count(tree%highest_lvl+1))
847 allocate(drf_count(tree%highest_lvl+1))
853 do id = 1,
size(ref_flags)
854 lvl = tree%boxes(id)%lvl
856 if (ref_flags(id) == af_refine)
then 857 ref_count(lvl) = ref_count(lvl) + 1
858 else if (ref_flags(id) == af_derefine)
then 859 drf_count(lvl) = drf_count(lvl) + 1
865 allocate(ref_info%lvls(1)%add(0))
866 allocate(ref_info%lvls(1)%rm(0))
868 do lvl = 2, tree%highest_lvl+1
869 n = ref_count(lvl-1) * n_ch
870 allocate(ref_info%lvls(lvl)%add(n))
871 n = drf_count(lvl-1) * n_ch
872 allocate(ref_info%lvls(lvl)%rm(n))
880 do id = 1,
size(ref_flags)
881 lvl = tree%boxes(id)%lvl
883 if (ref_flags(id) == af_refine)
then 884 ref_count(lvl) = ref_count(lvl) + 1
885 n = n_ch * (ref_count(lvl)-1) + 1
886 ref_info%lvls(lvl+1)%add(n:n+n_ch-1) = tree%boxes(id)%children
887 else if (ref_flags(id) == af_derefine)
then 888 drf_count(lvl) = drf_count(lvl) + 1
889 n = n_ch * (drf_count(lvl)-1) + 1
890 ref_info%lvls(lvl+1)%rm(n:n+n_ch-1) = tree%boxes(id)%children
893 end subroutine set_ref_info
897 subroutine get_free_ids(tree, ids)
898 type(a3_t),
intent(inout) :: tree
899 integer,
intent(out) :: ids(:)
900 integer :: i, highest_id_prev, n_ids
904 highest_id_prev = tree%highest_id
905 tree%highest_id = tree%highest_id + n_ids
908 ids = [(highest_id_prev + i, i=1,n_ids)]
909 end subroutine get_free_ids
916 subroutine consistent_ref_flags(tree, ref_flags, ref_subr, &
917 ref_buffer, keep_buffer)
918 use omp_lib
, only: omp_get_max_threads, omp_get_thread_num
919 type(a3_t),
intent(inout) :: tree
920 integer,
intent(inout) :: ref_flags(:)
921 procedure(a3_subr_ref) :: ref_subr
922 integer,
intent(in) :: ref_buffer
923 logical,
intent(in) :: keep_buffer
925 integer :: lvl, i, i_ch, ch_id, id, c_ids(a3_num_children)
926 integer :: nb, p_id, nb_id, p_nb_id
927 integer :: lvl_limit, thread_id
928 integer,
allocatable :: tmp_flags(:, :)
929 integer :: cell_flags(tree%n_cell, tree%n_cell, tree%n_cell)
930 integer,
parameter :: unset_flag = -huge(1)
934 allocate(tmp_flags(
size(ref_flags), omp_get_max_threads()))
936 lvl_limit = tree%lvl_limit
937 tmp_flags(:, :) = unset_flag
943 thread_id = omp_get_thread_num() + 1
945 do lvl = 1, tree%highest_lvl
947 do i = 1,
size(tree%lvls(lvl)%leaves)
948 id = tree%lvls(lvl)%leaves(i)
950 call ref_subr(tree%boxes(id), cell_flags)
951 call cell_to_ref_flags(cell_flags, tree%n_cell, &
952 tmp_flags(:, thread_id), tree, id, ref_buffer, keep_buffer)
956 if (tree%boxes(id)%lvl > 1)
then 957 p_id = tree%boxes(id)%parent
958 do i_ch = 1, a3_ix_to_ichild(tree%boxes(id)%ix)-1
959 ch_id = tree%boxes(p_id)%children(i_ch)
960 if (.not. a3_has_children(tree%boxes(ch_id)))
exit 963 if (i_ch == a3_ix_to_ichild(tree%boxes(id)%ix))
then 965 call ref_subr(tree%boxes(p_id), cell_flags)
966 call cell_to_ref_flags(cell_flags, tree%n_cell, &
967 tmp_flags(:, thread_id), tree, p_id, ref_buffer, keep_buffer)
976 do i = 1,
size(ref_flags)
977 ref_flags(i) = maxval(tmp_flags(i, :))
978 if (ref_flags(i) == unset_flag) ref_flags(i) = af_keep_ref
981 if (maxval(ref_flags) > af_do_ref .or. minval(ref_flags) < af_rm_ref) &
982 stop
"a3_adjust_refinement: invalid refinement flag given" 985 do i = 1,
size(tree%lvls(lvl_limit)%ids)
986 id = tree%lvls(lvl_limit)%ids(i)
987 if (ref_flags(id) == af_do_ref) ref_flags(id) = af_keep_ref
991 do lvl = tree%highest_lvl, 1, -1
992 do i = 1,
size(tree%lvls(lvl)%leaves)
993 id = tree%lvls(lvl)%leaves(i)
995 if (ref_flags(id) == af_do_ref .or. ref_flags(id) == af_refine)
then 996 ref_flags(id) = af_refine
999 do nb = 1, a3_num_neighbors
1000 nb_id = tree%boxes(id)%neighbors(nb)
1001 if (nb_id == af_no_box)
then 1003 p_id = tree%boxes(id)%parent
1004 p_nb_id = tree%boxes(p_id)%neighbors(nb)
1005 ref_flags(p_nb_id) = af_refine
1009 else if (ref_flags(id) == af_rm_ref)
then 1011 do nb = 1, a3_num_neighbors
1012 nb_id = tree%boxes(id)%neighbors(nb)
1013 if (nb_id > af_no_box)
then 1014 if (a3_has_children(tree%boxes(nb_id)) .or. &
1015 ref_flags(nb_id) > af_keep_ref)
then 1016 ref_flags(id) = af_keep_ref
1028 do lvl = tree%highest_lvl-1, 1, -1
1029 do i = 1,
size(tree%lvls(lvl)%parents)
1030 id = tree%lvls(lvl)%parents(i)
1034 c_ids = tree%boxes(id)%children
1035 if (all(ref_flags(c_ids) == af_rm_ref) .and. &
1036 ref_flags(id) <= af_keep_ref)
then 1037 ref_flags(id) = af_derefine
1039 ref_flags(id) = af_keep_ref
1044 end subroutine consistent_ref_flags
1049 subroutine cell_to_ref_flags(cell_flags, nc, ref_flags, tree, id, &
1050 ref_buffer, keep_buffer)
1052 integer,
intent(in) :: nc
1053 integer,
intent(in) :: cell_flags(nc, nc, nc)
1054 integer,
intent(inout) :: ref_flags(:)
1055 type(a3_t),
intent(in) :: tree
1056 integer,
intent(in) :: id
1057 integer,
intent(in) :: ref_buffer
1058 logical,
intent(in) :: keep_buffer
1059 integer :: ix0(3), ix1(3), i, j, k, nb_id
1061 if (minval(cell_flags) < af_rm_ref .or. &
1062 maxval(cell_flags) > af_do_ref)
then 1063 error stop
"Error: invalid cell flags given" 1067 if (any(cell_flags == af_do_ref))
then 1068 ref_flags(id) = af_do_ref
1069 else if (any(cell_flags == af_keep_ref))
then 1070 ref_flags(id) = max(ref_flags(id), af_keep_ref)
1072 ref_flags(id) = max(ref_flags(id), af_rm_ref)
1075 if (ref_buffer <= 0)
return 1079 do k = -1, 1;
do j = -1, 1;
do i = -1, 1
1080 if (all([i, j, k] == 0)) cycle
1082 nb_id = tree%boxes(id)%neighbor_mat(i, j, k)
1085 if (nb_id <= af_no_box) cycle
1090 where ([i, j, k] == 1)
1091 ix0 = nc - ref_buffer + 1
1093 elsewhere ([i, j, k] == -1)
1098 if (any(cell_flags(ix0(1):ix1(1), ix0(2):ix1(2), &
1099 ix0(3):ix1(3)) == af_do_ref))
then 1100 ref_flags(nb_id) = af_do_ref
1101 else if (keep_buffer .and. any(cell_flags(ix0(1):ix1(1), &
1102 ix0(2):ix1(2), ix0(3):ix1(3)) == af_keep_ref))
then 1103 ref_flags(nb_id) = max(ref_flags(nb_id), af_keep_ref)
1105 end do; end do; end do
1107 end subroutine cell_to_ref_flags
1110 subroutine remove_children(boxes, id)
1111 type(box3_t),
intent(inout) :: boxes(:)
1112 integer,
intent(in) :: id
1113 integer :: ic, c_id, nb_id, nb_rev, nb, i, j, k
1115 do ic = 1, a3_num_children
1116 c_id = boxes(id)%children(ic)
1119 do nb = 1, a3_num_neighbors
1120 nb_id = boxes(c_id)%neighbors(nb)
1121 if (nb_id > af_no_box)
then 1122 nb_rev = a3_neighb_rev(nb)
1123 boxes(nb_id)%neighbors(nb_rev) = af_no_box
1127 do k = -1, 1;
do j = -1, 1;
do i = -1, 1
1128 nb_id = boxes(c_id)%neighbor_mat(i, j, k)
1129 if (nb_id > af_no_box)
then 1130 boxes(nb_id)%neighbor_mat(-i, -j, -k) = af_no_box
1132 end do; end do; end do
1134 call clear_box(boxes(c_id))
1137 boxes(id)%children = af_no_box
1138 end subroutine remove_children
1141 subroutine add_children(boxes, id, c_ids, n_cc, n_fc)
1142 type(box3_t),
intent(inout) :: boxes(:)
1143 integer,
intent(in) :: id
1144 integer,
intent(in) :: c_ids(a3_num_children)
1145 integer,
intent(in) :: n_cc
1146 integer,
intent(in) :: n_fc
1147 integer :: i, nb, child_nb(2**(3-1))
1148 integer :: c_id, c_ix_base(3), dix(3)
1150 boxes(id)%children = c_ids
1151 c_ix_base = 2 * boxes(id)%ix - 1
1153 do i = 1, a3_num_children
1155 boxes(c_id)%ix = c_ix_base + a3_child_dix(:,i)
1156 boxes(c_id)%lvl = boxes(id)%lvl+1
1157 boxes(c_id)%parent = id
1158 boxes(c_id)%tag = af_init_tag
1159 boxes(c_id)%children = af_no_box
1160 boxes(c_id)%neighbors = af_no_box
1161 boxes(c_id)%neighbor_mat = af_no_box
1162 boxes(c_id)%neighbor_mat(0, 0, 0) = c_id
1163 boxes(c_id)%n_cell = boxes(id)%n_cell
1164 boxes(c_id)%coord_t = boxes(id)%coord_t
1165 boxes(c_id)%dr = 0.5_dp * boxes(id)%dr
1166 boxes(c_id)%r_min = boxes(id)%r_min + 0.5_dp * boxes(id)%dr * &
1167 a3_child_dix(:,i) * boxes(id)%n_cell
1169 call a3_init_box(boxes(c_id), boxes(id)%n_cell, n_cc, n_fc)
1173 do nb = 1, a3_num_neighbors
1174 if (boxes(id)%neighbors(nb) < af_no_box)
then 1175 child_nb = c_ids(a3_child_adj_nb(:, nb))
1176 boxes(child_nb)%neighbors(nb) = boxes(id)%neighbors(nb)
1177 dix = a3_neighb_dix(:, nb)
1178 boxes(child_nb)%neighbor_mat(dix(1), dix(2), dix(3)) = &
1179 boxes(id)%neighbors(nb)
1182 end subroutine add_children
1186 subroutine set_child_ids(p_ids, c_ids, boxes)
1187 integer,
intent(in) :: p_ids(:)
1188 integer,
allocatable,
intent(inout) :: c_ids(:)
1189 type(box3_t),
intent(in) :: boxes(:)
1190 integer :: i, i0, i1, n_children
1192 n_children = a3_num_children *
size(p_ids)
1193 if (n_children /=
size(c_ids))
then 1195 allocate(c_ids(n_children))
1198 do i = 1,
size(p_ids)
1199 i1 = i * a3_num_children
1200 i0 = i1 - a3_num_children + 1
1201 c_ids(i0:i1) = boxes(p_ids(i))%children
1203 end subroutine set_child_ids
1206 subroutine a3_consistent_fluxes(tree, f_ixs)
1207 type(a3_t),
intent(inout) :: tree
1208 integer,
intent(in) :: f_ixs(:)
1209 integer :: lvl, i, id, nb, nb_id
1211 if (.not. tree%ready) stop
"Tree not ready" 1213 do lvl = lbound(tree%lvls, 1), tree%highest_lvl-1
1215 do i = 1,
size(tree%lvls(lvl)%parents)
1216 id = tree%lvls(lvl)%parents(i)
1217 do nb = 1, a3_num_neighbors
1218 nb_id = tree%boxes(id)%neighbors(nb)
1221 if (nb_id > af_no_box)
then 1222 if (.not. a3_has_children(tree%boxes(nb_id)))
then 1223 call flux_from_children(tree%boxes, id, nb, f_ixs)
1231 end subroutine a3_consistent_fluxes
1235 subroutine flux_from_children(boxes, id, nb, f_ixs)
1236 type(box3_t),
intent(inout) :: boxes(:)
1237 integer,
intent(in) :: id
1238 integer,
intent(in) :: nb
1239 integer,
intent(in) :: f_ixs(:)
1240 integer :: nc, nch, c_id, i_ch, i, ic, d
1241 integer :: n_chnb, nb_id, i_nb, ioff(3)
1243 nc = boxes(id)%n_cell
1245 d = a3_neighb_dim(nb)
1247 nb_id = boxes(id)%neighbors(nb)
1249 if (a3_neighb_low(nb))
then 1260 i_ch = a3_child_adj_nb(ic, nb)
1261 c_id = boxes(id)%children(i_ch)
1262 ioff = nch*a3_child_dix(:, i_ch)
1263 boxes(nb_id)%fc(i_nb, ioff(2)+1:ioff(2)+nch, &
1264 ioff(3)+1:ioff(3)+nch, 1, f_ixs) = 0.25_dp * ( &
1265 boxes(c_id)%fc(i, 1:nc:2, 1:nc:2, 1, f_ixs) + &
1266 boxes(c_id)%fc(i, 2:nc:2, 1:nc:2, 1, f_ixs) + &
1267 boxes(c_id)%fc(i, 1:nc:2, 2:nc:2, 1, f_ixs) + &
1268 boxes(c_id)%fc(i, 2:nc:2, 2:nc:2, 1, f_ixs))
1272 i_ch = a3_child_adj_nb(ic, nb)
1273 c_id = boxes(id)%children(i_ch)
1274 ioff = nch*a3_child_dix(:, i_ch)
1275 boxes(nb_id)%fc(ioff(1)+1:ioff(1)+nch, i_nb, &
1276 ioff(3)+1:ioff(3)+nch, 2, f_ixs) = 0.25_dp * ( &
1277 boxes(c_id)%fc(1:nc:2, i, 1:nc:2, 2, f_ixs) + &
1278 boxes(c_id)%fc(2:nc:2, i, 1:nc:2, 2, f_ixs) + &
1279 boxes(c_id)%fc(1:nc:2, i, 2:nc:2, 2, f_ixs) + &
1280 boxes(c_id)%fc(2:nc:2, i, 2:nc:2, 2, f_ixs))
1284 i_ch = a3_child_adj_nb(ic, nb)
1285 c_id = boxes(id)%children(i_ch)
1286 ioff = nch*a3_child_dix(:, i_ch)
1287 boxes(nb_id)%fc(ioff(1)+1:ioff(1)+nch, &
1288 ioff(2)+1:ioff(2)+nch, i_nb, 3, f_ixs) = 0.25_dp * ( &
1289 boxes(c_id)%fc(1:nc:2, 1:nc:2, i, 3, f_ixs) + &
1290 boxes(c_id)%fc(2:nc:2, 1:nc:2, i, 3, f_ixs) + &
1291 boxes(c_id)%fc(1:nc:2, 2:nc:2, i, 3, f_ixs) + &
1292 boxes(c_id)%fc(2:nc:2, 2:nc:2, i, 3, f_ixs))
1295 end subroutine flux_from_children
This module contains all kinds of different 'helper' routines for Afivo. If the number of routines fo...
Subroutine for restriction.
This module contains routines for restriction: going from fine to coarse variables.
To fill ghost cells near physical boundaries.
Subroutine for prolongation.
This module contains methods to convert indices to morton numbers.
The basic building block of afivo: a box with cell-centered and face centered data, and information about its position, neighbors, children etc.
Type which stores all the boxes and levels, as well as some information about the number of boxes...
To fill ghost cells near refinement boundaries.
This module contains the core routines of Afivo, namely those that deal with initializing and changin...
This module contains the routines related to prolongation: going from coarse to fine variables...
This module contains routines related to the filling of ghost cells. Note that corner ghost cells are...
This module contains the basic types and constants that are used in the 3-dimensional version of Afiv...