13 public :: a3_loop_box_arg
14 public :: a3_loop_boxes
15 public :: a3_loop_boxes_arg
16 public :: a3_tree_clear_cc
17 public :: a3_box_clear_cc
18 public :: a3_tree_clear_ghostcells
19 public :: a3_box_clear_ghostcells
20 public :: a3_box_add_cc
21 public :: a3_box_sub_cc
22 public :: a3_tree_times_cc
23 public :: a3_tree_apply
24 public :: a3_box_times_cc
25 public :: a3_box_lincomb_cc
26 public :: a3_box_copy_cc_to
27 public :: a3_box_copy_cc
28 public :: a3_boxes_copy_cc
29 public :: a3_tree_copy_cc
30 public :: a3_reduction
31 public :: a3_reduction_vec
32 public :: a3_reduction_loc
33 public :: a3_tree_max_cc
34 public :: a3_tree_min_cc
35 public :: a3_tree_max_fc
36 public :: a3_tree_sum_cc
37 public :: a3_box_copy_fc
38 public :: a3_boxes_copy_fc
39 public :: a3_tree_copy_fc
42 public :: a3_get_id_at
51 subroutine a3_loop_box(tree, my_procedure, leaves_only)
52 type(
a3_t),
intent(inout) :: tree
53 procedure(
a3_subr) :: my_procedure
54 logical,
intent(in),
optional :: leaves_only
58 leaves = .false.;
if (
present(leaves_only)) leaves = leaves_only
59 if (.not. tree%ready) stop
"a3_loop_box: set_base has not been called" 62 do lvl = lbound(tree%lvls, 1), tree%highest_lvl
65 do i = 1,
size(tree%lvls(lvl)%leaves)
66 id = tree%lvls(lvl)%leaves(i)
67 call my_procedure(tree%boxes(id))
72 do i = 1,
size(tree%lvls(lvl)%ids)
73 id = tree%lvls(lvl)%ids(i)
74 call my_procedure(tree%boxes(id))
80 end subroutine a3_loop_box
83 subroutine a3_loop_box_arg(tree, my_procedure, rarg, leaves_only)
84 type(
a3_t),
intent(inout) :: tree
86 real(dp),
intent(in) :: rarg(:)
87 logical,
intent(in),
optional :: leaves_only
91 if (.not. tree%ready) stop
"Tree not ready" 92 leaves = .false.;
if (
present(leaves_only)) leaves = leaves_only
95 do lvl = lbound(tree%lvls, 1), tree%highest_lvl
98 do i = 1,
size(tree%lvls(lvl)%leaves)
99 id = tree%lvls(lvl)%leaves(i)
100 call my_procedure(tree%boxes(id), rarg)
105 do i = 1,
size(tree%lvls(lvl)%ids)
106 id = tree%lvls(lvl)%ids(i)
107 call my_procedure(tree%boxes(id), rarg)
113 end subroutine a3_loop_box_arg
116 subroutine a3_loop_boxes(tree, my_procedure, leaves_only)
117 type(
a3_t),
intent(inout) :: tree
119 logical,
intent(in),
optional :: leaves_only
121 integer :: lvl, i, id
123 if (.not. tree%ready) stop
"Tree not ready" 124 leaves = .false.;
if (
present(leaves_only)) leaves = leaves_only
127 do lvl = lbound(tree%lvls, 1), tree%highest_lvl
130 do i = 1,
size(tree%lvls(lvl)%leaves)
131 id = tree%lvls(lvl)%leaves(i)
132 call my_procedure(tree%boxes, id)
137 do i = 1,
size(tree%lvls(lvl)%ids)
138 id = tree%lvls(lvl)%ids(i)
139 call my_procedure(tree%boxes, id)
145 end subroutine a3_loop_boxes
148 subroutine a3_loop_boxes_arg(tree, my_procedure, rarg, leaves_only)
149 type(
a3_t),
intent(inout) :: tree
151 real(dp),
intent(in) :: rarg(:)
152 logical,
intent(in),
optional :: leaves_only
154 integer :: lvl, i, id
156 if (.not. tree%ready) stop
"Tree not ready" 157 leaves = .false.;
if (
present(leaves_only)) leaves = leaves_only
160 do lvl = lbound(tree%lvls, 1), tree%highest_lvl
163 do i = 1,
size(tree%lvls(lvl)%leaves)
164 id = tree%lvls(lvl)%leaves(i)
165 call my_procedure(tree%boxes, id, rarg)
170 do i = 1,
size(tree%lvls(lvl)%ids)
171 id = tree%lvls(lvl)%ids(i)
172 call my_procedure(tree%boxes, id, rarg)
178 end subroutine a3_loop_boxes_arg
181 pure function a3_r_inside(box, r, d)
result(inside)
183 real(dp),
intent(in) :: r(3)
184 real(dp),
intent(in),
optional :: d
188 r_max = box%r_min + box%dr * box%n_cell
190 inside = all(r+d >= box%r_min) .and. all(r-d <= r_max)
192 inside = all(r >= box%r_min) .and. all(r <= r_max)
194 end function a3_r_inside
199 pure function a3_get_id_at(tree, rr, highest_lvl, guess)
result(id)
201 real(dp),
intent(in) :: rr(3)
202 integer,
intent(in),
optional :: highest_lvl
203 integer,
intent(in),
optional :: guess
206 integer :: i, i_ch, lvl_max
208 if (
present(guess))
then 210 if (id > 0 .and. id < tree%highest_id)
then 211 if (tree%boxes(id)%in_use .and. &
212 a3_r_inside(tree%boxes(id), rr))
then 215 do while (a3_has_children(tree%boxes(id)))
216 i_ch = child_that_contains(tree%boxes(id), rr)
217 id = tree%boxes(id)%children(i_ch)
225 lvl_max = tree%lvl_limit
226 if (
present(highest_lvl)) lvl_max = highest_lvl
229 do i = 1,
size(tree%lvls(1)%ids)
230 id = tree%lvls(1)%ids(i)
231 if (a3_r_inside(tree%boxes(id), rr))
exit 234 if (i >
size(tree%lvls(1)%ids))
then 240 if (tree%boxes(id)%lvl >= lvl_max .or. &
241 .not. a3_has_children(tree%boxes(id)))
exit 242 i_ch = child_that_contains(tree%boxes(id), rr)
243 id = tree%boxes(id)%children(i_ch)
247 end function a3_get_id_at
252 pure function a3_get_loc(tree, rr, highest_lvl, guess)
result(loc)
254 real(dp),
intent(in) :: rr(3)
255 integer,
intent(in),
optional :: highest_lvl
257 integer,
intent(in),
optional :: guess
260 loc%id = a3_get_id_at(tree, rr, highest_lvl, guess)
262 if (loc%id == -1)
then 265 loc%ix = a3_cc_ix(tree%boxes(loc%id), rr)
269 where (loc%ix < 1) loc%ix = 1
270 where (loc%ix > tree%n_cell) loc%ix = tree%n_cell
272 end function a3_get_loc
275 pure function child_that_contains(box, rr)
result(i_ch)
276 type(
box3_t),
intent(in) :: box
277 real(dp),
intent(in) :: rr(3)
279 real(dp) :: center(3)
282 center = box%r_min + box%dr * ishft(box%n_cell, -1)
284 if (rr(1) > center(1)) i_ch = i_ch + 1
285 if (rr(2) > center(2)) i_ch = i_ch + 2
286 if (rr(3) > center(3)) i_ch = i_ch + 4
287 end function child_that_contains
290 pure function a3_r_loc(tree, loc)
result(r)
294 r = tree%boxes(loc%id)%r_min + &
295 (loc%ix-0.5_dp) * tree%boxes(loc%id)%dr
296 end function a3_r_loc
298 subroutine a3_tree_clear_cc(tree, iv)
299 type(
a3_t),
intent(inout) :: tree
300 integer,
intent(in) :: iv
301 integer :: lvl, i, id
304 do lvl = lbound(tree%lvls, 1), tree%highest_lvl
306 do i = 1,
size(tree%lvls(lvl)%ids)
307 id = tree%lvls(lvl)%ids(i)
308 call a3_box_clear_cc(tree%boxes(id), iv)
313 end subroutine a3_tree_clear_cc
316 subroutine a3_box_clear_cc(box, iv)
318 integer,
intent(in) :: iv
319 box%cc(:,:,:, iv) = 0
320 end subroutine a3_box_clear_cc
322 subroutine a3_tree_clear_ghostcells(tree, iv)
323 type(
a3_t),
intent(inout) :: tree
324 integer,
intent(in) :: iv
325 integer :: lvl, i, id
328 do lvl = lbound(tree%lvls, 1), tree%highest_lvl
330 do i = 1,
size(tree%lvls(lvl)%ids)
331 id = tree%lvls(lvl)%ids(i)
332 call a3_box_clear_ghostcells(tree%boxes(id), iv)
337 end subroutine a3_tree_clear_ghostcells
340 subroutine a3_box_clear_ghostcells(box, iv)
342 integer,
intent(in) :: iv
347 box%cc(0, :, :, iv) = 0
348 box%cc(nc+1, :, :, iv) = 0
349 box%cc(:, 0, :, iv) = 0
350 box%cc(:, nc+1, :, iv) = 0
351 box%cc(:, :, 0, iv) = 0
352 box%cc(:, :, nc+1, iv) = 0
353 end subroutine a3_box_clear_ghostcells
356 subroutine a3_box_add_cc(box, iv_from, iv_to)
358 integer,
intent(in) :: iv_from, iv_to
359 box%cc(:,:,:, iv_to) = box%cc(:,:,:, iv_to) + box%cc(:,:,:, iv_from)
360 end subroutine a3_box_add_cc
363 subroutine a3_box_sub_cc(box, iv_from, iv_to)
365 integer,
intent(in) :: iv_from, iv_to
366 box%cc(:,:,:, iv_to) = box%cc(:,:,:, iv_to) - box%cc(:,:,:, iv_from)
367 end subroutine a3_box_sub_cc
371 subroutine a3_tree_apply(tree, iv_a, iv_b, op, eps)
372 type(
a3_t),
intent(inout) :: tree
373 integer,
intent(in) :: iv_a, iv_b
374 character(len=*),
intent(in) :: op
375 real(dp),
intent(in),
optional :: eps
376 integer :: lvl, i, id
379 use_eps = sqrt(tiny(1.0_dp))
380 if (
present(eps)) use_eps = eps
383 do lvl = lbound(tree%lvls, 1), tree%highest_lvl
385 do i = 1,
size(tree%lvls(lvl)%ids)
386 id = tree%lvls(lvl)%ids(i)
389 tree%boxes(id)%cc(:, :, :, iv_a) = &
390 tree%boxes(id)%cc(:, :, :, iv_a) + &
391 tree%boxes(id)%cc(:, :, :, iv_b)
393 tree%boxes(id)%cc(:, :, :, iv_a) = &
394 tree%boxes(id)%cc(:, :, :, iv_a) * &
395 tree%boxes(id)%cc(:, :, :, iv_b)
397 tree%boxes(id)%cc(:, :, :, iv_a) = &
398 tree%boxes(id)%cc(:, :, :, iv_a) / &
399 max(tree%boxes(id)%cc(:, :, :, iv_b), eps)
401 error stop
"a3_tree_apply: unknown operand" 407 end subroutine a3_tree_apply
409 subroutine a3_tree_times_cc(tree, ivs, facs)
410 type(
a3_t),
intent(inout) :: tree
411 integer,
intent(in) :: ivs(:)
412 real(dp),
intent(in) :: facs(:)
413 integer :: lvl, i, id, n
415 if (
size(ivs) /=
size(facs)) &
416 error stop
"a3_times_cc: invalid array size" 419 do lvl = lbound(tree%lvls, 1), tree%highest_lvl
421 do i = 1,
size(tree%lvls(lvl)%ids)
422 id = tree%lvls(lvl)%ids(i)
424 call a3_box_times_cc(tree%boxes(id), facs(n), ivs(n))
430 end subroutine a3_tree_times_cc
433 subroutine a3_box_times_cc(box, a, iv)
435 real(dp),
intent(in) :: a
436 integer,
intent(in) :: iv
437 box%cc(:,:,:, iv) = a * box%cc(:,:,:, iv)
438 end subroutine a3_box_times_cc
441 subroutine a3_box_lincomb_cc(box, a, iv_a, b, iv_b)
443 real(dp),
intent(in) :: a, b
444 integer,
intent(in) :: iv_a, iv_b
445 box%cc(:,:,:, iv_b) = a * box%cc(:,:,:, iv_a) + b * box%cc(:,:,:, iv_b)
446 end subroutine a3_box_lincomb_cc
449 subroutine a3_box_copy_cc_to(box_from, iv_from, box_to, iv_to)
451 type(
box3_t),
intent(inout) :: box_to
452 integer,
intent(in) :: iv_from, iv_to
453 box_to%cc(:,:,:, iv_to) = box_from%cc(:,:,:, iv_from)
454 end subroutine a3_box_copy_cc_to
457 subroutine a3_box_copy_cc(box, iv_from, iv_to)
459 integer,
intent(in) :: iv_from, iv_to
460 box%cc(:,:,:, iv_to) = box%cc(:,:,:, iv_from)
461 end subroutine a3_box_copy_cc
464 subroutine a3_boxes_copy_cc(boxes, ids, iv_from, iv_to)
466 integer,
intent(in) :: ids(:), iv_from, iv_to
471 call a3_box_copy_cc(boxes(ids(i)), iv_from, iv_to)
474 end subroutine a3_boxes_copy_cc
477 subroutine a3_tree_copy_cc(tree, iv_from, iv_to)
478 type(
a3_t),
intent(inout) :: tree
479 integer,
intent(in) :: iv_from, iv_to
482 do lvl = lbound(tree%lvls, 1), tree%highest_lvl
483 call a3_boxes_copy_cc(tree%boxes, tree%lvls(lvl)%ids, iv_from, iv_to)
485 end subroutine a3_tree_copy_cc
488 subroutine a3_reduction(tree, box_func, reduction, init_val, out_val)
490 real(dp),
intent(in) :: init_val
491 real(dp),
intent(out) :: out_val
492 real(dp) :: tmp, my_val
493 integer :: i, id, lvl
497 real(dp) function box_func(box)
499 type(
box3_t),
intent(in) :: box
500 end function box_func
503 real(dp) function reduction(a, b)
505 real(dp),
intent(in) :: a, b
506 end function reduction
509 if (.not. tree%ready) stop
"Tree not ready" 514 do lvl = lbound(tree%lvls, 1), tree%highest_lvl
516 do i = 1,
size(tree%lvls(lvl)%leaves)
517 id = tree%lvls(lvl)%leaves(i)
518 tmp = box_func(tree%boxes(id))
519 my_val = reduction(tmp, my_val)
525 out_val = reduction(my_val, out_val)
528 end subroutine a3_reduction
531 subroutine a3_reduction_vec(tree, box_func, reduction, init_val, &
534 integer,
intent(in) :: n_vals
535 real(dp),
intent(in) :: init_val(n_vals)
536 real(dp),
intent(out) :: out_val(n_vals)
537 real(dp) :: tmp(n_vals), my_val(n_vals)
538 integer :: i, id, lvl
542 function box_func(box, n_vals)
result(vec)
544 type(
box3_t),
intent(in) :: box
545 integer,
intent(in) :: n_vals
546 real(dp) :: vec(n_vals)
547 end function box_func
550 function reduction(vec_1, vec_2, n_vals)
result(vec)
552 integer,
intent(in) :: n_vals
553 real(dp),
intent(in) :: vec_1(n_vals), vec_2(n_vals)
554 real(dp) :: vec(n_vals)
555 end function reduction
558 if (.not. tree%ready) stop
"Tree not ready" 563 do lvl = lbound(tree%lvls, 1), tree%highest_lvl
565 do i = 1,
size(tree%lvls(lvl)%leaves)
566 id = tree%lvls(lvl)%leaves(i)
567 tmp = box_func(tree%boxes(id), n_vals)
568 my_val = reduction(tmp, my_val, n_vals)
574 out_val = reduction(my_val, out_val, n_vals)
577 end subroutine a3_reduction_vec
581 subroutine a3_reduction_loc(tree, iv, box_subr, reduction, &
582 init_val, out_val, out_loc)
584 integer,
intent(in) :: iv
585 real(dp),
intent(in) :: init_val
586 real(dp),
intent(out) :: out_val
587 type(
a3_loc_t),
intent(out) :: out_loc
588 real(dp) :: tmp, new_val, my_val
589 integer :: i, id, lvl, tmp_ix(3)
594 subroutine box_subr(box, iv, val, ix)
596 type(
box3_t),
intent(in) :: box
597 integer,
intent(in) :: iv
598 real(dp),
intent(out) :: val
599 integer,
intent(out) :: ix(3)
600 end subroutine box_subr
603 real(dp) function reduction(a, b)
605 real(dp),
intent(in) :: a, b
606 end function reduction
609 if (.not. tree%ready) stop
"Tree not ready" 617 do lvl = lbound(tree%lvls, 1), tree%highest_lvl
619 do i = 1,
size(tree%lvls(lvl)%leaves)
620 id = tree%lvls(lvl)%leaves(i)
621 call box_subr(tree%boxes(id), iv, tmp, tmp_ix)
622 new_val = reduction(tmp, my_val)
623 if (abs(new_val - my_val) > 0)
then 633 new_val = reduction(my_val, out_val)
634 if (abs(new_val - out_val) > 0)
then 635 out_loc%id = my_loc%id
636 out_loc%ix = my_loc%ix
641 end subroutine a3_reduction_loc
645 subroutine a3_tree_max_cc(tree, iv, cc_max, loc)
647 integer,
intent(in) :: iv
648 real(dp),
intent(out) :: cc_max
650 type(
a3_loc_t),
intent(out),
optional :: loc
653 call a3_reduction_loc(tree, iv, box_max_cc, reduce_max, &
654 -huge(1.0_dp)/10, cc_max, tmp_loc)
655 if (
present(loc)) loc = tmp_loc
656 end subroutine a3_tree_max_cc
660 subroutine a3_tree_min_cc(tree, iv, cc_min, loc)
662 integer,
intent(in) :: iv
663 real(dp),
intent(out) :: cc_min
665 type(
a3_loc_t),
intent(out),
optional :: loc
668 call a3_reduction_loc(tree, iv, box_min_cc, reduce_min, &
669 huge(1.0_dp)/10, cc_min, tmp_loc)
671 if (
present(loc)) loc = tmp_loc
672 end subroutine a3_tree_min_cc
675 subroutine a3_tree_max_fc(tree, dim, iv, fc_max, loc)
677 integer,
intent(in) :: dim
678 integer,
intent(in) :: iv
679 real(dp),
intent(out) :: fc_max
681 type(
a3_loc_t),
intent(out),
optional :: loc
686 dim_iv = (dim-1) * tree%n_var_face + iv - 1
688 call a3_reduction_loc(tree, dim_iv, box_max_fc, reduce_max, &
689 -huge(1.0_dp)/10, fc_max, tmp_loc)
690 if (
present(loc)) loc = tmp_loc
691 end subroutine a3_tree_max_fc
693 subroutine box_max_cc(box, iv, val, ix)
694 type(
box3_t),
intent(in) :: box
695 integer,
intent(in) :: iv
696 real(dp),
intent(out) :: val
697 integer,
intent(out) :: ix(3)
701 ix = maxloc(box%cc(1:nc, 1:nc, 1:nc, iv))
702 val = box%cc(ix(1), ix(2), ix(3), iv)
703 end subroutine box_max_cc
705 subroutine box_min_cc(box, iv, val, ix)
706 type(
box3_t),
intent(in) :: box
707 integer,
intent(in) :: iv
708 real(dp),
intent(out) :: val
709 integer,
intent(out) :: ix(3)
713 ix = minloc(box%cc(1:nc, 1:nc, 1:nc, iv))
714 val = box%cc(ix(1), ix(2), ix(3), iv)
715 end subroutine box_min_cc
717 subroutine box_max_fc(box, dim_iv, val, ix)
718 type(
box3_t),
intent(in) :: box
719 integer,
intent(in) :: dim_iv
720 real(dp),
intent(out) :: val
721 integer,
intent(out) :: ix(3)
722 integer :: dim, iv, n_fc, nc, dix(3)
727 n_fc =
size(box%fc, 5)
729 dim = dim_iv / n_fc + 1
731 iv = dim_iv - (dim-1) * n_fc + 1
732 ix = maxloc(box%fc(1:nc+dix(1), 1:nc+dix(2), 1:nc+dix(3), dim, iv))
733 val = box%fc(ix(1), ix(2), ix(3), dim, iv)
734 end subroutine box_max_fc
736 real(dp) function reduce_max(a, b)
737 real(dp),
intent(in) :: a, b
738 reduce_max = max(a, b)
739 end function reduce_max
741 real(dp) function reduce_min(a, b)
742 real(dp),
intent(in) :: a, b
743 reduce_min = min(a, b)
744 end function reduce_min
748 subroutine a3_tree_sum_cc(tree, iv, cc_sum)
750 integer,
intent(in) :: iv
751 real(dp),
intent(out) :: cc_sum
752 real(dp) :: tmp, my_sum, fac
753 integer :: i, id, lvl, nc
755 if (.not. tree%ready) stop
"Tree not ready" 759 do lvl = lbound(tree%lvls, 1), tree%highest_lvl
760 fac = a3_lvl_dr(tree, lvl)**3
763 do i = 1,
size(tree%lvls(lvl)%leaves)
764 id = tree%lvls(lvl)%leaves(i)
765 nc = tree%boxes(id)%n_cell
766 tmp = sum(tree%boxes(id)%cc(1:nc, 1:nc, 1:nc, iv))
767 my_sum = my_sum + fac * tmp
775 end subroutine a3_tree_sum_cc
778 subroutine a3_box_copy_fc(box, iv_from, iv_to)
780 integer,
intent(in) :: iv_from
781 integer,
intent(in) :: iv_to
782 box%fc(:,:,:,:, iv_to) = box%fc(:,:,:,:, iv_from)
783 end subroutine a3_box_copy_fc
786 subroutine a3_boxes_copy_fc(boxes, ids, iv_from, iv_to)
788 integer,
intent(in) :: ids(:)
789 integer,
intent(in) :: iv_from
790 integer,
intent(in) :: iv_to
795 call a3_box_copy_fc(boxes(ids(i)), iv_from, iv_to)
798 end subroutine a3_boxes_copy_fc
801 subroutine a3_tree_copy_fc(tree, iv_from, iv_to)
802 type(
a3_t),
intent(inout) :: tree
803 integer,
intent(in) :: iv_from
804 integer,
intent(in) :: iv_to
807 if (.not. tree%ready) stop
"Tree not ready" 808 do lvl = lbound(tree%lvls, 1), tree%highest_lvl
809 call a3_boxes_copy_fc(tree%boxes, tree%lvls(lvl)%ids, iv_from, iv_to)
811 end subroutine a3_tree_copy_fc
816 pure function a3_n_cell(tree, lvl)
result(n_cell)
818 integer,
intent(in) :: lvl
824 n_cell = tree%n_cell / (2**(1-lvl))
826 end function a3_n_cell
Type specifying the location of a cell.
This module contains all kinds of different 'helper' routines for Afivo. If the number of routines fo...
Subroutine that gets a list of boxes, an id and an array of reals.
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...
Subroutine that gets a box.
Subroutine that gets a box and an array of reals.
Subroutine that gets a list of boxes and a box id.
This module contains the basic types and constants that are used in the 3-dimensional version of Afiv...