PartMC  2.6.1
aero_binned.F90
Go to the documentation of this file.
1 ! Copyright (C) 2005-2015 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 the.
4 
5 !> \file
6 !> The pmc_aero_binned module.
7 
8 !> The aero_binned_t structure and associated subroutines.
10 
11  use pmc_bin_grid
13  use pmc_spec_file
14  use pmc_util
15  use pmc_bin_grid
16  use pmc_aero_dist
17  use pmc_mpi
18  use pmc_aero_data
19 #ifdef PMC_USE_MPI
20  use mpi
21 #endif
22 
23  !> Aerosol number and volume distributions stored per bin.
24  !!
25  !! These quantities are densities both in volume (per m^3) and in
26  !! radius (per log_width). The total concentration per volume is computed as
27  !! sum(aero_binned%%num_conc * bin_grid%%log_width).
28  !!
29  !! An aero_binned_t is similar to an aero_dist_t in that they both
30  !! store binned aerosol distributions. The difference is that an
31  !! aero_dist_t has the same composition in every bin, whereas an
32  !! aero_binned_t can have aerosol composition that varies per bin.
33  !!
34  !! By convention, if aero_binned_is_allocated() return \c .false.,
35  !! then the aero_binned is treated as zero for all operations on
36  !! it. This will be the case for new \c aero_binned_t structures.
38  !> Number concentration per bin (#/m^3/log_width).
39  !! Array length is \c bin_grid_size(bin_grid).
40  real(kind=dp), allocatable :: num_conc(:)
41  !> Volume concentration per bin and per species (m^3/m^3/log_width).
42  !! Array size is <tt>bin_grid_size(bin_grid) x
43  !! aero_data_n_spec(aero_data)</tt>.
44  real(kind=dp), allocatable :: vol_conc(:,:)
45  end type aero_binned_t
46 
47 contains
48 
49 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
50 
51  !> Determine whether the \c aero_binned is correctly allocated.
52  logical function aero_binned_is_allocated(aero_binned)
53 
54  !> Aerosol binned to check.
55  type(aero_binned_t), intent(in) :: aero_binned
56 
57  logical :: valid
58 
59  valid = .true.
60  valid = valid .and. allocated(aero_binned%num_conc)
61  valid = valid .and. allocated(aero_binned%vol_conc)
62  valid = valid &
63  .and. (size(aero_binned%num_conc) == size(aero_binned%num_conc, 1))
65 
66  end function aero_binned_is_allocated
67 
68 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
69 
70  !> Set the number of bins and species in an aero_binned_t.
71  subroutine aero_binned_set_sizes(aero_binned, n_bin, n_spec)
72 
73  !> Structure to be allocated.
74  type(aero_binned_t), intent(inout) :: aero_binned
75  !> Number of aerosol bins to allocate (typically \c bin_grid%%n_bin).
76  integer, intent(in) :: n_bin
77  !> Number of aerosol species to allocate (typically
78  !> \c aero_data%%n_spec).
79  integer, intent(in) :: n_spec
80 
81  if (allocated(aero_binned%num_conc)) deallocate(aero_binned%num_conc)
82  if (allocated(aero_binned%vol_conc)) deallocate(aero_binned%vol_conc)
83  allocate(aero_binned%num_conc(n_bin))
84  allocate(aero_binned%vol_conc(n_bin, n_spec))
85  call aero_binned_zero(aero_binned)
86 
87  end subroutine aero_binned_set_sizes
88 
89 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
90 
91  !> Set all internal data in an aero_binned_t structure to zero.
92  subroutine aero_binned_zero(aero_binned)
93 
94  !> Structure to zero.
95  type(aero_binned_t), intent(inout) :: aero_binned
96 
97  if (aero_binned_is_allocated(aero_binned)) then
98  aero_binned%num_conc = 0d0
99  aero_binned%vol_conc = 0d0
100  end if
101 
102  end subroutine aero_binned_zero
103 
104 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
105 
106  !> Add two aero_binned_t structures together.
107  !!
108  !! Symbolically does aero_binned = aero_binned + aero_binned_delta.
109  subroutine aero_binned_add(aero_binned, aero_binned_delta)
110 
111  !> Base aero_binned_t structure that will be added to.
112  type(aero_binned_t), intent(inout) :: aero_binned
113  !> Structure to add to aero_binned.
114  type(aero_binned_t), intent(in) :: aero_binned_delta
115 
116  if (aero_binned_is_allocated(aero_binned_delta)) then
117  if (aero_binned_is_allocated(aero_binned)) then
118  aero_binned%num_conc = aero_binned%num_conc &
119  + aero_binned_delta%num_conc
120  aero_binned%vol_conc = aero_binned%vol_conc &
121  + aero_binned_delta%vol_conc
122  else
123  aero_binned%num_conc = aero_binned_delta%num_conc
124  aero_binned%vol_conc = aero_binned_delta%vol_conc
125  end if
126  end if
127 
128  end subroutine aero_binned_add
129 
130 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
131 
132  !> Add a scaled \c aero_binned_t structure to an existing one.
133  !!
134  !! Symbolically does aero_binned = aero_binned + alpha * aero_binned_delta.
135  subroutine aero_binned_add_scaled(aero_binned, aero_binned_delta, alpha)
136 
137  !> Base aero_binned_t structure that will be added to.
138  type(aero_binned_t), intent(inout) :: aero_binned
139  !> Structure to add to aero_binned.
140  type(aero_binned_t), intent(in) :: aero_binned_delta
141  !> Scale factor.
142  real(kind=dp), intent(in) :: alpha
143 
144  if (aero_binned_is_allocated(aero_binned_delta)) then
145  if (aero_binned_is_allocated(aero_binned)) then
146  aero_binned%num_conc = aero_binned%num_conc &
147  + alpha * aero_binned_delta%num_conc
148  aero_binned%vol_conc = aero_binned%vol_conc &
149  + alpha * aero_binned_delta%vol_conc
150  else
151  aero_binned%num_conc = aero_binned_delta%num_conc
152  aero_binned%vol_conc = aero_binned_delta%vol_conc
153  end if
154  end if
155 
156  end subroutine aero_binned_add_scaled
157 
158 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
159 
160  !> Subtract one aero_binned_t structure from another.
161  !!
162  !! Symbolically does aero_binned = aero_binned - aero_binned_delta.
163  subroutine aero_binned_sub(aero_binned, aero_binned_delta)
164 
165  !> Base aero_binned_t structure that will be subtracted from.
166  type(aero_binned_t), intent(inout) :: aero_binned
167  !> Structure to subtract from aero_binned.
168  type(aero_binned_t), intent(in) :: aero_binned_delta
169 
170  if (aero_binned_is_allocated(aero_binned_delta)) then
171  if (aero_binned_is_allocated(aero_binned)) then
172  aero_binned%num_conc = aero_binned%num_conc &
173  - aero_binned_delta%num_conc
174  aero_binned%vol_conc = aero_binned%vol_conc &
175  - aero_binned_delta%vol_conc
176  else
177  aero_binned%num_conc = - aero_binned_delta%num_conc
178  aero_binned%vol_conc = - aero_binned_delta%vol_conc
179  end if
180  end if
181 
182  end subroutine aero_binned_sub
183 
184 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
185 
186  !> Scale an aero_binned_t by a real number.
187  !!
188  !! Symbolically does aero_binned = aero_binned * alpha.
189  subroutine aero_binned_scale(aero_binned, alpha)
190 
191  !> Base aero_binned to scale.
192  type(aero_binned_t), intent(inout) :: aero_binned
193  !> Scale factor.
194  real(kind=dp), intent(in) :: alpha
195 
196  if (aero_binned_is_allocated(aero_binned)) then
197  aero_binned%num_conc = aero_binned%num_conc * alpha
198  aero_binned%vol_conc = aero_binned%vol_conc * alpha
199  end if
200 
201  end subroutine aero_binned_scale
202 
203 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
204 
205  !> Scales an aero_binned_t element-wise by an array of reals.
206  subroutine aero_binned_scale_by_array(aero_binned, alpha_array)
207 
208  !> Base aero_binned_t structure that will be scaled.
209  type(aero_binned_t), intent(inout) :: aero_binned
210  !> Structure to scale aero_binned.
211  real(kind=dp), allocatable, intent(in) :: alpha_array(:)
212 
213  integer :: i
214 
215  do i = 1, size(aero_binned%num_conc)
216  aero_binned%num_conc(i) = alpha_array(i)*aero_binned%num_conc(i)
217  aero_binned%vol_conc(i,:) = alpha_array(i)*aero_binned%vol_conc(i,:)
218  end do
219 
220  end subroutine aero_binned_scale_by_array
221 
222 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
223 
224  !> Add an aero_dist_t to an aero_binned_t.
225  !!
226  !! Symbolically does aero_binned = aero_binned + aero_dist.
227  subroutine aero_binned_add_aero_dist(aero_binned, bin_grid, &
228  aero_data, aero_dist)
229 
230  !> Base aero_binned_t structure to add to.
231  type(aero_binned_t), intent(inout) :: aero_binned
232  !> Bin grid.
233  type(bin_grid_t), intent(in) :: bin_grid
234  !> Aerosol data.
235  type(aero_data_t), intent(in) :: aero_data
236  !> The aero_dist_t structure to add.
237  type(aero_dist_t), intent(in) :: aero_dist
238 
239  real(kind=dp) :: dist_num_conc(bin_grid_size(bin_grid))
240  real(kind=dp) :: dist_vol_conc(bin_grid_size(bin_grid), &
241  aero_data_n_spec(aero_data))
242 
243  call aero_dist_num_conc(aero_dist, bin_grid, aero_data, &
244  dist_num_conc)
245  call aero_dist_vol_conc(aero_dist, bin_grid, aero_data, &
246  dist_vol_conc)
247  if (aero_binned_is_allocated(aero_binned)) then
248  aero_binned%num_conc = aero_binned%num_conc + dist_num_conc
249  aero_binned%vol_conc = aero_binned%vol_conc + dist_vol_conc
250  else
251  aero_binned%num_conc = dist_num_conc
252  aero_binned%vol_conc = dist_vol_conc
253  end if
254 
255  end subroutine aero_binned_add_aero_dist
256 
257 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
258 
259  !> Determine the number of bytes required to pack the structure.
260  !!
261  !! See pmc_mpi for usage details.
262  integer function pmc_mpi_pack_size_aero_binned(val)
263 
264  !> Structure to pack.
265  type(aero_binned_t), intent(in) :: val
266 
268  pmc_mpi_pack_size_real_array(val%num_conc) &
269  + pmc_mpi_pack_size_real_array_2d(val%vol_conc)
270 
271  end function pmc_mpi_pack_size_aero_binned
272 
273 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
274 
275  !> Pack the structure into the buffer and advance position.
276  !!
277  !! See pmc_mpi for usage details.
278  subroutine pmc_mpi_pack_aero_binned(buffer, position, val)
279 
280  !> Memory buffer.
281  character, intent(inout) :: buffer(:)
282  !> Current buffer position.
283  integer, intent(inout) :: position
284  !> Structure to pack.
285  type(aero_binned_t), intent(in) :: val
286 
287 #ifdef PMC_USE_MPI
288  integer :: prev_position
289 
290  prev_position = position
291  call pmc_mpi_pack_real_array(buffer, position, val%num_conc)
292  call pmc_mpi_pack_real_array_2d(buffer, position, val%vol_conc)
293  call assert(348207873, &
294  position - prev_position <= pmc_mpi_pack_size_aero_binned(val))
295 #endif
296 
297  end subroutine pmc_mpi_pack_aero_binned
298 
299 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
300 
301  !> Unpack the structure from the buffer and advance position.
302  !!
303  !! See pmc_mpi for usage details.
304  subroutine pmc_mpi_unpack_aero_binned(buffer, position, val)
305 
306  !> Memory buffer.
307  character, intent(inout) :: buffer(:)
308  !> Current buffer position.
309  integer, intent(inout) :: position
310  !> Structure to unpack into (must not be allocated).
311  type(aero_binned_t), intent(inout) :: val
312 
313 #ifdef PMC_USE_MPI
314  integer :: prev_position
315 
316  prev_position = position
317  call pmc_mpi_unpack_real_array(buffer, position, val%num_conc)
318  call pmc_mpi_unpack_real_array_2d(buffer, position, val%vol_conc)
319  call assert(878267066, &
320  position - prev_position <= pmc_mpi_pack_size_aero_binned(val))
321 #endif
322 
323  end subroutine pmc_mpi_unpack_aero_binned
324 
325 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
326 
327  !> Computes the average of the structure across all processes,
328  !> storing the result on the root process.
329  subroutine pmc_mpi_reduce_avg_aero_binned(val, val_avg)
330 
331  !> Per-process value to average.
332  type(aero_binned_t), intent(in) :: val
333  !> Averaged result (only valid on root process).
334  type(aero_binned_t), intent(inout) :: val_avg
335 
336  call pmc_mpi_reduce_avg_real_array(val%num_conc, val_avg%num_conc)
337  call pmc_mpi_reduce_avg_real_array_2d(val%vol_conc, val_avg%vol_conc)
338 
339  end subroutine pmc_mpi_reduce_avg_aero_binned
340 
341 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
342 
343  !> Write full state.
344  subroutine aero_binned_output_netcdf(aero_binned, ncid, bin_grid, &
345  aero_data)
346 
347  !> Aero_binned to write.
348  type(aero_binned_t), intent(in) :: aero_binned
349  !> NetCDF file ID, in data mode.
350  integer, intent(in) :: ncid
351  !> bin_grid structure.
352  type(bin_grid_t), intent(in) :: bin_grid
353  !> aero_data structure.
354  type(aero_data_t), intent(in) :: aero_data
355 
356  integer :: dimid_aero_diam, dimid_aero_species
357  real(kind=dp) :: mass_conc(bin_grid_size(bin_grid), &
358  aero_data_n_spec(aero_data))
359  integer :: i_bin
360 
361  !> \page output_format_aero_binned Output File Format: Aerosol Binned Sectional State
362  !!
363  !! The aerosol size distributions (number and mass) are stored on
364  !! a logarmithmic grid (see the \ref output_format_diam_bin_grid
365  !! section). To compute the total number or mass concentration,
366  !! compute the sum over \c i of <tt>aero_number_concentration(i) *
367  !! aero_diam_widths(i)</tt>, for example.
368  !!
369  !! The aerosol binned sectional state uses the \c aero_species
370  !! NetCDF dimension as specified in the \ref
371  !! output_format_aero_data section, as well as the \c aero_diam
372  !! NetCDF dimension specified in the \ref
373  !! output_format_diam_bin_grid section.
374  !!
375  !! The aerosol binned sectional state NetCDF variables are:
376  !! - \b aero_number_concentration (unit 1/m^3, dim \c aero_diam): the
377  !! number size distribution for the aerosol population,
378  !! \f$ dN(r)/d\ln r \f$, per bin
379  !! - \b aero_mass_concentration (unit kg/m^3, dim
380  !! <tt>dimid_aero_diam x dimid_aero_species</tt>): the mass size
381  !! distribution for the aerosol population,
382  !! \f$ dM(r,s)/d\ln r \f$, per bin and per species
383 
384  ! output_format_diam_bin_grid is here, as this is the only place it's used
385 
386  !> \page output_format_diam_bin_grid Output File Format: Diameter Bin Grid Data
387  !!
388  !! The aerosol diameter bin grid data NetCDF dimensions are:
389  !! - \b aero_diam: number of bins (grid cells) on the diameter axis
390  !! - \b aero_diam_edges: number of bin edges (grid cell edges) on
391  !! the diameter axis --- always equal to <tt>aero_diam + 1</tt>
392  !!
393  !! The aerosol diameter bin grid data NetCDF variables are:
394  !! - \b aero_diam (unit m, dim \c aero_diam): aerosol diameter axis
395  !! bin centers --- centered on a logarithmic scale from the edges, so
396  !! that <tt>aero_diam(i) / aero_diam_edges(i) =
397  !! sqrt(aero_diam_edges(i+1) / aero_diam_edges(i))</tt>
398  !! - \b aero_diam_edges (unit m, dim \c aero_diam_edges): aersol
399  !! diameter axis bin edges (there is one more edge than center)
400  !! - \b aero_diam_widths (dimensionless, dim \c aero_diam):
401  !! the base-e logarithmic bin widths --- <tt>aero_diam_widths(i)
402  !! = ln(aero_diam_edges(i+1) / aero_diam_edges(i))</tt>, so
403  !! all bins have the same width
404  !!
405  !! See also:
406  !! - \ref input_format_diam_bin_grid --- the corresponding input format
407 
408  do i_bin = 1,bin_grid_size(bin_grid)
409  mass_conc(i_bin,:) = aero_binned%vol_conc(i_bin,:) * aero_data%density
410  end do
411 
412  call bin_grid_netcdf_dim(bin_grid, ncid, "aero_diam", "m", &
413  dimid_aero_diam, "aerosol diameter", scale=2d0)
414  call aero_data_netcdf_dim_aero_species(aero_data, ncid, dimid_aero_species)
415 
416  call pmc_nc_write_real_1d(ncid, aero_binned%num_conc, &
417  "aero_number_concentration", (/ dimid_aero_diam /), &
418  unit="1/m^3", &
419  long_name="aerosol number size concentration distribution", &
420  description="logarithmic number size concentration, " &
421  // "d N(r)/d ln D --- multiply by aero_diam_widths(i) " &
422  // "and sum over i to compute the total number concentration")
423  call pmc_nc_write_real_2d(ncid, mass_conc, &
424  "aero_mass_concentration", &
425  (/ dimid_aero_diam, dimid_aero_species /), unit="kg/m^3", &
426  long_name="aerosol mass size concentration distribution", &
427  description="logarithmic mass size concentration per species, " &
428  // "d M(r,s)/d ln D --- multiply by aero_diam_widths(i) " &
429  // "and sum over i to compute the total mass concentration of " &
430  // "species s")
431 
432  end subroutine aero_binned_output_netcdf
433 
434  ! output_format_diam_bin_grid is here, as this is the only place it's used
435 
436  ! this belongs in the subroutine above, but is outside because
437  ! Doxygen 1.8.7 doesn't resolve references when multiple \page
438  ! blocks are in one subroutine
439 
440  !> \page output_format_diam_bin_grid Output File Format: Diameter Bin Grid Data
441  !!
442  !! The aerosol diameter bin grid data NetCDF dimensions are:
443  !! - \b aero_diam: number of bins (grid cells) on the diameter axis
444  !! - \b aero_diam_edges: number of bin edges (grid cell edges) on
445  !! the diameter axis --- always equal to <tt>aero_diam + 1</tt>
446  !!
447  !! The aerosol diameter bin grid data NetCDF variables are:
448  !! - \b aero_diam (unit m, dim \c aero_diam): aerosol diameter axis
449  !! bin centers --- centered on a logarithmic scale from the edges, so
450  !! that <tt>aero_diam(i) / aero_diam_edges(i) =
451  !! sqrt(aero_diam_edges(i+1) / aero_diam_edges(i))</tt>
452  !! - \b aero_diam_edges (unit m, dim \c aero_diam_edges): aersol
453  !! diameter axis bin edges (there is one more edge than center)
454  !! - \b aero_diam_widths (dimensionless, dim \c aero_diam):
455  !! the base-e logarithmic bin widths --- <tt>aero_diam_widths(i)
456  !! = ln(aero_diam_edges(i+1) / aero_diam_edges(i))</tt>, so
457  !! all bins have the same width
458  !!
459  !! See also:
460  !! - \ref input_format_diam_bin_grid --- the corresponding input format
461 
462 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
463 
464  !> Read full state.
465  subroutine aero_binned_input_netcdf(aero_binned, ncid, bin_grid, &
466  aero_data)
467 
468  !> Aero_binned to write.
469  type(aero_binned_t), intent(inout) :: aero_binned
470  !> NetCDF file ID, in data mode.
471  integer, intent(in) :: ncid
472  !> bin_grid structure.
473  type(bin_grid_t), intent(in) :: bin_grid
474  !> aero_data structure.
475  type(aero_data_t), intent(in) :: aero_data
476 
477  integer :: i_bin
478 
479  call pmc_nc_read_real_1d(ncid, aero_binned%num_conc, &
480  "aero_number_concentration")
481  call pmc_nc_read_real_2d(ncid, aero_binned%vol_conc, &
482  "aero_mass_concentration")
483  ! convert mass concentation to volume concentration
484  do i_bin = 1,bin_grid_size(bin_grid)
485  aero_binned%vol_conc(i_bin,:) = aero_binned%vol_conc(i_bin,:) &
486  / aero_data%density
487  end do
488 
489  end subroutine aero_binned_input_netcdf
490 
491 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
492 
493 end module pmc_aero_binned
pmc_aero_binned::aero_binned_add_scaled
subroutine aero_binned_add_scaled(aero_binned, aero_binned_delta, alpha)
Add a scaled aero_binned_t structure to an existing one.
Definition: aero_binned.F90:136
pmc_aero_data::aero_data_n_spec
elemental integer function aero_data_n_spec(aero_data)
Return the number of aerosol species, or -1 if uninitialized.
Definition: aero_data.F90:236
pmc_aero_binned::pmc_mpi_reduce_avg_aero_binned
subroutine pmc_mpi_reduce_avg_aero_binned(val, val_avg)
Computes the average of the structure across all processes, storing the result on the root process.
Definition: aero_binned.F90:330
pmc_mpi
Wrapper functions for MPI.
Definition: mpi.F90:13
pmc_aero_binned::aero_binned_set_sizes
subroutine aero_binned_set_sizes(aero_binned, n_bin, n_spec)
Set the number of bins and species in an aero_binned_t.
Definition: aero_binned.F90:72
pmc_mpi::pmc_mpi_reduce_avg_real_array_2d
subroutine pmc_mpi_reduce_avg_real_array_2d(val, val_avg)
Computes the average of val across all processes, storing the result in val_avg on the root process.
Definition: mpi.F90:1253
pmc_aero_particle
The aero_particle_t structure and associated subroutines.
Definition: aero_particle.F90:9
pmc_aero_binned::pmc_mpi_pack_aero_binned
subroutine pmc_mpi_pack_aero_binned(buffer, position, val)
Pack the structure into the buffer and advance position.
Definition: aero_binned.F90:279
pmc_aero_binned::aero_binned_add
subroutine aero_binned_add(aero_binned, aero_binned_delta)
Add two aero_binned_t structures together.
Definition: aero_binned.F90:110
pmc_spec_file
Reading formatted text input.
Definition: spec_file.F90:43
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_mpi::pmc_mpi_pack_size_real_array
integer function pmc_mpi_pack_size_real_array(val)
Determines the number of bytes required to pack the given value.
Definition: mpi.F90:477
pmc_aero_dist::aero_dist_vol_conc
subroutine aero_dist_vol_conc(aero_dist, bin_grid, aero_data, vol_conc)
Return the binned per-species volume concentration for an aero_dist.
Definition: aero_dist.F90:127
pmc_aero_binned::aero_binned_add_aero_dist
subroutine aero_binned_add_aero_dist(aero_binned, bin_grid, aero_data, aero_dist)
Add an aero_dist_t to an aero_binned_t.
Definition: aero_binned.F90:229
pmc_mpi::pmc_mpi_pack_size_real_array_2d
integer function pmc_mpi_pack_size_real_array_2d(val)
Determines the number of bytes required to pack the given value.
Definition: mpi.F90:530
pmc_aero_binned::aero_binned_scale_by_array
subroutine aero_binned_scale_by_array(aero_binned, alpha_array)
Scales an aero_binned_t element-wise by an array of reals.
Definition: aero_binned.F90:207
pmc_aero_dist
The aero_dist_t structure and associated subroutines.
Definition: aero_dist.F90:18
pmc_aero_binned::pmc_mpi_pack_size_aero_binned
integer function pmc_mpi_pack_size_aero_binned(val)
Determine the number of bytes required to pack the structure.
Definition: aero_binned.F90:263
pmc_mpi::pmc_mpi_pack_real_array_2d
subroutine pmc_mpi_pack_real_array_2d(buffer, position, val)
Packs the given value into the buffer, advancing position.
Definition: mpi.F90:784
pmc_aero_binned::aero_binned_sub
subroutine aero_binned_sub(aero_binned, aero_binned_delta)
Subtract one aero_binned_t structure from another.
Definition: aero_binned.F90:164
pmc_aero_data::aero_data_t
Aerosol material properties and associated data.
Definition: aero_data.F90:49
pmc_aero_binned::aero_binned_is_allocated
logical function aero_binned_is_allocated(aero_binned)
Determine whether the aero_binned is correctly allocated.
Definition: aero_binned.F90:53
pmc_aero_data::aero_data_netcdf_dim_aero_species
subroutine aero_data_netcdf_dim_aero_species(aero_data, ncid, dimid_aero_species)
Write the aero species dimension to the given NetCDF file if it is not already present and in any cas...
Definition: aero_data.F90:596
pmc_bin_grid::bin_grid_netcdf_dim
subroutine bin_grid_netcdf_dim(bin_grid, ncid, dim_name, unit, dimid, long_name, scale)
Write a bin grid dimension to the given NetCDF file if it is not already present and in any case retu...
Definition: bin_grid.F90:388
pmc_aero_dist::aero_dist_t
A complete aerosol distribution, consisting of several modes.
Definition: aero_dist.F90:33
pmc_util
Common utility subroutines.
Definition: util.F90:9
pmc_mpi::pmc_mpi_unpack_real_array_2d
subroutine pmc_mpi_unpack_real_array_2d(buffer, position, val)
Unpacks the given value from the buffer, advancing position.
Definition: mpi.F90:1042
pmc_aero_binned::aero_binned_scale
subroutine aero_binned_scale(aero_binned, alpha)
Scale an aero_binned_t by a real number.
Definition: aero_binned.F90:190
pmc_aero_binned::aero_binned_zero
subroutine aero_binned_zero(aero_binned)
Set all internal data in an aero_binned_t structure to zero.
Definition: aero_binned.F90:93
pmc_aero_binned
The aero_binned_t structure and associated subroutines.
Definition: aero_binned.F90:9
pmc_aero_binned::aero_binned_input_netcdf
subroutine aero_binned_input_netcdf(aero_binned, ncid, bin_grid, aero_data)
Read full state.
Definition: aero_binned.F90:467
pmc_aero_binned::aero_binned_t
Aerosol number and volume distributions stored per bin.
Definition: aero_binned.F90:37
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_mpi::pmc_mpi_pack_real_array
subroutine pmc_mpi_pack_real_array(buffer, position, val)
Packs the given value into the buffer, advancing position.
Definition: mpi.F90:720
pmc_aero_binned::pmc_mpi_unpack_aero_binned
subroutine pmc_mpi_unpack_aero_binned(buffer, position, val)
Unpack the structure from the buffer and advance position.
Definition: aero_binned.F90:305
pmc_bin_grid::bin_grid_t
1D grid, either logarithmic or linear.
Definition: bin_grid.F90:33
pmc_mpi::pmc_mpi_reduce_avg_real_array
subroutine pmc_mpi_reduce_avg_real_array(val, val_avg)
Computes the average of val across all processes, storing the result in val_avg on the root process.
Definition: mpi.F90:1226
pmc_aero_dist::aero_dist_num_conc
subroutine aero_dist_num_conc(aero_dist, bin_grid, aero_data, num_conc)
Return the binned number concentration for an aero_dist.
Definition: aero_dist.F90:99
pmc_mpi::pmc_mpi_unpack_real_array
subroutine pmc_mpi_unpack_real_array(buffer, position, val)
Unpacks the given value from the buffer, advancing position.
Definition: mpi.F90:978