PartMC  2.6.1
aero_sorted.F90
Go to the documentation of this file.
1 ! Copyright (C) 2011, 2012 Nicole Riemer and Matthew West
2 ! Licensed under the GNU General Public License version 2 or (at your
3 ! option) any later version. See the file COPYING for details.
4 
5 !> \file
6 !> The pmc_aero_sorted module.
7 
8 !> The aero_sorted_t structure and assocated subroutines.
10 
15  use pmc_aero_data
17  use pmc_bin_grid
18  use pmc_mpi
19 
20  !> Sorting of particles into bins.
21  !!
22  !! Two different bin-sortings are maintained, one per size bin and
23  !! weight class, and the other per weight group and weight class.
24  !!
25  !! A particle can thus be identified by its position \c i_part in an
26  !! \c aero_particle_array_t, or by an entry in one of the two
27  !! sortings.
28  !!
29  !! For example, for size bin \c i_bin and weight class \c i_class,
30  !! the number of particles with this size and class are
31  !! <pre>
32  !! n = integer_varray_n_entry(aero_sorted%size_class%inverse(i_bin, i_class))
33  !! </pre>
34  !! For particle number \c i_entry in this size/class bin, the
35  !! particle number is
36  !! <pre>
37  !! i_part = aero_sorted%%size_class%%inverse(i_bin, i_class)%%entry(i_entry)
38  !! </pre>
39  !! For particle number \c i_part, the size bin and weight class are
40  !! <pre>
41  !! i_bin = aero_sorted%%size_class%%forward1%%entry(i_part)
42  !! i_class = aero_sorted%%size_class%%forward2%%entry(i_part)
43  !! </pre>
44  !!
45  !! Similar relationships hold for \c aero_sorted%%group_class which
46  !! sorts particles per weight group/class.
48  !> Bin grid for sorting.
49  type(bin_grid_t) :: bin_grid
50  !> Map of size bin and weight class numbers.
51  type(integer_rmap2_t) :: size_class
52  !> Map of weight group and weight class numbers.
53  type(integer_rmap2_t) :: group_class
54  !> Whether coagulation kernel bounds are valid.
55  logical :: coag_kernel_bounds_valid
56  !> Coagulation kernel lower bound [<tt>bin_grid_size(bin_grid) x
57  !> bin_grid_size(bin_grid)</tt>].
58  real(kind=dp), allocatable, dimension(:,:) :: coag_kernel_min
59  !> Coagulation kernel upper bound [<tt>bin_grid_size(bin_grid) x
60  !> bin_grid_size(bin_grid)</tt>].
61  real(kind=dp), allocatable, dimension(:,:) :: coag_kernel_max
62  !> Whether particle removal rate bounds are valid.
63  logical :: removal_rate_bounds_valid
64  !> Particle removal rate upper bound [<tt>bin_grid_size(bin_grid)</tt>].
65  real(kind=dp), allocatable, dimension(:) :: removal_rate_max
66  end type aero_sorted_t
67 
68  !> How many size bins to use per decade of particle radius.
69  real(kind=dp), parameter :: aero_sorted_bins_per_decade = 10d0
70  !> Factor to extend size grid beyond largest/smallest particles.
71  real(kind=dp), parameter :: aero_sorted_bin_over_factor = 10d0
72  !> Size grid extension factor when we should regenerate grid.
73  real(kind=dp), parameter :: aero_sorted_bin_safety_factor = 3d0
74 
75 contains
76 
77 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
78 
79  !> Returns the number of size bins.
80  integer function aero_sorted_n_bin(aero_sorted)
81 
82  !> Aerosol sorting to use.
83  type(aero_sorted_t), intent(in) :: aero_sorted
84 
85  aero_sorted_n_bin = size(aero_sorted%size_class%inverse, 1)
86 
87  end function aero_sorted_n_bin
88 
89 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
90 
91  !> Returns the number of weight groups.
92  integer function aero_sorted_n_group(aero_sorted)
93 
94  !> Aerosol sorting to use.
95  type(aero_sorted_t), intent(in) :: aero_sorted
96 
97  aero_sorted_n_group = size(aero_sorted%group_class%inverse, 1)
98 
99  end function aero_sorted_n_group
100 
101 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
102 
103  !> Returns the number of weight classes.
104  integer function aero_sorted_n_class(aero_sorted)
105 
106  !> Aerosol sorting to use.
107  type(aero_sorted_t), intent(in) :: aero_sorted
108 
109  aero_sorted_n_class = size(aero_sorted%size_class%inverse, 2)
110 
111  end function aero_sorted_n_class
112 
113 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
114 
115  !> Set the bin grid to be used for sorting.
116  subroutine aero_sorted_set_bin_grid(aero_sorted, bin_grid, n_group, n_class)
117 
118  !> Aerosol sorted.
119  type(aero_sorted_t), intent(inout) :: aero_sorted
120  !> Bin grid.
121  type(bin_grid_t), intent(in) :: bin_grid
122  !> Number of weight groups.
123  integer, intent(in) :: n_group
124  !> Number of weight classes.
125  integer, intent(in) :: n_class
126 
127  integer :: n_bin
128 
129  n_bin = bin_grid_size(bin_grid)
130  call integer_rmap2_set_ranges(aero_sorted%size_class, n_bin, n_class)
131  call integer_rmap2_set_ranges(aero_sorted%group_class, n_group, n_class)
132  aero_sorted%coag_kernel_bounds_valid = .false.
133  if (allocated(aero_sorted%coag_kernel_min)) then
134  deallocate(aero_sorted%coag_kernel_min)
135  end if
136  allocate(aero_sorted%coag_kernel_min(n_bin, n_bin))
137  if (allocated(aero_sorted%coag_kernel_max)) then
138  deallocate(aero_sorted%coag_kernel_max)
139  end if
140  allocate(aero_sorted%coag_kernel_max(n_bin, n_bin))
141  aero_sorted%removal_rate_bounds_valid = .false.
142  if (allocated(aero_sorted%removal_rate_max)) then
143  deallocate(aero_sorted%removal_rate_max)
144  end if
145  allocate(aero_sorted%removal_rate_max(n_bin))
146  aero_sorted%bin_grid = bin_grid
147 
148  end subroutine aero_sorted_set_bin_grid
149 
150 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
151 
152  !> Discard particles that don't fit the bin grid.
153  subroutine aero_sorted_discard_outside_grid(aero_sorted, &
154  aero_particle_array, aero_data)
155 
156  !> Aerosol sorted.
157  type(aero_sorted_t), intent(in) :: aero_sorted
158  !> Aerosol particles to discard from.
159  type(aero_particle_array_t), intent(inout) :: aero_particle_array
160  !> Aerosol data.
161  type(aero_data_t), intent(in) :: aero_data
162 
163  integer :: i_part, i_bin
164 
165  ! Work backwards so we only shift particles that we've already
166  ! tested.
167  do i_part = aero_particle_array%n_part,1,-1
168  i_bin = aero_sorted_particle_in_bin(aero_sorted, &
169  aero_particle_array%particle(i_part), aero_data)
170  if ((i_bin < 1) .or. (i_bin > bin_grid_size(aero_sorted%bin_grid))) then
171  call warn_msg(954800836, "particle ID " &
172  // trim(integer_to_string( &
173  aero_particle_array%particle(i_part)%id)) &
174  // " outside of bin_grid, discarding")
175  call aero_particle_array_remove_particle(aero_particle_array, &
176  i_part)
177  end if
178  end do
179 
180  end subroutine aero_sorted_discard_outside_grid
181 
182 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
183 
184  !> Sort the particles.
185  subroutine aero_sorted_sort_particles(aero_sorted, aero_particle_array, &
186  aero_data)
187 
188  !> Aerosol sorted.
189  type(aero_sorted_t), intent(inout) :: aero_sorted
190  !> Aerosol particles to sort.
191  type(aero_particle_array_t), intent(in) :: aero_particle_array
192  !> Aerosol data.
193  type(aero_data_t), intent(in) :: aero_data
194 
195  integer :: i_part, i_bin, i_group, i_class
196 
197  call integer_rmap2_zero(aero_sorted%size_class)
198  call integer_rmap2_zero(aero_sorted%group_class)
199 
200  do i_part = 1,aero_particle_array%n_part
201  i_bin = aero_sorted_particle_in_bin(aero_sorted, &
202  aero_particle_array%particle(i_part), aero_data)
203  i_group = aero_particle_array%particle(i_part)%weight_group
204  i_class = aero_particle_array%particle(i_part)%weight_class
205  call integer_rmap2_append(aero_sorted%size_class, i_bin, i_class)
206  call integer_rmap2_append(aero_sorted%group_class, i_group, i_class)
207  end do
208 
209  end subroutine aero_sorted_sort_particles
210 
211 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
212 
213  !> Remake a sorting if particles are getting too close to the edges.
214  subroutine aero_sorted_remake_if_needed(aero_sorted, aero_particle_array, &
215  aero_data, valid_sort, n_group, n_class, bin_grid, all_procs_same)
216 
217  !> Aerosol sorted to (possibly) remake.
218  type(aero_sorted_t), intent(inout) :: aero_sorted
219  !> Aerosol particles to sort.
220  type(aero_particle_array_t), intent(inout) :: aero_particle_array
221  !> Aerosol data.
222  type(aero_data_t), intent(in) :: aero_data
223  !> Whether the given aero_sorted is valid.
224  logical, intent(in) :: valid_sort
225  !> Number of weight groups.
226  integer, optional, intent(in) :: n_group
227  !> Number of weight classes.
228  integer, optional, intent(in) :: n_class
229  !> An optional bin_grid to use for the sort.
230  type(bin_grid_t), optional, intent(in) :: bin_grid
231  !> Whether all processors should use the same bin grid.
232  logical, optional, intent(in) :: all_procs_same
233 
234  integer :: i_bin, i_bin_min, i_bin_max, i_part, n_bin, use_n_group
235  integer :: use_n_class
236  real(kind=dp) :: r, r_min, r_max, grid_r_min, grid_r_max
237  real(kind=dp) :: local_r_min, local_r_max
238  logical :: need_new_bin_grid
239  type(bin_grid_t) :: new_bin_grid
240 
241  if (present(n_group)) then
242  call assert(267881270, present(n_class))
243  use_n_group = n_group
244  use_n_class = n_class
245  else
246  call assert(352582858, valid_sort)
247  use_n_group = aero_sorted_n_group(aero_sorted)
248  use_n_class = aero_sorted_n_class(aero_sorted)
249  end if
250 
251  if (present(bin_grid)) then
252  call aero_sorted_set_bin_grid(aero_sorted, bin_grid, use_n_group, &
253  use_n_class)
254  call aero_sorted_discard_outside_grid(aero_sorted, &
255  aero_particle_array, aero_data)
256  call aero_sorted_sort_particles(aero_sorted, aero_particle_array, &
257  aero_data)
258  return
259  end if
260 
261  need_new_bin_grid = .false.
262 
263  ! determine r_min and r_max
264  r_min = 0d0
265  r_max = 0d0
266  if (valid_sort) then
267  ! use bin data to avoid looping over all particles
268  i_bin_min = 0
269  i_bin_max = 0
270  do i_bin = 1,bin_grid_size(aero_sorted%bin_grid)
271  if (sum(integer_varray_n_entry( &
272  aero_sorted%size_class%inverse(i_bin, :))) > 0) then
273  if (i_bin_min == 0) then
274  i_bin_min = i_bin
275  end if
276  i_bin_max = i_bin
277  end if
278  end do
279 
280  if (i_bin_min == 0) then
281  ! there aren't any particles
282  call assert(333430891, i_bin_max == 0)
283  if (bin_grid_size(aero_sorted%bin_grid) > 0) then
284  ! take r_min = upper edge, etc.
285  r_min = aero_sorted%bin_grid%edges( &
286  bin_grid_size(aero_sorted%bin_grid) + 1)
287  r_max = aero_sorted%bin_grid%edges(1)
288  end if
289  else
290  r_min = aero_sorted%bin_grid%edges(i_bin_min)
291  r_max = aero_sorted%bin_grid%edges(i_bin_max + 1)
292  end if
293  else
294  ! no bin data, need to loop over all particles
295  do i_part = 1,aero_particle_array%n_part
296  r = aero_particle_radius(aero_particle_array%particle(i_part), &
297  aero_data)
298  if (i_part == 1) then
299  r_min = r
300  r_max = r
301  else
302  r_min = min(r_min, r)
303  r_max = max(r_max, r)
304  end if
305  end do
306  end if
307 
308  if (present(all_procs_same)) then
309  if (all_procs_same) then
310  ! take global min/max
311  local_r_max = r_max
312  call pmc_mpi_allreduce_max_real(local_r_max, r_max)
313  ! don't contaminate global min with zeros
314  if (r_min == 0d0) then
315  local_r_min = r_max
316  else
317  local_r_min = r_min
318  end if
319  call pmc_mpi_allreduce_min_real(local_r_min, r_min)
320 
321  ! check that all the bin grids are really the same
322  if (.not. pmc_mpi_allequal_bin_grid(aero_sorted%bin_grid)) then
323  need_new_bin_grid = .true.
324  end if
325  end if
326  end if
327 
328  ! no particles and no existing useful bin_grid
329  if (r_max == 0d0) then
330  if (valid_sort) return
331  call bin_grid_make(new_bin_grid, bin_grid_type_log, n_bin=0, min=0d0, &
332  max=0d0)
333  call aero_sorted_set_bin_grid(aero_sorted, new_bin_grid, use_n_group, &
334  use_n_class)
335  return
336  end if
337 
338  if (bin_grid_size(aero_sorted%bin_grid) < 1) then
339  need_new_bin_grid = .true.
340  else
341  grid_r_min = aero_sorted%bin_grid%edges(1)
342  grid_r_max = aero_sorted%bin_grid%edges( &
343  bin_grid_size(aero_sorted%bin_grid) + 1)
344 
345  ! We don't check to see whether we could make the bin grid
346  ! smaller, as there doesn't seem much point. It would be easy
347  ! to add if desired.
348  if ((r_min / grid_r_min < aero_sorted_bin_safety_factor) &
349  .or. (grid_r_max / r_max < aero_sorted_bin_safety_factor)) then
350  need_new_bin_grid = .true.
351  end if
352  end if
353 
354  if (need_new_bin_grid) then
355  grid_r_min = r_min / aero_sorted_bin_over_factor
356  grid_r_max = r_max * aero_sorted_bin_over_factor
357  n_bin = ceiling((log10(grid_r_max) - log10(grid_r_min)) &
359  call bin_grid_make(new_bin_grid, bin_grid_type_log, n_bin, grid_r_min, &
360  grid_r_max)
361  call aero_sorted_set_bin_grid(aero_sorted, new_bin_grid, use_n_group, &
362 
363  use_n_class)
364  call aero_sorted_sort_particles(aero_sorted, aero_particle_array, &
365  aero_data)
366  else
367  if (.not. valid_sort) then
368  call aero_sorted_sort_particles(aero_sorted, aero_particle_array, &
369  aero_data)
370  end if
371  end if
372 
373  end subroutine aero_sorted_remake_if_needed
374 
375 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
376 
377  !> Find the bin number that contains a given particle.
378  integer function aero_sorted_particle_in_bin(aero_sorted, aero_particle, &
379  aero_data)
380 
381  !> Aerosol sort.
382  type(aero_sorted_t), intent(in) :: aero_sorted
383  !> Particle.
384  type(aero_particle_t), intent(in) :: aero_particle
385  !> Aerosol data.
386  type(aero_data_t), intent(in) :: aero_data
387 
388  aero_sorted_particle_in_bin = bin_grid_find(aero_sorted%bin_grid, &
389  aero_particle_radius(aero_particle, aero_data))
390 
391  end function aero_sorted_particle_in_bin
392 
393 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
394 
395  !> Add a new particle to both an aero_sorted and the corresponding
396  !> aero_particle_array.
397  subroutine aero_sorted_add_particle(aero_sorted, aero_particle_array, &
398  aero_particle, aero_data, allow_resort)
399 
400  !> Sorted particle structure.
401  type(aero_sorted_t), intent(inout) :: aero_sorted
402  !> Aerosol particles.
403  type(aero_particle_array_t), intent(inout) :: aero_particle_array
404  !> Particle to add.
405  type(aero_particle_t), intent(in) :: aero_particle
406  !> Aerosol data.
407  type(aero_data_t), intent(in) :: aero_data
408  !> Whether to allow a resort due to the add.
409  logical, optional, intent(in) :: allow_resort
410 
411  integer :: i_bin, i_group, i_class, n_bin, n_group, n_class
412 
413  i_bin = aero_sorted_particle_in_bin(aero_sorted, aero_particle, &
414  aero_data)
415  i_group = aero_particle%weight_group
416  i_class = aero_particle%weight_class
417 
418  n_bin = bin_grid_size(aero_sorted%bin_grid)
419  n_group = aero_sorted_n_group(aero_sorted)
420  n_class = aero_sorted_n_class(aero_sorted)
421  call assert(417177855, (i_group >= 1) .and. (i_group <= n_group))
422  call assert(233133947, (i_class >= 1) .and. (i_class <= n_class))
423 
424  ! add the particle to the aero_particle_array
425  call aero_particle_array_add_particle(aero_particle_array, aero_particle)
426 
427  if ((i_bin < 1) .or. (i_bin > n_bin)) then
428  ! particle doesn't fit in the current bin_grid, so remake the
429  ! bin_grid if we are allowed
430  ! if bin_grid is unallocated, then i_bin will be -1 thus will remake
431  ! the bin_grid.
432  if (present(allow_resort)) then
433  if (.not. allow_resort) then
434  ! FIXME: this could be avoided if the new bin_grid was an
435  ! extension of the old one (only added bins, first bins
436  ! are the same)
437  call die_msg(134572570, "particle outside of bin_grid: " &
438  // "try reducing the timestep del_t")
439  end if
440  end if
441  call aero_sorted_remake_if_needed(aero_sorted, aero_particle_array, &
442  aero_data, valid_sort=.false., n_group=n_group, n_class=n_class)
443  else
444  ! particle fits in the current bin_grid
445  call integer_rmap2_append(aero_sorted%size_class, i_bin, i_class)
446  call integer_rmap2_append(aero_sorted%group_class, i_group, i_class)
447  end if
448 
449  end subroutine aero_sorted_add_particle
450 
451 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
452 
453  !> Remove a particle from both an aero_sorted and the corresponding
454  !> aero_particle_array.
455  subroutine aero_sorted_remove_particle(aero_sorted, aero_particle_array, &
456  i_part)
457 
458  !> Sorted particle structure.
459  type(aero_sorted_t), intent(inout) :: aero_sorted
460  !> Aerosol particles.
461  type(aero_particle_array_t), intent(inout) :: aero_particle_array
462  !> Index of particle to remove.
463  integer, intent(in) :: i_part
464 
465  ! all of these shift the last item into the newly-empty slot
466  call aero_particle_array_remove_particle(aero_particle_array, i_part)
467  call integer_rmap2_remove(aero_sorted%size_class, i_part)
468  call integer_rmap2_remove(aero_sorted%group_class, i_part)
469 
470  end subroutine aero_sorted_remove_particle
471 
472 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
473 
474  !> Move a particle to a different bin and group.
475  subroutine aero_sorted_move_particle(aero_sorted, i_part, new_bin, &
476  new_group, new_class)
477 
478  !> Aerosol sorted.
479  type(aero_sorted_t), intent(inout) :: aero_sorted
480  !> Particle number to move.
481  integer, intent(in) :: i_part
482  !> New bin to move particle to.
483  integer, intent(in) :: new_bin
484  !> New weight group to move particle to.
485  integer, intent(in) :: new_group
486  !> New weight class to move particle to.
487  integer, intent(in) :: new_class
488 
489  call integer_rmap2_change(aero_sorted%size_class, i_part, new_bin, &
490  new_class)
491  call integer_rmap2_change(aero_sorted%group_class, i_part, new_group, &
492  new_class)
493 
494  end subroutine aero_sorted_move_particle
495 
496 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
497 
498  !> Check sorting.
499  subroutine aero_sorted_check(aero_sorted, aero_particle_array, &
500  aero_data, n_group, n_class, continue_on_error)
501 
502  !> Aerosol sorted to check.
503  type(aero_sorted_t), intent(in) :: aero_sorted
504  !> Aerosol particles.
505  type(aero_particle_array_t), intent(in) :: aero_particle_array
506  !> Aerosol data.
507  type(aero_data_t), intent(in) :: aero_data
508  !> Number of weight groups.
509  integer, optional, intent(in) :: n_group
510  !> Number of weight classes.
511  integer, optional, intent(in) :: n_class
512  !> Whether to continue despite error.
513  logical, intent(in) :: continue_on_error
514 
515  integer :: i_part, i_bin
516 
517  call integer_rmap2_check(aero_sorted%size_class, "size_class", &
518  n_domain=aero_particle_array%n_part, &
519  n_range_1=bin_grid_size(aero_sorted%bin_grid), n_range_2=n_class, &
520  continue_on_error=continue_on_error)
521  do i_part = 1,aero_particle_array%n_part
522  i_bin = aero_sorted_particle_in_bin(aero_sorted, &
523  aero_particle_array%particle(i_part), aero_data)
524  if ((i_bin /= aero_sorted%size_class%forward1%entry(i_part)) &
525  .or. (i_bin /= aero_sorted%size_class%forward1%entry(i_part))) then
526  write(0,*) 'ERROR aero_sorted A: ', "size_class"
527  write(0,*) 'i_part', i_part
528  write(0,*) 'i_bin', i_bin
529  write(0,*) 'aero_sorted%size_class%forward1%entry(i_part)', &
530  aero_sorted%size_class%forward1%entry(i_part)
531  write(0,*) 'aero_sorted%size_class%forward2%entry(i_part)', &
532  aero_sorted%size_class%forward2%entry(i_part)
533  call assert(565030916, continue_on_error)
534  end if
535  end do
536 
537  call integer_rmap2_check(aero_sorted%group_class, "group_class", &
538  n_domain=aero_particle_array%n_part, &
539  n_range_1=n_group, n_range_2=n_class, &
540  continue_on_error=continue_on_error)
541  do i_part = 1,aero_particle_array%n_part
542  if ((aero_particle_array%particle(i_part)%weight_group &
543  /= aero_sorted%group_class%forward1%entry(i_part)) &
544  .or. (aero_particle_array%particle(i_part)%weight_class &
545  /= aero_sorted%group_class%forward2%entry(i_part))) then
546  write(0,*) 'ERROR aero_sorted B: ', "group_class"
547  write(0,*) 'i_part', i_part
548  write(0,*) 'aero_particle_array%particle(i_part)%weight_group', &
549  aero_particle_array%particle(i_part)%weight_group
550  write(0,*) 'aero_particle_array%particle(i_part)%weight_class', &
551  aero_particle_array%particle(i_part)%weight_class
552  write(0,*) 'aero_sorted%group_class%forward1%entry(i_part)', &
553  aero_sorted%group_class%forward1%entry(i_part)
554  write(0,*) 'aero_sorted%group_class%forward2%entry(i_part)', &
555  aero_sorted%group_class%forward2%entry(i_part)
556  call assert(803595412, continue_on_error)
557  end if
558  end do
559 
560  end subroutine aero_sorted_check
561 
562 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
563 
564  !> Determines the number of bytes required to pack the given value.
565  integer function pmc_mpi_pack_size_aero_sorted(val)
566 
567  !> Value to pack.
568  type(aero_sorted_t), intent(in) :: val
569 
570  integer :: total_size
571 
572  total_size = 0
573  total_size = total_size + pmc_mpi_pack_size_bin_grid(val%bin_grid)
574  total_size = total_size + pmc_mpi_pack_size_integer_rmap2(val%size_class)
575  total_size = total_size + pmc_mpi_pack_size_integer_rmap2(val%group_class)
576  pmc_mpi_pack_size_aero_sorted = total_size
577 
578  end function pmc_mpi_pack_size_aero_sorted
579 
580 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
581 
582  !> Packs the given value into the buffer, advancing position.
583  subroutine pmc_mpi_pack_aero_sorted(buffer, position, val)
584 
585  !> Memory buffer.
586  character, intent(inout) :: buffer(:)
587  !> Current buffer position.
588  integer, intent(inout) :: position
589  !> Value to pack.
590  type(aero_sorted_t), intent(in) :: val
591 
592 #ifdef PMC_USE_MPI
593  integer :: prev_position
594 
595  prev_position = position
596  call pmc_mpi_pack_bin_grid(buffer, position, val%bin_grid)
597  call pmc_mpi_pack_integer_rmap2(buffer, position, val%size_class)
598  call pmc_mpi_pack_integer_rmap2(buffer, position, val%group_class)
599  call assert(786981367, &
600  position - prev_position <= pmc_mpi_pack_size_aero_sorted(val))
601 #endif
602 
603  end subroutine pmc_mpi_pack_aero_sorted
604 
605 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
606 
607  !> Unpacks the given value from the buffer, advancing position.
608  subroutine pmc_mpi_unpack_aero_sorted(buffer, position, val)
609 
610  !> Memory buffer.
611  character, intent(inout) :: buffer(:)
612  !> Current buffer position.
613  integer, intent(inout) :: position
614  !> Value to pack.
615  type(aero_sorted_t), intent(inout) :: val
616 
617 #ifdef PMC_USE_MPI
618  integer :: prev_position, n_bin, n_group, n_class
619 
620  prev_position = position
621  call pmc_mpi_unpack_bin_grid(buffer, position, val%bin_grid)
622  call pmc_mpi_unpack_integer_rmap2(buffer, position, val%size_class)
623  call pmc_mpi_unpack_integer_rmap2(buffer, position, val%group_class)
624  call assert(703866072, &
625  position - prev_position <= pmc_mpi_pack_size_aero_sorted(val))
626 #endif
627 
628  end subroutine pmc_mpi_unpack_aero_sorted
629 
630 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
631 
632 end module pmc_aero_sorted
pmc_aero_particle::aero_particle_t
Single aerosol particle data structure.
Definition: aero_particle.F90:26
pmc_aero_particle_array::aero_particle_array_t
1-D array of particles, used by aero_state to store the particles.
Definition: aero_particle_array.F90:41
pmc_mpi
Wrapper functions for MPI.
Definition: mpi.F90:13
pmc_aero_sorted::aero_sorted_bins_per_decade
real(kind=dp), parameter aero_sorted_bins_per_decade
How many size bins to use per decade of particle radius.
Definition: aero_sorted.F90:69
pmc_integer_rmap2
The integer_rmap2_t structure and assocated subroutines.
Definition: integer_rmap2.F90:9
pmc_aero_sorted::aero_sorted_particle_in_bin
integer function aero_sorted_particle_in_bin(aero_sorted, aero_particle, aero_data)
Find the bin number that contains a given particle.
Definition: aero_sorted.F90:380
pmc_aero_particle
The aero_particle_t structure and associated subroutines.
Definition: aero_particle.F90:9
pmc_aero_sorted::aero_sorted_check
subroutine aero_sorted_check(aero_sorted, aero_particle_array, aero_data, n_group, n_class, continue_on_error)
Check sorting.
Definition: aero_sorted.F90:501
pmc_integer_rmap2::pmc_mpi_pack_integer_rmap2
subroutine pmc_mpi_pack_integer_rmap2(buffer, position, val)
Packs the given value into the buffer, advancing position.
Definition: integer_rmap2.F90:409
pmc_mpi::pmc_mpi_allreduce_min_real
subroutine pmc_mpi_allreduce_min_real(val, val_min)
Computes the minimum of val across all processes, storing the result in val_min on all processes.
Definition: mpi.F90:1376
pmc_util::die_msg
subroutine die_msg(code, error_msg)
Error immediately.
Definition: util.F90:134
pmc_aero_sorted::aero_sorted_n_bin
integer function aero_sorted_n_bin(aero_sorted)
Returns the number of size bins.
Definition: aero_sorted.F90:81
pmc_constants::dp
integer, parameter dp
Kind of a double precision real number.
Definition: constants.F90:12
pmc_aero_sorted::aero_sorted_bin_safety_factor
real(kind=dp), parameter aero_sorted_bin_safety_factor
Size grid extension factor when we should regenerate grid.
Definition: aero_sorted.F90:73
pmc_bin_grid::bin_grid_size
elemental integer function bin_grid_size(bin_grid)
Return the number of bins in the grid, or -1 if the bin grid is not allocated.
Definition: bin_grid.F90:51
pmc_util::assert
subroutine assert(code, condition_ok)
Errors unless condition_ok is true.
Definition: util.F90:103
pmc_aero_sorted::pmc_mpi_pack_aero_sorted
subroutine pmc_mpi_pack_aero_sorted(buffer, position, val)
Packs the given value into the buffer, advancing position.
Definition: aero_sorted.F90:584
pmc_integer_rmap2::integer_rmap2_append
subroutine integer_rmap2_append(integer_rmap2, i_range_1, i_range_2)
Set the map value of the next free domain value to (i_range_1, i_range_2.
Definition: integer_rmap2.F90:108
pmc_bin_grid::pmc_mpi_allequal_bin_grid
logical function pmc_mpi_allequal_bin_grid(val)
Check whether all processors have the same value.
Definition: bin_grid.F90:350
pmc_integer_varray::integer_varray_n_entry
elemental integer function integer_varray_n_entry(integer_varray)
Return the current number of entries.
Definition: integer_varray.F90:31
pmc_integer_rmap
The integer_rmap_t structure and assocated subroutines.
Definition: integer_rmap.F90:9
pmc_aero_particle_array::aero_particle_array_add_particle
subroutine aero_particle_array_add_particle(aero_particle_array, aero_particle)
Adds the given particle to the end of the array.
Definition: aero_particle_array.F90:160
pmc_aero_sorted::aero_sorted_set_bin_grid
subroutine aero_sorted_set_bin_grid(aero_sorted, bin_grid, n_group, n_class)
Set the bin grid to be used for sorting.
Definition: aero_sorted.F90:117
pmc_util::warn_msg
subroutine warn_msg(code, warning_msg, already_warned)
Prints a warning message.
Definition: util.F90:37
pmc_bin_grid::pmc_mpi_pack_size_bin_grid
integer function pmc_mpi_pack_size_bin_grid(val)
Determines the number of bytes required to pack the given value.
Definition: bin_grid.F90:282
pmc_util::integer_to_string
character(len=pmc_util_convert_string_len) function integer_to_string(val)
Convert an integer to a string format.
Definition: util.F90:766
pmc_bin_grid::pmc_mpi_pack_bin_grid
subroutine pmc_mpi_pack_bin_grid(buffer, position, val)
Packs the given value into the buffer, advancing position.
Definition: bin_grid.F90:298
pmc_aero_sorted::aero_sorted_sort_particles
subroutine aero_sorted_sort_particles(aero_sorted, aero_particle_array, aero_data)
Sort the particles.
Definition: aero_sorted.F90:187
pmc_integer_varray
The integer_varray_t structure and assocated subroutines.
Definition: integer_varray.F90:9
pmc_integer_rmap2::integer_rmap2_t
A map , together with its multi-valued inverse.
Definition: integer_rmap2.F90:53
pmc_aero_sorted::aero_sorted_n_group
integer function aero_sorted_n_group(aero_sorted)
Returns the number of weight groups.
Definition: aero_sorted.F90:93
pmc_integer_rmap2::integer_rmap2_check
subroutine integer_rmap2_check(integer_rmap2, name, n_domain, n_range_1, n_range_2, continue_on_error)
Check that the data is consistent.
Definition: integer_rmap2.F90:250
pmc_integer_rmap2::integer_rmap2_change
subroutine integer_rmap2_change(integer_rmap2, i_domain, i_range_1, i_range_2)
Change the map value of i_domain to (i_range_1, i_range_2).
Definition: integer_rmap2.F90:137
pmc_integer_rmap2::pmc_mpi_unpack_integer_rmap2
subroutine pmc_mpi_unpack_integer_rmap2(buffer, position, val)
Unpacks the given value from the buffer, advancing position.
Definition: integer_rmap2.F90:447
pmc_integer_rmap2::pmc_mpi_pack_size_integer_rmap2
integer function pmc_mpi_pack_size_integer_rmap2(val)
Determines the number of bytes required to pack the given value.
Definition: integer_rmap2.F90:376
pmc_aero_sorted::pmc_mpi_unpack_aero_sorted
subroutine pmc_mpi_unpack_aero_sorted(buffer, position, val)
Unpacks the given value from the buffer, advancing position.
Definition: aero_sorted.F90:609
pmc_aero_sorted
The aero_sorted_t structure and assocated subroutines.
Definition: aero_sorted.F90:9
pmc_aero_data::aero_data_t
Aerosol material properties and associated data.
Definition: aero_data.F90:49
pmc_aero_sorted::pmc_mpi_pack_size_aero_sorted
integer function pmc_mpi_pack_size_aero_sorted(val)
Determines the number of bytes required to pack the given value.
Definition: aero_sorted.F90:566
pmc_mpi::pmc_mpi_allreduce_max_real
subroutine pmc_mpi_allreduce_max_real(val, val_max)
Computes the maximum of val across all processes, storing the result in val_max on all processes.
Definition: mpi.F90:1399
pmc_aero_sorted::aero_sorted_t
Sorting of particles into bins.
Definition: aero_sorted.F90:47
pmc_aero_sorted::aero_sorted_add_particle
subroutine aero_sorted_add_particle(aero_sorted, aero_particle_array, aero_particle, aero_data, allow_resort)
Add a new particle to both an aero_sorted and the corresponding aero_particle_array.
Definition: aero_sorted.F90:399
pmc_aero_sorted::aero_sorted_bin_over_factor
real(kind=dp), parameter aero_sorted_bin_over_factor
Factor to extend size grid beyond largest/smallest particles.
Definition: aero_sorted.F90:71
pmc_aero_sorted::aero_sorted_remake_if_needed
subroutine aero_sorted_remake_if_needed(aero_sorted, aero_particle_array, aero_data, valid_sort, n_group, n_class, bin_grid, all_procs_same)
Remake a sorting if particles are getting too close to the edges.
Definition: aero_sorted.F90:216
pmc_aero_particle::aero_particle_radius
elemental real(kind=dp) function aero_particle_radius(aero_particle, aero_data)
Total radius of the particle (m).
Definition: aero_particle.F90:339
pmc_bin_grid::pmc_mpi_unpack_bin_grid
subroutine pmc_mpi_unpack_bin_grid(buffer, position, val)
Unpacks the given value from the buffer, advancing position.
Definition: bin_grid.F90:324
pmc_aero_sorted::aero_sorted_discard_outside_grid
subroutine aero_sorted_discard_outside_grid(aero_sorted, aero_particle_array, aero_data)
Discard particles that don't fit the bin grid.
Definition: aero_sorted.F90:155
pmc_bin_grid
The bin_grid_t structure and associated subroutines.
Definition: bin_grid.F90:9
pmc_aero_data
The aero_data_t structure and associated subroutines.
Definition: aero_data.F90:9
pmc_aero_sorted::aero_sorted_n_class
integer function aero_sorted_n_class(aero_sorted)
Returns the number of weight classes.
Definition: aero_sorted.F90:105
pmc_bin_grid::bin_grid_t
1D grid, either logarithmic or linear.
Definition: bin_grid.F90:33
pmc_integer_rmap2::integer_rmap2_zero
elemental subroutine integer_rmap2_zero(integer_rmap2)
Resets an integer_rmap2 to have no mappings.
Definition: integer_rmap2.F90:90
pmc_aero_particle_array
The aero_particle_array_t structure and assoicated subroutines.
Definition: aero_particle_array.F90:9
pmc_integer_rmap2::integer_rmap2_set_ranges
elemental subroutine integer_rmap2_set_ranges(integer_rmap2, n_range_1, n_range_2)
Sets the maximum ranges of the forward map.
Definition: integer_rmap2.F90:71
pmc_aero_sorted::aero_sorted_remove_particle
subroutine aero_sorted_remove_particle(aero_sorted, aero_particle_array, i_part)
Remove a particle from both an aero_sorted and the corresponding aero_particle_array.
Definition: aero_sorted.F90:457
pmc_integer_rmap2::integer_rmap2_remove
subroutine integer_rmap2_remove(integer_rmap2, i_domain)
Replace the map at the given i_domain with the map value of the last entry, and delete the last entry...
Definition: integer_rmap2.F90:191
pmc_bin_grid::bin_grid_type_log
integer, parameter bin_grid_type_log
Logarithmically spaced bin grid.
Definition: bin_grid.F90:23
pmc_bin_grid::bin_grid_make
subroutine bin_grid_make(bin_grid, type, n_bin, min, max)
Generates the bin grid given the range and number of bins.
Definition: bin_grid.F90:84
pmc_aero_sorted::aero_sorted_move_particle
subroutine aero_sorted_move_particle(aero_sorted, i_part, new_bin, new_group, new_class)
Move a particle to a different bin and group.
Definition: aero_sorted.F90:477
pmc_bin_grid::bin_grid_find
integer function bin_grid_find(bin_grid, val)
Find the bin number that contains a given value.
Definition: bin_grid.F90:144
pmc_aero_particle_array::aero_particle_array_remove_particle
subroutine aero_particle_array_remove_particle(aero_particle_array, index)
Removes the particle at the given index.
Definition: aero_particle_array.F90:180