PartMC  2.6.1
aero_weight_array.F90
Go to the documentation of this file.
1 ! Copyright (C) 2012 Jeff Curtis
2 ! Copyright (C) 2012-2015 Matthew West
3 ! Licensed under the GNU General Public License version 2 or (at your
4 ! option) any later version. See the file COPYING for details.
5 
6 !> \file
7 !> The pmc_aero_weight_array module.
8 
9 !> The aero_weight_array_t structure and associated subroutines.
11 
12  use pmc_util
13  use pmc_constants
14  use pmc_rand
15  use pmc_spec_file
17  use pmc_netcdf
18  use pmc_mpi
19  use pmc_aero_weight
20  use pmc_aero_data
21 #ifdef PMC_USE_MPI
22  use mpi
23 #endif
24 
25  !> An array of aerosol size distribution weighting functions.
26  !!
27  !! Each particle has a weight group and a weight class, which
28  !! defines the weighting function associated with it. To determine
29  !! the actual weight for a particle, the harmonic mean of the weight
30  !! from each group is computed (for the given class). All particles
31  !! of a given size within a weight class will thus have the same
32  !! weight, irrespective of which group they are in. The group is
33  !! only important when doubling or halving occurs, which takes place
34  !! for a specific group and class.
36  !> Aero weight array, <tt>aero_weight_array_n_group(aero_weight_array) x
37  !> aero_weight_array_n_class(aero_weight_array)</tt>.
38  type(aero_weight_t), allocatable :: weight(:, :)
39  end type aero_weight_array_t
40 
41 contains
42 
43 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
44 
45  !> Sets the number of weight groups and classes.
46  subroutine aero_weight_array_set_sizes(aero_weight_array, n_group, &
47  n_class)
48 
49  !> Aerosol weight array.
50  type(aero_weight_array_t), intent(inout) :: aero_weight_array
51  !> Number of weight groups.
52  integer,intent(in) :: n_group
53  !> Number of weight classes.
54  integer,intent(in) :: n_class
55 
56  if (allocated(aero_weight_array%weight)) then
57  deallocate(aero_weight_array%weight)
58  end if
59  allocate(aero_weight_array%weight(n_group, n_class))
60 
61  end subroutine aero_weight_array_set_sizes
62 
63 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
64 
65  !> Allocates an \c aero_weight_array as flat weightings.
66  subroutine aero_weight_array_set_flat(aero_weight_array, n_class)
67 
68  !> Aerosol weight array.
69  type(aero_weight_array_t), intent(out) :: aero_weight_array
70  !> Number of weight classes.
71  integer,intent(in) :: n_class
72 
73  call aero_weight_array_set_sizes(aero_weight_array, 1, n_class)
74  aero_weight_array%weight%type = aero_weight_type_none
75  aero_weight_array%weight%magnitude = 1d0
76  aero_weight_array%weight%exponent = 0d0
77 
78  end subroutine aero_weight_array_set_flat
79 
80 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
81 
82  !> Allocates an \c aero_weight_array as power weightings.
83  subroutine aero_weight_array_set_power(aero_weight_array, n_class, &
84  exponent)
85 
86  !> Aerosol weight array.
87  type(aero_weight_array_t), intent(out) :: aero_weight_array
88  !> Number of weight classes.
89  integer,intent(in) :: n_class
90  !> Exponent for power-law.
91  real(kind=dp), intent(in) :: exponent
92 
93  call aero_weight_array_set_sizes(aero_weight_array, 1, n_class)
94  aero_weight_array%weight%type = aero_weight_type_power
95  aero_weight_array%weight%magnitude = 1d0
96  aero_weight_array%weight%exponent = exponent
97 
98  end subroutine aero_weight_array_set_power
99 
100 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
101 
102  !> Allocates an \c aero_weight_array as joint flat/power-3 weightings..
103  subroutine aero_weight_array_set_nummass(aero_weight_array, n_class)
104 
105  !> Aerosol weight array.
106  type(aero_weight_array_t), intent(out) :: aero_weight_array
107  !> Number of weight classes.
108  integer,intent(in) :: n_class
109 
110  call aero_weight_array_set_sizes(aero_weight_array, 2, n_class)
111  aero_weight_array%weight(1, :)%type = aero_weight_type_none
112  aero_weight_array%weight(1, :)%magnitude = 1d0
113  aero_weight_array%weight(1, :)%exponent = 0d0
114  aero_weight_array%weight(2, :)%type = aero_weight_type_power
115  aero_weight_array%weight(2, :)%magnitude = 1d0
116  aero_weight_array%weight(2, :)%exponent = -3d0
117 
118  end subroutine aero_weight_array_set_nummass
119 
120 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
121 
122  !> Normalizes the \c aero_weight_array to a non-zero value.
123  elemental subroutine aero_weight_array_normalize(aero_weight_array)
124 
125  !> Aerosol weight array.
126  type(aero_weight_array_t), intent(inout) :: aero_weight_array
127 
128  call aero_weight_normalize(aero_weight_array%weight)
129 
130  end subroutine aero_weight_array_normalize
131 
132 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
133 
134  !> Return the number of weight groups.
135  integer function aero_weight_array_n_group(aero_weight_array)
136 
137  !> Aerosol weight array.
138  type(aero_weight_array_t), intent(in) :: aero_weight_array
139 
140  aero_weight_array_n_group = size(aero_weight_array%weight, 1)
141 
142  end function aero_weight_array_n_group
143 
144 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
145 
146  !> Return the number of weight classes.
147  integer function aero_weight_array_n_class(aero_weight_array)
148 
149  !> Aerosol weight array.
150  type(aero_weight_array_t), intent(in) :: aero_weight_array
151 
152  aero_weight_array_n_class = size(aero_weight_array%weight, 2)
153 
154  end function aero_weight_array_n_class
155 
156 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
157 
158  !> Scale the weights by the given factor, so
159  !> <tt>new_weight = old_weight * factor</tt>.
160  subroutine aero_weight_array_scale(aero_weight_array, factor)
161 
162  !> Aerosol weight array to scale.
163  type(aero_weight_array_t), intent(inout) :: aero_weight_array
164  !> Factor to scale by.
165  real(kind=dp), intent(in) :: factor
166 
167  call aero_weight_scale(aero_weight_array%weight, factor)
168 
169  end subroutine aero_weight_array_scale
170 
171 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
172 
173  !> Combine \c aero_weight_array_delta into \c aero_weight_array
174  !> with a harmonic mean.
175  subroutine aero_weight_array_combine(aero_weight_array, &
176  aero_weight_array_delta)
177 
178  !> Aerosol weight array to combine into.
179  type(aero_weight_array_t), intent(inout) :: aero_weight_array
180  !> Aerosol weight array to combine from.
181  type(aero_weight_array_t), intent(in) :: aero_weight_array_delta
182 
183  call aero_weight_combine(aero_weight_array%weight, &
184  aero_weight_array_delta%weight)
185 
186  end subroutine aero_weight_array_combine
187 
188 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
189 
190  !> Adjust source and destination weights to reflect moving \c
191  !> sample_prop proportion of particles from
192  !> \c aero_weight_array_from to \c aero_weight_array_to.
193  subroutine aero_weight_array_shift(aero_weight_array_from, &
194  aero_weight_array_to, sample_prop, overwrite_to)
195 
196  !> Aerosol weight array to shift from.
197  type(aero_weight_array_t), intent(inout) :: aero_weight_array_from
198  !> Aerosol weight array to shift to.
199  type(aero_weight_array_t), intent(inout) :: aero_weight_array_to
200  !> Proportion of particles being transfered.
201  real(kind=dp), intent(in) :: sample_prop
202  !> Whether to overwrite the destination weight (default: no).
203  logical, intent(in), optional :: overwrite_to
204 
205  call aero_weight_shift(aero_weight_array_from%weight, &
206  aero_weight_array_to%weight, sample_prop, overwrite_to)
207 
208  end subroutine aero_weight_array_shift
209 
210 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
211 
212  !> Compute the number concentration for a particle (m^{-3}).
213  real(kind=dp) function aero_weight_array_single_num_conc(aero_weight_array, &
214  aero_particle, aero_data)
215 
216  !> Aerosol weight array.
217  type(aero_weight_array_t), intent(in) :: aero_weight_array
218  !> Aerosol particle to compute number concentration for.
219  type(aero_particle_t), intent(in) :: aero_particle
220  !> Aerosol data.
221  type(aero_data_t), intent(in) :: aero_data
222 
224  aero_weight_array%weight(aero_particle%weight_group, &
225  aero_particle%weight_class), aero_particle, aero_data)
226 
228 
229 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
230 
231  !> Compute the total number concentration at a given radius (m^3).
233  aero_weight_array, i_class, radius)
234 
235  !> Aerosol weight array.
236  type(aero_weight_array_t), intent(in) :: aero_weight_array
237  !> Weight class number.
238  integer, intent(in) :: i_class
239  !> Radius to compute number concentration at (m).
240  real(kind=dp), intent(in) :: radius
241 
242  integer :: i_group
243  real(kind=dp) :: num_conc(size(aero_weight_array%weight, 1))
244 
245  do i_group = 1,size(aero_weight_array%weight, 1)
246  num_conc(i_group) = aero_weight_num_conc_at_radius( &
247  aero_weight_array%weight(i_group, i_class), radius)
248  end do
249  ! harmonic mean (same as summing the computational volumes)
250  aero_weight_array_num_conc_at_radius = 1d0 / sum(1d0 / num_conc)
251 
253 
254 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
255 
256  !> Compute the number concentration for a particle (m^{-3}).
257  real(kind=dp) function aero_weight_array_num_conc(aero_weight_array, &
258  aero_particle, aero_data)
259 
260  !> Aerosol weight array.
261  type(aero_weight_array_t), intent(in) :: aero_weight_array
262  !> Aerosol particle to compute number concentration for.
263  type(aero_particle_t), intent(in) :: aero_particle
264  !> Aerosol data.
265  type(aero_data_t), intent(in) :: aero_data
266 
268  aero_weight_array, aero_particle%weight_class, &
269  aero_particle_radius(aero_particle, aero_data))
270 
271  end function aero_weight_array_num_conc
272 
273 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
274 
275  !> Check whether a given aero_weight array is flat in total.
276  logical function aero_weight_array_check_flat(aero_weight_array)
277 
278  !> Aerosol weight array.
279  type(aero_weight_array_t), intent(in) :: aero_weight_array
280 
281  integer :: i_group, i_class
282 
283  ! check that all weights have correctly set exponents
284  do i_group = 1,size(aero_weight_array%weight, 1)
285  do i_class = 1,size(aero_weight_array%weight, 2)
287  aero_weight_array%weight(i_group, i_class))
288  end do
289  end do
290 
291  if (all(abs(sum(aero_weight_array%weight%exponent, 1)) &
292  < 1d-20 * sum(abs(aero_weight_array%weight%exponent), 1))) then
294  else
296  end if
297 
298  end function aero_weight_array_check_flat
299 
300 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
301 
302  !> Determine whether all weight functions in an array are monotone
303  !> increasing, monotone decreasing, or neither.
304  subroutine aero_weight_array_check_monotonicity(aero_weight_array, &
305  monotone_increasing, monotone_decreasing)
306 
307  !> Aerosol weight array.
308  type(aero_weight_array_t), intent(in) :: aero_weight_array
309  !> Whether all weights are monotone increasing.
310  logical, intent(out) :: monotone_increasing
311  !> Whether all weights are monotone decreasing.
312  logical, intent(out) :: monotone_decreasing
313 
314  integer :: i_group, i_class
315  logical :: mono_increasing_array(size(aero_weight_array%weight, 1), &
316  size(aero_weight_array%weight, 2))
317  logical :: mono_decreasing_array(size(aero_weight_array%weight, 1), &
318  size(aero_weight_array%weight, 2))
319 
320  do i_group = 1,size(aero_weight_array%weight, 1)
321  do i_class = 1,size(aero_weight_array%weight, 2)
323  aero_weight_array%weight(i_group, i_class), &
324  mono_increasing_array(i_group, i_class), &
325  mono_decreasing_array(i_group, i_class))
326  end do
327  end do
328 
329  monotone_increasing = all(mono_increasing_array)
330  monotone_decreasing = all(mono_decreasing_array)
331 
333 
334 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
335 
336  !> Compute the maximum and minimum number concentrations between the
337  !> given radii.
338  subroutine aero_weight_array_minmax_num_conc(aero_weight_array, i_class, &
339  radius_1, radius_2, num_conc_min, num_conc_max)
340 
341  !> Aerosol weight array.
342  type(aero_weight_array_t), intent(in) :: aero_weight_array
343  !> Weight class.
344  integer, intent(in) :: i_class
345  !> First radius.
346  real(kind=dp), intent(in) :: radius_1
347  !> Second radius.
348  real(kind=dp), intent(in) :: radius_2
349  !> Minimum number concentration.
350  real(kind=dp), intent(out) :: num_conc_min
351  !> Maximum number concentration.
352  real(kind=dp), intent(out) :: num_conc_max
353 
354  real(kind=dp) :: num_conc_1, num_conc_2
355  logical :: monotone_increasing, monotone_decreasing
356 
357  call aero_weight_array_check_monotonicity(aero_weight_array, &
358  monotone_increasing, monotone_decreasing)
359  call assert(857727714, monotone_increasing .or. monotone_decreasing)
360 
361  num_conc_1 = aero_weight_array_num_conc_at_radius(aero_weight_array, &
362  i_class, radius_1)
363  num_conc_2 = aero_weight_array_num_conc_at_radius(aero_weight_array, &
364  i_class, radius_2)
365  num_conc_min = min(num_conc_1, num_conc_2)
366  num_conc_max = max(num_conc_1, num_conc_2)
367 
368  end subroutine aero_weight_array_minmax_num_conc
369 
370 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
371 
372  !> Choose a random group at the given radius, with probability
373  !> inversely proportional to group weight at that radius.
374  integer function aero_weight_array_rand_group(aero_weight_array, i_class, &
375  radius)
376 
377  !> Aerosol weight array.
378  type(aero_weight_array_t), intent(in) :: aero_weight_array
379  !> Weight class to select from.
380  integer, intent(in) :: i_class
381  !> Radius to sample group at (m).
382  real(kind=dp), intent(in) :: radius
383 
384  real(kind=dp) :: comp_vols(size(aero_weight_array%weight, 1))
385  integer :: i_group
386 
387  do i_group = 1,size(aero_weight_array%weight, 1)
388  comp_vols(i_group) = 1d0 / aero_weight_num_conc_at_radius( &
389  aero_weight_array%weight(i_group, i_class), radius)
390  end do
392 
393  end function aero_weight_array_rand_group
394 
395 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
396 
397  !> Read an aero_weight_array from a spec file.
398  subroutine spec_file_read_aero_weight_array(file, aero_weight_array)
399 
400  !> Spec file.
401  type(spec_file_t), intent(inout) :: file
402  !> Aerosol weight array.
403  type(aero_weight_array_t), intent(inout) :: aero_weight_array
404 
405  integer :: i_group, i_class
406 
407  do i_group = 1,size(aero_weight_array%weight, 1)
408  do i_class = 1,size(aero_weight_array%weight, 2)
409  call spec_file_read_aero_weight(file, &
410  aero_weight_array%weight(i_group, i_class))
411  end do
412  end do
413 
414  end subroutine spec_file_read_aero_weight_array
415 
416 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
417 
418  !> Determines the number of bytes required to pack the given value.
420 
421  !> Value to pack.
422  type(aero_weight_array_t), intent(in) :: val
423 
424  integer :: i_group, i_class, total_size
425  logical :: is_allocated
426 
427  total_size = 0
428  is_allocated = allocated(val%weight)
429  total_size = total_size + pmc_mpi_pack_size_logical(is_allocated)
430  if (is_allocated) then
431  total_size = total_size &
432  + pmc_mpi_pack_size_integer(size(val%weight, 1)) &
433  + pmc_mpi_pack_size_integer(size(val%weight, 2))
434  do i_group = 1,size(val%weight, 1)
435  do i_class = 1,size(val%weight, 2)
436  total_size = total_size &
437  + pmc_mpi_pack_size_aero_weight(val%weight(i_group, i_class))
438  end do
439  end do
440  end if
442 
444 
445 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
446 
447  !> Packs the given value into the buffer, advancing position.
448  subroutine pmc_mpi_pack_aero_weight_array(buffer, position, val)
449 
450  !> Memory buffer.
451  character, intent(inout) :: buffer(:)
452  !> Current buffer position.
453  integer, intent(inout) :: position
454  !> Value to pack.
455  type(aero_weight_array_t), intent(in) :: val
456 
457 #ifdef PMC_USE_MPI
458  integer :: prev_position, i_group, i_class
459  logical :: is_allocated
460 
461  prev_position = position
462  is_allocated = allocated(val%weight)
463  call pmc_mpi_pack_logical(buffer, position, is_allocated)
464  if (is_allocated) then
465  call pmc_mpi_pack_integer(buffer, position, size(val%weight, 1))
466  call pmc_mpi_pack_integer(buffer, position, size(val%weight, 2))
467  do i_group = 1,size(val%weight, 1)
468  do i_class = 1,size(val%weight, 2)
469  call pmc_mpi_pack_aero_weight(buffer, position, &
470  val%weight(i_group, i_class))
471  end do
472  end do
473  end if
474  call assert(84068036, &
475  position - prev_position <= pmc_mpi_pack_size_aero_weight_array(val))
476 #endif
477 
478  end subroutine pmc_mpi_pack_aero_weight_array
479 
480 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
481 
482  !> Unpacks the given value from the buffer, advancing position.
483  subroutine pmc_mpi_unpack_aero_weight_array(buffer, position, val)
484 
485  !> Memory buffer.
486  character, intent(inout) :: buffer(:)
487  !> Current buffer position.
488  integer, intent(inout) :: position
489  !> Value to pack.
490  type(aero_weight_array_t), intent(inout) :: val
491 
492 #ifdef PMC_USE_MPI
493  integer :: prev_position, n_group, n_class, i_group, i_class
494  logical :: is_allocated
495 
496  prev_position = position
497  call pmc_mpi_unpack_logical(buffer, position, is_allocated)
498  if (is_allocated) then
499  call pmc_mpi_unpack_integer(buffer, position, n_group)
500  call pmc_mpi_unpack_integer(buffer, position, n_class)
501  call aero_weight_array_set_sizes(val, n_group, n_class)
502  do i_group = 1,size(val%weight, 1)
503  do i_class = 1,size(val%weight, 2)
504  call pmc_mpi_unpack_aero_weight(buffer, position, &
505  val%weight(i_group, i_class))
506  end do
507  end do
508  else
509  if (allocated(val%weight)) then
510  deallocate(val%weight)
511  end if
512  end if
513  call assert(321022868, &
514  position - prev_position <= pmc_mpi_pack_size_aero_weight_array(val))
515 #endif
516 
517  end subroutine pmc_mpi_unpack_aero_weight_array
518 
519 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
520 
521  !> Write the \c aero_weight_group dimension to the given NetCDF file
522  !> if it is not already present and in any case return the
523  !> associated dimid.
524  subroutine aero_weight_netcdf_dim_aero_weight_group(aero_weight_array, &
525  ncid, dimid_aero_weight_group)
526 
527  !> Aero_weight structure array.
528  type(aero_weight_array_t), intent(in) :: aero_weight_array
529  !> NetCDF file ID, in data mode.
530  integer, intent(in) :: ncid
531  !> Dimid of the species dimension.
532  integer, intent(out) :: dimid_aero_weight_group
533 
534  integer :: status, i_group, n_group
535  integer :: varid_aero_weight_group
536  integer :: aero_weight_group_centers(size(aero_weight_array%weight, 1))
537 
538  ! try to get the dimension ID
539  status = nf90_inq_dimid(ncid, "aero_weight_group", dimid_aero_weight_group)
540  if (status == nf90_noerr) return
541  if (status /= nf90_ebaddim) call pmc_nc_check(status)
542 
543  ! dimension not defined, so define it
544  call pmc_nc_check(nf90_redef(ncid))
545 
546  n_group = size(aero_weight_array%weight, 1)
547 
548  call pmc_nc_check(nf90_def_dim(ncid, "aero_weight_group", n_group, &
549  dimid_aero_weight_group))
550  call pmc_nc_check(nf90_def_var(ncid, "aero_weight_group", nf90_int, &
551  dimid_aero_weight_group, varid_aero_weight_group))
552  call pmc_nc_check(nf90_put_att(ncid, varid_aero_weight_group, &
553  "description", "dummy dimension variable (no useful value)"))
554 
555  call pmc_nc_check(nf90_enddef(ncid))
556 
557  do i_group = 1,n_group
558  aero_weight_group_centers(i_group) = i_group
559  end do
560  call pmc_nc_check(nf90_put_var(ncid, varid_aero_weight_group, &
561  aero_weight_group_centers))
562 
564 
565 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
566 
567  !> Write the \c aero_weight_class dimension to the given NetCDF file
568  !> if it is not already present and in any case return the
569  !> associated dimid.
570  subroutine aero_weight_netcdf_dim_aero_weight_class(aero_weight_array, &
571  ncid, dimid_aero_weight_class)
572 
573  !> Aero_weight structure array.
574  type(aero_weight_array_t), intent(in) :: aero_weight_array
575  !> NetCDF file ID, in data mode.
576  integer, intent(in) :: ncid
577  !> Dimid of the species dimension.
578  integer, intent(out) :: dimid_aero_weight_class
579 
580  integer :: status, i_class, n_class
581  integer :: varid_aero_weight_class
582  integer :: aero_weight_class_centers(size(aero_weight_array%weight, 2))
583 
584  ! try to get the dimension ID
585  status = nf90_inq_dimid(ncid, "aero_weight_class", dimid_aero_weight_class)
586  if (status == nf90_noerr) return
587  if (status /= nf90_ebaddim) call pmc_nc_check(status)
588 
589  ! dimension not defined, so define it
590  call pmc_nc_check(nf90_redef(ncid))
591 
592  n_class = size(aero_weight_array%weight, 2)
593 
594  call pmc_nc_check(nf90_def_dim(ncid, "aero_weight_class", n_class, &
595  dimid_aero_weight_class))
596  call pmc_nc_check(nf90_def_var(ncid, "aero_weight_class", nf90_int, &
597  dimid_aero_weight_class, varid_aero_weight_class))
598  call pmc_nc_check(nf90_put_att(ncid, varid_aero_weight_class, &
599  "description", "dummy dimension variable (no useful value)"))
600 
601  call pmc_nc_check(nf90_enddef(ncid))
602 
603  do i_class = 1,n_class
604  aero_weight_class_centers(i_class) = i_class
605  end do
606  call pmc_nc_check(nf90_put_var(ncid, varid_aero_weight_class, &
607  aero_weight_class_centers))
608 
610 
611 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
612 
613  !> Write full aero_weight_array.
614  subroutine aero_weight_array_output_netcdf(aero_weight_array, ncid)
615 
616  !> Aero weight array to write.
617  type(aero_weight_array_t), intent(in) :: aero_weight_array
618  !> NetCDF file ID, in data mode.
619  integer, intent(in) :: ncid
620 
621  integer :: dimid_aero_weight_group, dimid_aero_weight_class
622 
623  !> \page output_format_aero_weight_array Output File Format: Aerosol Weighting Functions
624  !!
625  !! The aerosol weighting function NetCDF dimensions are:
626  !! - \b aero_weight_group: number of aerosol weighting groups
627  !! - \b aero_weight_class: number of aerosol weighting classes
628  !!
629  !! The aerosol weighting function NetCDF variables are:
630  !! - \b weight_type (no unit, dim \c aero_weight): the type of
631  !! each weighting function, with 0 = invalid weight, 1 = no
632  !! weight (\f$w(D) = 1\f$), 2 = power weight (\f$w(D) =
633  !! (D/D_0)^\alpha\f$), 3 = MFA weight (\f$w(D) =
634  !! (D/D_0)^{-3}\f$)
635  !! - \b weight_magnitude (unit m^{-3}, dim \c aero_weight): the
636  !! number concentration magnitude associated with each
637  !! weighting function
638  !! - \b weight_exponent (no unit, dim \c aero_weight): for each
639  !! weighting function, specifies the exponent \f$\alpha\f$ for
640  !! the power \c weight_type, the value -3 for the MFA \c
641  !! weight_type, and zero for any other \c weight_type
642 
643  call aero_weight_netcdf_dim_aero_weight_group(aero_weight_array, ncid, &
644  dimid_aero_weight_group)
645  call aero_weight_netcdf_dim_aero_weight_class(aero_weight_array, ncid, &
646  dimid_aero_weight_class)
647 
648  call pmc_nc_write_integer_2d(ncid, aero_weight_array%weight%type, &
649  "weight_type", &
650  (/ dimid_aero_weight_group, dimid_aero_weight_class /), &
651  description="type of each aerosol weighting function: 0 = invalid, " &
652  // "1 = none (w(D) = 1), 2 = power (w(D) = (D/D_0)^alpha), " &
653  // "3 = MFA (mass flow) (w(D) = (D/D_0)^(-3))")
654  call pmc_nc_write_real_2d(ncid, aero_weight_array%weight%magnitude, &
655  "weight_magnitude", &
656  (/ dimid_aero_weight_group, dimid_aero_weight_class /), &
657  unit="m^{-3}", &
658  description="magnitude for each weighting function")
659  call pmc_nc_write_real_2d(ncid, aero_weight_array%weight%exponent, &
660  "weight_exponent", &
661  (/ dimid_aero_weight_group, dimid_aero_weight_class /), unit="1", &
662  description="exponent alpha for the power weight_type, " &
663  // "set to -3 for MFA, and zero otherwise")
664 
665  end subroutine aero_weight_array_output_netcdf
666 
667 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
668 
669  !> Read full aero_weight_array.
670  subroutine aero_weight_array_input_netcdf(aero_weight_array, ncid)
671 
672  !> Aero weight array to read.
673  type(aero_weight_array_t), intent(inout) :: aero_weight_array
674  !> NetCDF file ID, in data mode.
675  integer, intent(in) :: ncid
676 
677  integer :: dimid_aero_weight_group, dimid_aero_weight_class, n_group
678  integer :: n_class
679  character(len=1000) :: name
680  integer, allocatable :: type(:, :)
681  real(kind=dp), allocatable :: magnitude(:, :), exponent(:, :)
682 
683  call pmc_nc_check(nf90_inq_dimid(ncid, "aero_weight_group", &
684  dimid_aero_weight_group))
685  call pmc_nc_check(nf90_inq_dimid(ncid, "aero_weight_class", &
686  dimid_aero_weight_class))
687  call pmc_nc_check(nf90_inquire_dimension(ncid, &
688  dimid_aero_weight_group, name, n_group))
689  call pmc_nc_check(nf90_inquire_dimension(ncid, &
690  dimid_aero_weight_class, name, n_class))
691  call assert(719221386, n_group < 1000)
692  call assert(520105999, n_class < 1000)
693 
694  call pmc_nc_read_integer_2d(ncid, type, "weight_type")
695  call pmc_nc_read_real_2d(ncid, magnitude, "weight_magnitude")
696  call pmc_nc_read_real_2d(ncid, exponent, "weight_exponent")
697 
698  call assert(309191498, size(magnitude) == size(type))
699  call assert(588649520, size(magnitude) == size(exponent))
700 
701  call aero_weight_array_set_sizes(aero_weight_array, n_group, n_class)
702 
703  aero_weight_array%weight%type = type
704  aero_weight_array%weight%magnitude = magnitude
705  aero_weight_array%weight%exponent = exponent
706 
707  end subroutine aero_weight_array_input_netcdf
708 
709 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
710 
711 end module pmc_aero_weight_array
pmc_aero_particle::aero_particle_t
Single aerosol particle data structure.
Definition: aero_particle.F90:26
pmc_aero_weight_array::aero_weight_array_n_class
integer function aero_weight_array_n_class(aero_weight_array)
Return the number of weight classes.
Definition: aero_weight_array.F90:148
pmc_aero_weight::aero_weight_type_none
integer, parameter aero_weight_type_none
Type code for no (or flat) weighting.
Definition: aero_weight.F90:26
pmc_mpi
Wrapper functions for MPI.
Definition: mpi.F90:13
pmc_aero_weight_array::aero_weight_array_single_num_conc
real(kind=dp) function aero_weight_array_single_num_conc(aero_weight_array, aero_particle, aero_data)
Compute the number concentration for a particle (m^{-3}).
Definition: aero_weight_array.F90:215
pmc_aero_weight_array::aero_weight_netcdf_dim_aero_weight_class
subroutine aero_weight_netcdf_dim_aero_weight_class(aero_weight_array, ncid, dimid_aero_weight_class)
Write the aero_weight_class dimension to the given NetCDF file if it is not already present and in an...
Definition: aero_weight_array.F90:572
pmc_aero_weight_array::pmc_mpi_pack_size_aero_weight_array
integer function pmc_mpi_pack_size_aero_weight_array(val)
Determines the number of bytes required to pack the given value.
Definition: aero_weight_array.F90:420
pmc_aero_weight::aero_weight_combine
elemental subroutine aero_weight_combine(aero_weight, aero_weight_delta)
Combine aero_weight_delta into aero_weight with a harmonic mean.
Definition: aero_weight.F90:75
pmc_aero_weight
The aero_weight_t structure and associated subroutines.
Definition: aero_weight.F90:9
pmc_netcdf::pmc_nc_write_real_2d
subroutine pmc_nc_write_real_2d(ncid, var, name, dimids, dim_name_1, dim_name_2, unit, long_name, standard_name, description)
Write a simple real 2D array to a NetCDF file.
Definition: netcdf.F90:634
pmc_aero_particle
The aero_particle_t structure and associated subroutines.
Definition: aero_particle.F90:9
pmc_aero_weight::aero_weight_scale
elemental subroutine aero_weight_scale(aero_weight, factor)
Scale the weight by the given fraction, so new_weight = old_weight * factor.
Definition: aero_weight.F90:61
pmc_aero_weight_array::aero_weight_array_check_monotonicity
subroutine aero_weight_array_check_monotonicity(aero_weight_array, monotone_increasing, monotone_decreasing)
Determine whether all weight functions in an array are monotone increasing, monotone decreasing,...
Definition: aero_weight_array.F90:306
pmc_aero_weight_array::aero_weight_array_set_nummass
subroutine aero_weight_array_set_nummass(aero_weight_array, n_class)
Allocates an aero_weight_array as joint flat/power-3 weightings..
Definition: aero_weight_array.F90:104
pmc_mpi::pmc_mpi_pack_logical
subroutine pmc_mpi_pack_logical(buffer, position, val)
Packs the given value into the buffer, advancing position.
Definition: mpi.F90:638
pmc_netcdf
Wrapper functions for NetCDF. These all take a NetCDF ncid in data mode and return with it again in d...
Definition: netcdf.F90:11
pmc_constants::dp
integer, parameter dp
Kind of a double precision real number.
Definition: constants.F90:12
pmc_aero_weight_array
The aero_weight_array_t structure and associated subroutines.
Definition: aero_weight_array.F90:10
pmc_aero_weight::pmc_mpi_pack_size_aero_weight
integer function pmc_mpi_pack_size_aero_weight(val)
Determines the number of bytes required to pack the given value.
Definition: aero_weight.F90:313
pmc_spec_file
Reading formatted text input.
Definition: spec_file.F90:43
pmc_aero_weight_array::pmc_mpi_unpack_aero_weight_array
subroutine pmc_mpi_unpack_aero_weight_array(buffer, position, val)
Unpacks the given value from the buffer, advancing position.
Definition: aero_weight_array.F90:484
pmc_aero_weight_array::aero_weight_array_input_netcdf
subroutine aero_weight_array_input_netcdf(aero_weight_array, ncid)
Read full aero_weight_array.
Definition: aero_weight_array.F90:671
pmc_aero_weight_array::aero_weight_array_set_flat
subroutine aero_weight_array_set_flat(aero_weight_array, n_class)
Allocates an aero_weight_array as flat weightings.
Definition: aero_weight_array.F90:67
pmc_util::assert
subroutine assert(code, condition_ok)
Errors unless condition_ok is true.
Definition: util.F90:103
pmc_aero_weight_array::aero_weight_array_t
An array of aerosol size distribution weighting functions.
Definition: aero_weight_array.F90:35
pmc_netcdf::pmc_nc_write_integer_2d
subroutine pmc_nc_write_integer_2d(ncid, var, name, dimids, dim_name_1, dim_name_2, unit, long_name, standard_name, description)
Write a simple integer 2D array to a NetCDF file.
Definition: netcdf.F90:688
pmc_mpi::pmc_mpi_pack_size_logical
integer function pmc_mpi_pack_size_logical(val)
Determines the number of bytes required to pack the given value.
Definition: mpi.F90:407
pmc_spec_file::spec_file_t
An input file with extra data for printing messages.
Definition: spec_file.F90:59
pmc_aero_weight::aero_weight_check_valid_exponent
subroutine aero_weight_check_valid_exponent(aero_weight)
Ensures that a weight function exponent is valid.
Definition: aero_weight.F90:197
pmc_aero_weight_array::aero_weight_array_num_conc
real(kind=dp) function aero_weight_array_num_conc(aero_weight_array, aero_particle, aero_data)
Compute the number concentration for a particle (m^{-3}).
Definition: aero_weight_array.F90:259
pmc_aero_weight_array::aero_weight_array_num_conc_at_radius
real(kind=dp) function aero_weight_array_num_conc_at_radius(aero_weight_array, i_class, radius)
Compute the total number concentration at a given radius (m^3).
Definition: aero_weight_array.F90:234
pmc_aero_weight::aero_weight_type_power
integer, parameter aero_weight_type_power
Type code for power function weighting.
Definition: aero_weight.F90:28
pmc_aero_weight_array::aero_weight_array_combine
subroutine aero_weight_array_combine(aero_weight_array, aero_weight_array_delta)
Combine aero_weight_array_delta into aero_weight_array with a harmonic mean.
Definition: aero_weight_array.F90:177
pmc_aero_weight::aero_weight_num_conc_at_radius
real(kind=dp) function aero_weight_num_conc_at_radius(aero_weight, radius)
Compute the number concentration at a given radius (m^{-3}).
Definition: aero_weight.F90:128
pmc_rand::sample_cts_pdf
integer function sample_cts_pdf(pdf)
Sample the given continuous probability density function.
Definition: rand.F90:490
pmc_aero_weight_array::aero_weight_netcdf_dim_aero_weight_group
subroutine aero_weight_netcdf_dim_aero_weight_group(aero_weight_array, ncid, dimid_aero_weight_group)
Write the aero_weight_group dimension to the given NetCDF file if it is not already present and in an...
Definition: aero_weight_array.F90:526
pmc_aero_weight::aero_weight_shift
elemental subroutine aero_weight_shift(aero_weight_from, aero_weight_to, sample_prop, overwrite_to)
Adjust source and destination weights to reflect moving sample_prop proportion of particles from aero...
Definition: aero_weight.F90:93
pmc_aero_weight_array::aero_weight_array_normalize
elemental subroutine aero_weight_array_normalize(aero_weight_array)
Normalizes the aero_weight_array to a non-zero value.
Definition: aero_weight_array.F90:124
pmc_aero_weight::pmc_mpi_pack_aero_weight
subroutine pmc_mpi_pack_aero_weight(buffer, position, val)
Packs the given value into the buffer, advancing position.
Definition: aero_weight.F90:328
pmc_aero_weight_array::aero_weight_array_set_power
subroutine aero_weight_array_set_power(aero_weight_array, n_class, exponent)
Allocates an aero_weight_array as power weightings.
Definition: aero_weight_array.F90:85
pmc_aero_weight::aero_weight_t
An aerosol size distribution weighting function.
Definition: aero_weight.F90:33
pmc_rand
Random number generators.
Definition: rand.F90:9
pmc_aero_weight_array::aero_weight_array_rand_group
integer function aero_weight_array_rand_group(aero_weight_array, i_class, radius)
Choose a random group at the given radius, with probability inversely proportional to group weight at...
Definition: aero_weight_array.F90:376
pmc_aero_weight_array::aero_weight_array_set_sizes
subroutine aero_weight_array_set_sizes(aero_weight_array, n_group, n_class)
Sets the number of weight groups and classes.
Definition: aero_weight_array.F90:48
pmc_aero_weight_array::aero_weight_array_minmax_num_conc
subroutine aero_weight_array_minmax_num_conc(aero_weight_array, i_class, radius_1, radius_2, num_conc_min, num_conc_max)
Compute the maximum and minimum number concentrations between the given radii.
Definition: aero_weight_array.F90:340
pmc_aero_weight_array::spec_file_read_aero_weight_array
subroutine spec_file_read_aero_weight_array(file, aero_weight_array)
Read an aero_weight_array from a spec file.
Definition: aero_weight_array.F90:399
pmc_aero_data::aero_data_t
Aerosol material properties and associated data.
Definition: aero_data.F90:49
pmc_mpi::pmc_mpi_unpack_integer
subroutine pmc_mpi_unpack_integer(buffer, position, val)
Unpacks the given value from the buffer, advancing position.
Definition: mpi.F90:818
pmc_mpi::pmc_mpi_unpack_logical
subroutine pmc_mpi_unpack_logical(buffer, position, val)
Unpacks the given value from the buffer, advancing position.
Definition: mpi.F90:896
pmc_constants
Physical constants.
Definition: constants.F90:9
pmc_aero_weight::aero_weight_normalize
elemental subroutine aero_weight_normalize(aero_weight)
Sets the aero_weight to a non-zero normalized value.
Definition: aero_weight.F90:48
pmc_aero_weight::aero_weight_check_monotonicity
subroutine aero_weight_check_monotonicity(aero_weight, monotone_increasing, monotone_decreasing)
Determine whether a weight function is monotone increasing, monotone decreasing, or neither.
Definition: aero_weight.F90:220
pmc_netcdf::pmc_nc_check
subroutine pmc_nc_check(status)
Check the status of a NetCDF function call.
Definition: netcdf.F90:23
pmc_util
Common utility subroutines.
Definition: util.F90:9
pmc_aero_weight_array::aero_weight_array_shift
subroutine aero_weight_array_shift(aero_weight_array_from, aero_weight_array_to, sample_prop, overwrite_to)
Adjust source and destination weights to reflect moving sample_prop proportion of particles from aero...
Definition: aero_weight_array.F90:195
pmc_aero_weight_array::aero_weight_array_scale
subroutine aero_weight_array_scale(aero_weight_array, factor)
Scale the weights by the given factor, so new_weight = old_weight * factor.
Definition: aero_weight_array.F90:161
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_mpi::pmc_mpi_pack_size_integer
integer function pmc_mpi_pack_size_integer(val)
Determines the number of bytes required to pack the given value.
Definition: mpi.F90:345
pmc_mpi::pmc_mpi_pack_integer
subroutine pmc_mpi_pack_integer(buffer, position, val)
Packs the given value into the buffer, advancing position.
Definition: mpi.F90:561
pmc_aero_data
The aero_data_t structure and associated subroutines.
Definition: aero_data.F90:9
pmc_aero_weight_array::pmc_mpi_pack_aero_weight_array
subroutine pmc_mpi_pack_aero_weight_array(buffer, position, val)
Packs the given value into the buffer, advancing position.
Definition: aero_weight_array.F90:449
pmc_aero_weight_array::aero_weight_array_check_flat
logical function aero_weight_array_check_flat(aero_weight_array)
Check whether a given aero_weight array is flat in total.
Definition: aero_weight_array.F90:277
pmc_aero_weight::pmc_mpi_unpack_aero_weight
subroutine pmc_mpi_unpack_aero_weight(buffer, position, val)
Unpacks the given value from the buffer, advancing position.
Definition: aero_weight.F90:353
pmc_netcdf::pmc_nc_read_real_2d
subroutine pmc_nc_read_real_2d(ncid, var, name, must_be_present)
Read a simple real 2D array from a NetCDF file.
Definition: netcdf.F90:301
pmc_netcdf::pmc_nc_read_integer_2d
subroutine pmc_nc_read_integer_2d(ncid, var, name, must_be_present)
Read a simple integer 2D array from a NetCDF file.
Definition: netcdf.F90:345
pmc_aero_weight_array::aero_weight_array_n_group
integer function aero_weight_array_n_group(aero_weight_array)
Return the number of weight groups.
Definition: aero_weight_array.F90:136
pmc_aero_weight::aero_weight_num_conc
real(kind=dp) function aero_weight_num_conc(aero_weight, aero_particle, aero_data)
Compute the number concentration for a particle (m^{-3}).
Definition: aero_weight.F90:153