Afivo  0.3
m_a2_particles.f90
1 
6  use m_a2_types
7 
8  implicit none
9  private
10 
11  public :: a2_particles_to_grid
12 
13 contains
14 
18  subroutine a2_particles_to_grid(tree, iv, coords, weights, n_particles, &
19  order, id_guess, density, fill_gc)
20  use m_a2_restrict, only: a2_restrict_tree
21  use m_a2_ghostcell, only: a2_gc_tree
22  use m_a2_utils, only: a2_get_id_at, a2_tree_clear_ghostcells
23  type(a2_t), intent(inout) :: tree
24  integer, intent(in) :: iv
25  integer, intent(in) :: n_particles
26  real(dp), intent(in) :: coords(2, n_particles)
27  real(dp), intent(in) :: weights(n_particles)
28  integer, intent(in) :: order
30  integer, intent(inout), optional :: id_guess(n_particles)
32  logical, intent(in), optional :: density
34  logical, intent(in), optional :: fill_gc
35 
36  integer :: n, m
37  integer :: current_thread, current_work
38  integer :: threads_left, work_left
39  integer, allocatable :: ids(:)
40  integer, allocatable :: npart_per_box(:)
41  integer, allocatable :: box_threads(:)
42  integer, allocatable :: threads(:)
43  logical :: as_density
44  logical :: fill_gc_at_end
45 
46  allocate(ids(n_particles))
47  allocate(npart_per_box(-1:tree%highest_id))
48  allocate(box_threads(tree%highest_id))
49  allocate(threads(n_particles))
50 
51  npart_per_box(:) = 0
52  as_density = .true.
53  if (present(density)) as_density = density
54  fill_gc_at_end = .true.
55  if (present(fill_gc)) fill_gc_at_end = fill_gc
56 
57  if (present(id_guess)) then
58  !$omp parallel do reduction(+:npart_per_box)
59  do n = 1, n_particles
60  ids(n) = a2_get_id_at(tree, coords(:, n), &
61  guess=id_guess(n))
62  id_guess(n) = ids(n)
63  npart_per_box(ids(n)) = npart_per_box(ids(n)) + 1
64  end do
65  !$omp end parallel do
66  else
67  !$omp parallel do reduction(+:npart_per_box)
68  do n = 1, n_particles
69  ids(n) = a2_get_id_at(tree, coords(:, n))
70  npart_per_box(ids(n)) = npart_per_box(ids(n)) + 1
71  end do
72  !$omp end parallel do
73  end if
74 
75  if (sum(npart_per_box(-1:0)) > 0) then
76  print *, "a2_particles_to_grid: some are outside domain"
77  m = 0
78  do n = 1, n_particles
79  if (ids(n) <= af_no_box) then
80  print *, n, coords(:, n)
81  m = m + 1
82  end if
83  if (m > 10) then
84  print *, "..."
85  exit
86  end if
87  end do
88  error stop "a2_particles_to_grid: some are outside domain"
89  end if
90 
91  threads_left = af_get_max_threads()
92  current_thread = 0
93  current_work = 0
94  work_left = n_particles
95 
96  do m = 1, tree%highest_id
97  box_threads(m) = current_thread
98  current_work = current_work + npart_per_box(m)
99 
100  if (current_work > work_left/threads_left) then
101  current_thread = current_thread + 1
102  threads_left = threads_left - 1
103  work_left = work_left - current_work
104  current_work = 0
105  end if
106  end do
107 
108  !$omp parallel do
109  do n = 1, n_particles
110  threads(n) = box_threads(ids(n))
111  end do
112  !$omp end parallel do
113 
114  ! Set density to zero
115  call a2_tree_clear_ghostcells(tree, iv)
116 
117  select case (order)
118  case (0)
119  call particles_to_grid_0(tree, iv, coords, weights, ids, &
120  threads, n_particles, as_density)
121  case (1)
122  call particles_to_grid_1(tree, iv, coords, weights, ids, &
123  threads, n_particles, as_density)
124  call tree_add_from_ghostcells(tree, iv)
125  case default
126  error stop "a2_particles_to_grid: Invalid interpolation order"
127  end select
128 
129  call a2_restrict_tree(tree, iv)
130 
131  if (fill_gc_at_end) then
132  if (.not. tree%has_cc_method(iv)) then
133  print *, "Variable with index ", iv, "has no cc_method"
134  print *, "do this with call a2_set_cc_methods(tree, iv, ...)"
135  error stop "a2_particles_to_grid: no ghost cell method defined"
136  else
137  call a2_gc_tree(tree, iv)
138  end if
139  end if
140  end subroutine a2_particles_to_grid
141 
142  subroutine particles_to_grid_0(tree, iv, coords, weights, ids, &
143  threads, n_particles, density)
144  use omp_lib
145  type(a2_t), intent(inout) :: tree
146  integer, intent(in) :: iv
147  integer, intent(in) :: n_particles
148  real(dp), intent(in) :: coords(2, n_particles)
149  real(dp), intent(in) :: weights(n_particles)
150  integer, intent(in) :: ids(n_particles)
151  integer, intent(in) :: threads(n_particles)
152  logical, intent(in) :: density
153  integer :: n, thread_id, ix(2)
154 
155  !$omp parallel private(n, thread_id, ix)
156  thread_id = omp_get_thread_num()
157 
158  do n = 1, n_particles
159  if (threads(n) /= thread_id) cycle
160  ! Handle this particle
161  ix = a2_cc_ix(tree%boxes(ids(n)), coords(:, n))
162 
163  ! Fix indices for points exactly on the boundaries of a box (which could
164  ! get a ghost cell index)
165  where (ix < 1) ix = 1
166  where (ix > tree%n_cell) ix = tree%n_cell
167 
168  if (density) then
169  tree%boxes(ids(n))%cc(ix(1), ix(2), iv) = &
170  tree%boxes(ids(n))%cc(ix(1), ix(2), iv) + &
171  weights(n) / tree%boxes(ids(n))%dr**2
172  else
173  tree%boxes(ids(n))%cc(ix(1), ix(2), iv) = &
174  tree%boxes(ids(n))%cc(ix(1), ix(2), iv) + &
175  weights(n)
176  end if
177  end do
178  !$omp end parallel
179  end subroutine particles_to_grid_0
180 
183  subroutine particles_to_grid_1(tree, iv, coords, weights, ids, &
184  threads, n_particles, density)
185  use omp_lib
186  type(a2_t), intent(inout) :: tree
187  integer, intent(in) :: iv
188  integer, intent(in) :: n_particles
189  real(dp), intent(in) :: coords(2, n_particles)
190  real(dp), intent(in) :: weights(n_particles)
191  integer, intent(in) :: ids(n_particles)
192  integer, intent(in) :: threads(n_particles)
193  logical, intent(in) :: density
194  real(dp) :: tmp(2), inv_dr
195  real(dp) :: wu(2), wl(2), w(2, 2)
196  integer :: id, ix(2), n, thread_id
197 
198  !$omp parallel private(n, inv_dr, tmp, thread_id, ix, id, wu, wl, w)
199  thread_id = omp_get_thread_num()
200 
201  do n = 1, n_particles
202  if (threads(n) /= thread_id) cycle
203 
204  id = ids(n)
205  inv_dr = 1.0_dp/tree%boxes(id)%dr
206  tmp = (coords(:, n) - tree%boxes(id)%r_min) * inv_dr + 0.5_dp
207  ix = floor(tmp)
208  wu = tmp - ix
209  wl = 1 - wu
210 
211  w(:, 1) = [wl(1), wu(1)] * wl(2)
212  w(:, 2) = [wl(1), wu(1)] * wu(2)
213 
214  ! Linear interpolation
215  if (density) then
216  tree%boxes(id)%cc(ix(1):ix(1)+1, ix(2):ix(2)+1, iv) = &
217  tree%boxes(id)%cc(ix(1):ix(1)+1, ix(2):ix(2)+1, iv) + &
218  w * weights(n) / tree%boxes(id)%dr**2
219  else
220  tree%boxes(id)%cc(ix(1):ix(1)+1, ix(2):ix(2)+1, iv) = &
221  tree%boxes(id)%cc(ix(1):ix(1)+1, ix(2):ix(2)+1, iv) + &
222  w * weights(n)
223  end if
224  end do
225  !$omp end parallel
226 
227  end subroutine particles_to_grid_1
228 
229  subroutine tree_add_from_ghostcells(tree, iv)
230  type(a2_t), intent(inout) :: tree
231  integer, intent(in) :: iv
232  integer :: lvl, i, id
233 
234  !$omp parallel private(lvl, i, id)
235  do lvl = 1, tree%highest_lvl
236  !$omp do
237  do i = 1, size(tree%lvls(lvl)%leaves)
238  id = tree%lvls(lvl)%leaves(i)
239  call add_from_ghostcells(tree%boxes, id, iv)
240  end do
241  !$omp end do nowait
242  end do
243  !$omp end parallel
244  end subroutine tree_add_from_ghostcells
245 
246  subroutine add_from_ghostcells(boxes, id, iv)
247  type(box2_t), intent(inout) :: boxes(:)
248  integer, intent(in) :: id
249  integer, intent(in) :: iv
250  integer :: i, j, i0(2), i1(2)
251  integer :: n0(2), n1(2), nb_id, nc
252  logical :: copy_own
253 
254  nc = boxes(id)%n_cell
255 
256  do j = -1, 1; do i = -1, 1
257  if (all([i, j] == 0)) cycle
258 
259  nb_id = boxes(id)%neighbor_mat(i, j)
260 
261  copy_own = .false.
262 
263  if (nb_id <= af_no_box) then
264  copy_own = .true.
265  else if (nb_id > af_no_box) then
266  if (a2_has_children(boxes(nb_id))) copy_own = .true.
267  end if
268 
269  if (copy_own) then
270  ! Physical boundary
271  i0 = 1
272  i1 = nc
273  n0 = 1
274  n1 = nc
275 
276  where ([i, j] == 1)
277  i0 = nc
278  n0 = nc+1
279  n1 = nc+1
280  elsewhere ([i, j] == -1)
281  i1 = 1
282  n0 = 0
283  n1 = 0
284  end where
285 
286  boxes(id)%cc(i0(1):i1(1), i0(2):i1(2), iv) = &
287  boxes(id)%cc(i0(1):i1(1), i0(2):i1(2), iv) + &
288  boxes(id)%cc(n0(1):n1(1), n0(2):n1(2), iv)
289  else
290  i0 = 1
291  i1 = nc
292  n0 = 1
293  n1 = nc
294  where ([i, j] == 1)
295  i0 = nc
296  n0 = 0
297  n1 = 0
298  elsewhere ([i, j] == -1)
299  i1 = 1
300  n0 = nc+1
301  n1 = nc+1
302  end where
303 
304  boxes(id)%cc(i0(1):i1(1), i0(2):i1(2), iv) = &
305  boxes(id)%cc(i0(1):i1(1), i0(2):i1(2), iv) + &
306  boxes(nb_id)%cc(n0(1):n1(1), n0(2):n1(2), iv)
307  end if
308  end do; end do
309  end subroutine add_from_ghostcells
310 
311 end module m_a2_particles
This module contains all kinds of different &#39;helper&#39; routines for Afivo. If the number of routines fo...
Definition: m_a2_utils.f90:5
This module contains routines related to the filling of ghost cells. Note that corner ghost cells are...
Type which stores all the boxes and levels, as well as some information about the number of boxes...
Definition: m_a2_types.f90:93
This module contains the basic types and constants that are used in the 2-dimensional version of Afiv...
Definition: m_a2_types.f90:5
This module contains routines for restriction: going from fine to coarse variables.
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_a2_types.f90:71
This module contains routines related to , which can interpolate &#39;to&#39; the grid and &#39;from&#39; the grid (u...