PartMC  2.6.1
aero_weight.F90
Go to the documentation of this file.
1 ! Copyright (C) 2010-2015 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_weight module.
7 
8 !> The aero_weight_t structure and associated subroutines.
10 
11  use pmc_util
12  use pmc_constants
13  use pmc_rand
14  use pmc_spec_file
16  use pmc_aero_data
17  use pmc_netcdf
18  use pmc_mpi
19 #ifdef PMC_USE_MPI
20  use mpi
21 #endif
22 
23  !> Type code for an undefined or invalid weighting.
24  integer, parameter :: aero_weight_type_invalid = 0
25  !> Type code for no (or flat) weighting.
26  integer, parameter :: aero_weight_type_none = 1
27  !> Type code for power function weighting.
28  integer, parameter :: aero_weight_type_power = 2
29  !> Type code for MFA weighting.
30  integer, parameter :: aero_weight_type_mfa = 3
31 
32  !> An aerosol size distribution weighting function.
34  !> Weight type (given by module constants).
35  integer :: type
36  !> Overall weight magnitude (m^{-3}).
37  real(kind=dp) :: magnitude
38  !> Exponent for "power" weight.
39  real(kind=dp) :: exponent
40  end type aero_weight_t
41 
42 contains
43 
44 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
45 
46  !> Sets the \c aero_weight to a non-zero normalized value.
47  elemental subroutine aero_weight_normalize(aero_weight)
48 
49  !> Aerosol weight.
50  type(aero_weight_t), intent(inout) :: aero_weight
51 
52  aero_weight%magnitude = 1d0
53 
54  end subroutine aero_weight_normalize
55 
56 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
57 
58  !> Scale the weight by the given fraction, so <tt>new_weight =
59  !> old_weight * factor</tt>.
60  elemental subroutine aero_weight_scale(aero_weight, factor)
61 
62  !> Aerosol weight to scale.
63  type(aero_weight_t), intent(inout) :: aero_weight
64  !> Factor to scale by.
65  real(kind=dp), intent(in) :: factor
66 
67  aero_weight%magnitude = aero_weight%magnitude * factor
68 
69  end subroutine aero_weight_scale
70 
71 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
72 
73  !> Combine \c aero_weight_delta into \c aero_weight with a harmonic mean.
74  elemental subroutine aero_weight_combine(aero_weight, aero_weight_delta)
75 
76  !> Aerosol weight to add into.
77  type(aero_weight_t), intent(inout) :: aero_weight
78  !> Aerosol weight to add from.
79  type(aero_weight_t), intent(in) :: aero_weight_delta
80 
81  aero_weight%magnitude = harmonic_mean(aero_weight%magnitude, &
82  aero_weight_delta%magnitude)
83 
84  end subroutine aero_weight_combine
85 
86 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
87 
88  !> Adjust source and destination weights to reflect moving \c
89  !> sample_prop proportion of particles from \c aero_weight_from to
90  !> \c aero_weight_to.
91  elemental subroutine aero_weight_shift(aero_weight_from, &
92  aero_weight_to, sample_prop, overwrite_to)
93 
94  !> Aerosol weight to shift from.
95  type(aero_weight_t), intent(inout) :: aero_weight_from
96  !> Aerosol weight to shift to.
97  type(aero_weight_t), intent(inout) :: aero_weight_to
98  !> Proportion of particles being transfered.
99  real(kind=dp), intent(in) :: sample_prop
100  !> Whether to overwrite the destination weight (default: no).
101  logical, intent(in), optional :: overwrite_to
102 
103  real(kind=dp) :: magnitude_transfer
104  logical :: use_overwrite_to
105 
106  magnitude_transfer = aero_weight_from%magnitude / sample_prop
107  aero_weight_from%magnitude = harmonic_mean(aero_weight_from%magnitude, &
108  - magnitude_transfer)
109  use_overwrite_to = .false.
110  if (present(overwrite_to)) then
111  if (overwrite_to) then
112  use_overwrite_to = .true.
113  end if
114  end if
115  if (use_overwrite_to) then
116  aero_weight_to%magnitude = magnitude_transfer
117  else
118  aero_weight_to%magnitude = harmonic_mean(aero_weight_to%magnitude, &
119  magnitude_transfer)
120  end if
121 
122  end subroutine aero_weight_shift
123 
124 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
125 
126  !> Compute the number concentration at a given radius (m^{-3}).
127  real(kind=dp) function aero_weight_num_conc_at_radius(aero_weight, radius)
128 
129  !> Aerosol weight.
130  type(aero_weight_t), intent(in) :: aero_weight
131  !> Radius to compute number concentration at (m).
132  real(kind=dp), intent(in) :: radius
133 
135  if (aero_weight%type == aero_weight_type_none) then
136  aero_weight_num_conc_at_radius = aero_weight%magnitude
137  elseif ((aero_weight%type == aero_weight_type_power) &
138  .or. (aero_weight%type == aero_weight_type_mfa)) then
139  aero_weight_num_conc_at_radius = aero_weight%magnitude &
140  * radius**aero_weight%exponent
141  else
142  call die_msg(700421478, "unknown aero_weight type: " &
143  // trim(integer_to_string(aero_weight%type)))
144  end if
145 
146  end function aero_weight_num_conc_at_radius
147 
148 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
149 
150  !> Compute the number concentration for a particle (m^{-3}).
151  real(kind=dp) function aero_weight_num_conc(aero_weight, aero_particle, &
152  aero_data)
153 
154  !> Aerosol weight.
155  type(aero_weight_t), intent(in) :: aero_weight
156  !> Aerosol particle to compute number concentration for.
157  type(aero_particle_t), intent(in) :: aero_particle
158  !> Aerosol data.
159  type(aero_data_t), intent(in) :: aero_data
160 
162  aero_particle_radius(aero_particle, aero_data))
163 
164  end function aero_weight_num_conc
165 
166 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
167 
168  !> Compute the radius at a given number concentration (m). Inverse
169  !> of aero_weight_num_conc_at_radius().
170  real(kind=dp) function aero_weight_radius_at_num_conc(aero_weight, num_conc)
171 
172  !> Aerosol weight.
173  type(aero_weight_t), intent(in) :: aero_weight
174  !> Number concentration to compute the radius at (m^{-3}).
175  real(kind=dp), intent(in) :: num_conc
176 
178  if (aero_weight%type == aero_weight_type_none) then
179  call die_msg(545688537, "cannot invert weight type 'none'")
180  elseif ((aero_weight%type == aero_weight_type_power) &
181  .or. (aero_weight%type == aero_weight_type_mfa)) then
182  call assert_msg(902242996, aero_weight%exponent /= 0d0, &
183  "cannot invert weight with zero exponent")
185  = exp(log(num_conc / aero_weight%magnitude) / aero_weight%exponent)
186  else
187  call die_msg(307766845, "unknown aero_weight type: " &
188  // trim(integer_to_string(aero_weight%type)))
189  end if
190 
191  end function aero_weight_radius_at_num_conc
192 
193 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
194 
195  !> Ensures that a weight function exponent is valid.
196  subroutine aero_weight_check_valid_exponent(aero_weight)
197 
198  !> Aerosol weight array.
199  type(aero_weight_t), intent(in) :: aero_weight
200 
201  ! check we know about all the weight type
202  call assert(269952052, (aero_weight%type == aero_weight_type_none) &
203  .or. (aero_weight%type == aero_weight_type_power) &
204  .or. (aero_weight%type == aero_weight_type_mfa))
205  if (aero_weight%type == aero_weight_type_none) then
206  call assert(853998284, aero_weight%exponent == 0d0)
207  end if
208  if (aero_weight%type == aero_weight_type_mfa) then
209  call assert(829651126, aero_weight%exponent == -3d0)
210  end if
211 
212  end subroutine aero_weight_check_valid_exponent
213 
214 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
215 
216  !> Determine whether a weight function is monotone increasing,
217  !> monotone decreasing, or neither.
218  subroutine aero_weight_check_monotonicity(aero_weight, &
219  monotone_increasing, monotone_decreasing)
220 
221  !> Aerosol weight array.
222  type(aero_weight_t), intent(in) :: aero_weight
223  !> Whether all weights are monotone increasing.
224  logical, intent(out) :: monotone_increasing
225  !> Whether all weights are monotone decreasing.
226  logical, intent(out) :: monotone_decreasing
227 
228  ! check we know about all the weight types
229  call assert(610698264, (aero_weight%type == aero_weight_type_none) &
230  .or. (aero_weight%type == aero_weight_type_power) &
231  .or. (aero_weight%type == aero_weight_type_mfa))
232  monotone_increasing = .true.
233  monotone_decreasing = .true.
234  if (aero_weight%type == aero_weight_type_power) then
235  if (aero_weight%exponent < 0d0) then
236  monotone_increasing = .false.
237  end if
238  if (aero_weight%exponent > 0d0) then
239  monotone_decreasing = .false.
240  end if
241  end if
242  if (aero_weight%type == aero_weight_type_mfa) then
243  monotone_increasing = .false.
244  end if
245 
246  end subroutine aero_weight_check_monotonicity
247 
248 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
249 
250  !> Read an aero_weight from a spec file.
251  subroutine spec_file_read_aero_weight(file, aero_weight)
252 
253  !> Spec file.
254  type(spec_file_t), intent(inout) :: file
255  !> Aerosol weight.
256  type(aero_weight_t), intent(inout) :: aero_weight
257 
258  character(len=SPEC_LINE_MAX_VAR_LEN) :: weight_type
259 
260  !> \page input_format_aero_weight Input File Format: Aerosol Weighting Function
261  !!
262  !! For efficiency the aerosol population can be weighted so that
263  !! the true number distribution \f$n(D)\f$ is given by
264  !! \f[ n(D) = w(D) c(D) \f]
265  !! where \f$w(D)\f$ is a fixed weighting function, \f$c(D)\f$ is
266  !! the computational (simulated) number distribution, and \f$D\f$
267  !! is the diameter. Thus a large value of \f$w(D)\f$ means that
268  !! relatively few computational particles are used at diameter
269  !! \f$D\f$, while a small value of \f$w(D)\f$ means that
270  !! relatively many computational particles will be used at that
271  !! diameter.
272  !!
273  !! The aerosol weighting function is specified by the parameters:
274  !! - \b weight (string): the type of weighting function --- must
275  !! be one of: "none" for no weighting (\f$w(D) = 1\f$);
276  !! "power" for a power-law weighting (\f$w(D) = D^\alpha\f$),
277  !! or "mfa" for the mass flow algorithm weighting (\f$w(D) =
278  !! D^{-3}\f$ with dependent coagulation particle removal)
279  !! - if the \c weight is \c power then the next parameter is:
280  !! - \b exponent (real, dimensionless): the exponent
281  !! \f$\alpha\f$ in the power law relationship --- setting
282  !! the \c exponent to 0 is equivalent to no weighting, while
283  !! setting the exponent negative uses more computational
284  !! particles at larger diameters and setting the exponent
285  !! positive uses more computational particles at smaller
286  !! diameters; in practice exponents between 0 and -3 are
287  !! most useful
288  !!
289  !! See also:
290  !! - \ref spec_file_format --- the input file text format
291 
292  call spec_file_read_string(file, 'weight', weight_type)
293  aero_weight%magnitude = 0d0
294  if (trim(weight_type) == 'none') then
295  aero_weight%type = aero_weight_type_none
296  elseif (trim(weight_type) == 'power') then
297  aero_weight%type = aero_weight_type_power
298  call spec_file_read_real(file, 'exponent', aero_weight%exponent)
299  elseif (trim(weight_type) == 'mfa') then
300  aero_weight%type = aero_weight_type_mfa
301  aero_weight%exponent = -3d0
302  else
303  call spec_file_die_msg(456342050, file, "unknown weight_type: " &
304  // trim(weight_type))
305  end if
306 
307  end subroutine spec_file_read_aero_weight
308 
309 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
310 
311  !> Determines the number of bytes required to pack the given value.
312  integer function pmc_mpi_pack_size_aero_weight(val)
313 
314  !> Value to pack.
315  type(aero_weight_t), intent(in) :: val
316 
318  pmc_mpi_pack_size_integer(val%type) &
319  + pmc_mpi_pack_size_real(val%magnitude) &
320  + pmc_mpi_pack_size_real(val%exponent)
321 
322  end function pmc_mpi_pack_size_aero_weight
323 
324 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
325 
326  !> Packs the given value into the buffer, advancing position.
327  subroutine pmc_mpi_pack_aero_weight(buffer, position, val)
328 
329  !> Memory buffer.
330  character, intent(inout) :: buffer(:)
331  !> Current buffer position.
332  integer, intent(inout) :: position
333  !> Value to pack.
334  type(aero_weight_t), intent(in) :: val
335 
336 #ifdef PMC_USE_MPI
337  integer :: prev_position
338 
339  prev_position = position
340  call pmc_mpi_pack_integer(buffer, position, val%type)
341  call pmc_mpi_pack_real(buffer, position, val%magnitude)
342  call pmc_mpi_pack_real(buffer, position, val%exponent)
343  call assert(579699255, &
344  position - prev_position <= pmc_mpi_pack_size_aero_weight(val))
345 #endif
346 
347  end subroutine pmc_mpi_pack_aero_weight
348 
349 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
350 
351  !> Unpacks the given value from the buffer, advancing position.
352  subroutine pmc_mpi_unpack_aero_weight(buffer, position, val)
353 
354  !> Memory buffer.
355  character, intent(inout) :: buffer(:)
356  !> Current buffer position.
357  integer, intent(inout) :: position
358  !> Value to pack.
359  type(aero_weight_t), intent(inout) :: val
360 
361 #ifdef PMC_USE_MPI
362  integer :: prev_position
363 
364  prev_position = position
365  call pmc_mpi_unpack_integer(buffer, position, val%type)
366  call pmc_mpi_unpack_real(buffer, position, val%magnitude)
367  call pmc_mpi_unpack_real(buffer, position, val%exponent)
368  call assert(639056899, &
369  position - prev_position <= pmc_mpi_pack_size_aero_weight(val))
370 #endif
371 
372  end subroutine pmc_mpi_unpack_aero_weight
373 
374 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
375 
376 end module pmc_aero_weight
pmc_aero_particle::aero_particle_t
Single aerosol particle data structure.
Definition: aero_particle.F90:26
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::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_mpi::pmc_mpi_pack_size_real
integer function pmc_mpi_pack_size_real(val)
Determines the number of bytes required to pack the given value.
Definition: mpi.F90:365
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_util::die_msg
subroutine die_msg(code, error_msg)
Error immediately.
Definition: util.F90:134
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::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_mpi::pmc_mpi_pack_real
subroutine pmc_mpi_pack_real(buffer, position, val)
Packs the given value into the buffer, advancing position.
Definition: mpi.F90:586
pmc_util::assert
subroutine assert(code, condition_ok)
Errors unless condition_ok is true.
Definition: util.F90:103
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_util::harmonic_mean
elemental real(kind=dp) function harmonic_mean(x1, x2)
Compute the harmonic mean of two numbers.
Definition: util.F90:1599
pmc_spec_file::spec_file_read_real
subroutine spec_file_read_real(file, name, var)
Read a real number from a spec file that must have the given name.
Definition: spec_file.F90:563
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_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_util::assert_msg
subroutine assert_msg(code, condition_ok, error_msg)
Errors unless condition_ok is true.
Definition: util.F90:77
pmc_aero_weight::aero_weight_type_mfa
integer, parameter aero_weight_type_mfa
Type code for MFA weighting.
Definition: aero_weight.F90:30
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_aero_weight::aero_weight_type_invalid
integer, parameter aero_weight_type_invalid
Type code for an undefined or invalid weighting.
Definition: aero_weight.F90:24
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::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::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_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_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_util
Common utility subroutines.
Definition: util.F90:9
pmc_spec_file::spec_file_die_msg
subroutine spec_file_die_msg(code, file, msg)
Exit with an error message containing filename and line number.
Definition: spec_file.F90:74
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_spec_file::spec_file_read_string
subroutine spec_file_read_string(file, name, var)
Read a string from a spec file that must have a given name.
Definition: spec_file.F90:605
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::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_mpi::pmc_mpi_unpack_real
subroutine pmc_mpi_unpack_real(buffer, position, val)
Unpacks the given value from the buffer, advancing position.
Definition: mpi.F90:843
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
pmc_aero_weight::aero_weight_radius_at_num_conc
real(kind=dp) function aero_weight_radius_at_num_conc(aero_weight, num_conc)
Compute the radius at a given number concentration (m). Inverse of aero_weight_num_conc_at_radius().
Definition: aero_weight.F90:171