Line data Source code
1 : module aerosol_properties_mod
2 : use shr_kind_mod, only: r8 => shr_kind_r8
3 :
4 : implicit none
5 :
6 : private
7 :
8 : public :: aerosol_properties
9 :
10 : !> aerosol_properties defines the configuration of any aerosol package (using
11 : !! any aerosol representation) based on user specification. These values are
12 : !! set during initialization and do not vary during the simulation.
13 : !!
14 : !! Each aerosol package (e.g., MAM, CARMA, etc) must extend the abstract
15 : !! aerosol_properties class to define the details of their configuration. Any
16 : !! package must implement each of the deferred procedures of the abstract
17 : !! aerosol_properties class, may include additional private data members and
18 : !! type-bound procedures, and may override functions of the abstract class.
19 : !!
20 : !! Please see the modal_aerosol_properties module for an example of how the
21 : !! aerosol_properties class can be extended for a specific aerosol package.
22 : type, abstract :: aerosol_properties
23 : private
24 : integer :: nbins_ = 0 ! number of aerosol bins
25 : integer :: ncnst_tot_ = 0 ! total number of constituents
26 : integer, allocatable :: nmasses_(:) ! number of species masses
27 : integer, allocatable :: nspecies_(:) ! number of species
28 : integer, allocatable :: indexer_(:,:) ! unique indices of the aerosol elements
29 : real(r8), allocatable :: alogsig_(:) ! natural log of geometric deviation of the number distribution for aerosol bin
30 : real(r8), allocatable :: f1_(:) ! eq 28 Abdul-Razzak et al 1998
31 : real(r8), allocatable :: f2_(:) ! eq 29 Abdul-Razzak et al 1998
32 : ! Abdul-Razzak, H., S.J. Ghan, and C. Rivera-Carpio, A parameterization of aerosol activation,
33 : ! 1, Singleaerosoltype. J. Geophys. Res., 103, 6123-6132, 1998.
34 : real(r8) :: soa_equivso4_factor_ = -huge(1._r8)
35 : real(r8) :: pom_equivso4_factor_ = -huge(1._r8)
36 : contains
37 : procedure :: initialize => aero_props_init
38 : procedure,private :: nbins_0list
39 : procedure(aero_nbins_rlist), deferred :: nbins_rlist
40 : generic :: nbins => nbins_0list,nbins_rlist
41 : procedure :: ncnst_tot
42 : procedure,private :: nspecies_per_bin
43 : procedure(aero_nspecies_rlist), deferred :: nspecies_per_bin_rlist
44 : procedure,private :: nspecies_all_bins
45 : generic :: nspecies => nspecies_all_bins,nspecies_per_bin,nspecies_per_bin_rlist
46 : procedure,private :: n_masses_all_bins
47 : procedure,private :: n_masses_per_bin
48 : generic :: nmasses => n_masses_all_bins,n_masses_per_bin
49 : procedure :: indexer
50 : procedure :: maxsat
51 : procedure(aero_amcube), deferred :: amcube
52 : procedure :: alogsig_0list
53 : procedure(aero_alogsig_rlist), deferred :: alogsig_rlist
54 : generic :: alogsig => alogsig_0list,alogsig_rlist
55 : procedure(aero_number_transported), deferred :: number_transported
56 : procedure(aero_props_get), deferred :: get
57 : procedure(aero_actfracs), deferred :: actfracs
58 : procedure(aero_num_names), deferred :: num_names
59 : procedure(aero_mmr_names), deferred :: mmr_names
60 : procedure(aero_amb_num_name), deferred :: amb_num_name
61 : procedure(aero_amb_mmr_name), deferred :: amb_mmr_name
62 : procedure(aero_species_type), deferred :: species_type
63 : procedure(aero_icenuc_updates_num), deferred :: icenuc_updates_num
64 : procedure(aero_icenuc_updates_mmr), deferred :: icenuc_updates_mmr
65 : procedure(aero_apply_num_limits), deferred :: apply_number_limits
66 : procedure(aero_hetfrz_species), deferred :: hetfrz_species
67 : procedure :: soa_equivso4_factor ! SOA Hygroscopicity / Sulfate Hygroscopicity
68 : procedure :: pom_equivso4_factor ! POM Hygroscopicity / Sulfate Hygroscopicity
69 : procedure(aero_soluble), deferred :: soluble
70 : procedure(aero_min_mass_mean_rad), deferred :: min_mass_mean_rad
71 : procedure(aero_optics_params), deferred :: optics_params
72 : procedure(aero_bin_name), deferred :: bin_name
73 :
74 : procedure :: final=>aero_props_final
75 : end type aerosol_properties
76 :
77 : integer,public, parameter :: aero_name_len = 32 ! common length of aersols names, species, etc
78 :
79 : abstract interface
80 :
81 : !------------------------------------------------------------------------------
82 : ! returns number of transported aerosol constituents
83 : !------------------------------------------------------------------------------
84 : integer function aero_number_transported(self)
85 : import :: aerosol_properties
86 : class(aerosol_properties), intent(in) :: self
87 : end function aero_number_transported
88 :
89 : !------------------------------------------------------------------------
90 : ! returns aerosol properties:
91 : ! density
92 : ! hygroscopicity
93 : ! species type
94 : ! short wave species refractive indices
95 : ! long wave species refractive indices
96 : ! species morphology
97 : !------------------------------------------------------------------------
98 : subroutine aero_props_get(self, bin_ndx, species_ndx, list_ndx, density, hygro, &
99 : spectype, specmorph, refindex_sw, refindex_lw)
100 : import :: aerosol_properties, r8
101 : class(aerosol_properties), intent(in) :: self
102 : integer, intent(in) :: bin_ndx ! bin index
103 : integer, intent(in) :: species_ndx ! species index
104 : integer, optional, intent(in) :: list_ndx ! climate or a diagnostic list number
105 : real(r8), optional, intent(out) :: density ! density (kg/m3)
106 : real(r8), optional, intent(out) :: hygro ! hygroscopicity
107 : character(len=*), optional, intent(out) :: spectype ! species type
108 : character(len=*), optional, intent(out) :: specmorph ! species morphology
109 : complex(r8), pointer, optional, intent(out) :: refindex_sw(:) ! short wave species refractive indices
110 : complex(r8), pointer, optional, intent(out) :: refindex_lw(:) ! long wave species refractive indices
111 :
112 : end subroutine aero_props_get
113 :
114 : !------------------------------------------------------------------------
115 : ! returns optics type and table parameters
116 : !------------------------------------------------------------------------
117 : subroutine aero_optics_params(self, list_ndx, bin_ndx, opticstype, extpsw, abspsw, asmpsw, absplw, &
118 : refrtabsw, refitabsw, refrtablw, refitablw, ncoef, prefr, prefi, sw_hygro_ext_wtp, &
119 : sw_hygro_ssa_wtp, sw_hygro_asm_wtp, lw_hygro_ext_wtp, wgtpct, nwtp, &
120 : sw_hygro_coreshell_ext, sw_hygro_coreshell_ssa, sw_hygro_coreshell_asm, lw_hygro_coreshell_ext, &
121 : corefrac, bcdust, kap, relh, nfrac, nbcdust, nkap, nrelh )
122 :
123 : import :: aerosol_properties, r8
124 :
125 : class(aerosol_properties), intent(in) :: self
126 : integer, intent(in) :: bin_ndx ! bin index
127 : integer, intent(in) :: list_ndx ! rad climate/diags list
128 :
129 : character(len=*), optional, intent(out) :: opticstype
130 :
131 : ! refactive index table parameters
132 : real(r8), optional, pointer :: extpsw(:,:,:,:) ! short wave specific extinction
133 : real(r8), optional, pointer :: abspsw(:,:,:,:) ! short wave specific absorption
134 : real(r8), optional, pointer :: asmpsw(:,:,:,:) ! short wave asymmetry factor
135 : real(r8), optional, pointer :: absplw(:,:,:,:) ! long wave specific absorption
136 : real(r8), optional, pointer :: refrtabsw(:,:) ! table of short wave real refractive indices for aerosols
137 : real(r8), optional, pointer :: refitabsw(:,:) ! table of short wave imaginary refractive indices for aerosols
138 : real(r8), optional, pointer :: refrtablw(:,:) ! table of long wave real refractive indices for aerosols
139 : real(r8), optional, pointer :: refitablw(:,:) ! table of long wave imaginary refractive indices for aerosols
140 : integer, optional, intent(out) :: ncoef ! number of chebychev polynomials
141 : integer, optional, intent(out) :: prefr ! number of real refractive indices in table
142 : integer, optional, intent(out) :: prefi ! number of imaginary refractive indices in table
143 :
144 : ! hygrowghtpct table parameters
145 : real(r8), optional, pointer :: sw_hygro_ext_wtp(:,:) ! short wave extinction table
146 : real(r8), optional, pointer :: sw_hygro_ssa_wtp(:,:) ! short wave single-scatter albedo table
147 : real(r8), optional, pointer :: sw_hygro_asm_wtp(:,:) ! short wave asymmetry table
148 : real(r8), optional, pointer :: lw_hygro_ext_wtp(:,:) ! long wave absorption table
149 : real(r8), optional, pointer :: wgtpct(:) ! weight precent of H2SO4/H2O solution
150 : integer, optional, intent(out) :: nwtp ! number of weight precent values
151 :
152 : ! hygrocoreshell table parameters
153 : real(r8), optional, pointer :: sw_hygro_coreshell_ext(:,:,:,:,:) ! short wave extinction table
154 : real(r8), optional, pointer :: sw_hygro_coreshell_ssa(:,:,:,:,:) ! short wave single-scatter albedo table
155 : real(r8), optional, pointer :: sw_hygro_coreshell_asm(:,:,:,:,:) ! short wave asymmetry table
156 : real(r8), optional, pointer :: lw_hygro_coreshell_ext(:,:,:,:,:) ! long wave absorption table
157 : real(r8), optional, pointer :: corefrac(:) ! core fraction dimension values
158 : real(r8), optional, pointer :: bcdust(:) ! bc/(bc + dust) fraction dimension values
159 : real(r8), optional, pointer :: kap(:) ! hygroscopicity dimension values
160 : real(r8), optional, pointer :: relh(:) ! relative humidity dimension values
161 : integer, optional, intent(out) :: nfrac ! core fraction dimension size
162 : integer, optional, intent(out) :: nbcdust ! bc/(bc + dust) fraction dimension size
163 : integer, optional, intent(out) :: nkap ! hygroscopicity dimension size
164 : integer, optional, intent(out) :: nrelh ! relative humidity dimension size
165 :
166 : end subroutine aero_optics_params
167 :
168 : !------------------------------------------------------------------------
169 : ! returns species type
170 : !------------------------------------------------------------------------
171 : subroutine aero_species_type(self, bin_ndx, species_ndx, spectype)
172 : import :: aerosol_properties
173 : class(aerosol_properties), intent(in) :: self
174 : integer, intent(in) :: bin_ndx ! bin number
175 : integer, intent(in) :: species_ndx ! species number
176 : character(len=*), intent(out) :: spectype ! species type
177 :
178 : end subroutine aero_species_type
179 :
180 : !------------------------------------------------------------------------
181 : ! returns mass and number activation fractions
182 : !------------------------------------------------------------------------
183 : subroutine aero_actfracs(self, bin_ndx, smc, smax, fn, fm )
184 : import :: aerosol_properties, r8
185 : class(aerosol_properties), intent(in) :: self
186 : integer, intent(in) :: bin_ndx ! bin index
187 : real(r8),intent(in) :: smc ! critical supersaturation for particles of bin radius
188 : real(r8),intent(in) :: smax ! maximum supersaturation for multiple competing aerosols
189 : real(r8),intent(out) :: fn ! activation fraction for aerosol number
190 : real(r8),intent(out) :: fm ! activation fraction for aerosol mass
191 :
192 : end subroutine aero_actfracs
193 :
194 : !------------------------------------------------------------------------
195 : ! returns constituents names of aerosol number mixing ratios
196 : !------------------------------------------------------------------------
197 : subroutine aero_num_names(self, bin_ndx, name_a, name_c)
198 : import :: aerosol_properties
199 : class(aerosol_properties), intent(in) :: self
200 : integer, intent(in) :: bin_ndx ! bin number
201 : character(len=*), intent(out) :: name_a ! constituent name of ambient aerosol number dens
202 : character(len=*), intent(out) :: name_c ! constituent name of cloud-borne aerosol number dens
203 : end subroutine aero_num_names
204 :
205 : !------------------------------------------------------------------------
206 : ! returns constituents names of aerosol mass mixing ratios
207 : !------------------------------------------------------------------------
208 : subroutine aero_mmr_names(self, bin_ndx, species_ndx, name_a, name_c)
209 : import :: aerosol_properties
210 : class(aerosol_properties), intent(in) :: self
211 : integer, intent(in) :: bin_ndx ! bin number
212 : integer, intent(in) :: species_ndx ! species number
213 : character(len=*), intent(out) :: name_a ! constituent name of ambient aerosol MMR
214 : character(len=*), intent(out) :: name_c ! constituent name of cloud-borne aerosol MMR
215 : end subroutine aero_mmr_names
216 :
217 : !------------------------------------------------------------------------
218 : ! returns constituent name of ambient aerosol number mixing ratios
219 : !------------------------------------------------------------------------
220 : subroutine aero_amb_num_name(self, bin_ndx, name)
221 : import :: aerosol_properties
222 : class(aerosol_properties), intent(in) :: self
223 : integer, intent(in) :: bin_ndx ! bin number
224 : character(len=*), intent(out) :: name ! constituent name of ambient aerosol number dens
225 :
226 : end subroutine aero_amb_num_name
227 :
228 : !------------------------------------------------------------------------
229 : ! returns constituent name of ambient aerosol mass mixing ratios
230 : !------------------------------------------------------------------------
231 : subroutine aero_amb_mmr_name(self, bin_ndx, species_ndx, name)
232 : import :: aerosol_properties
233 : class(aerosol_properties), intent(in) :: self
234 : integer, intent(in) :: bin_ndx ! bin number
235 : integer, intent(in) :: species_ndx ! species number
236 : character(len=*), intent(out) :: name ! constituent name of ambient aerosol MMR
237 :
238 : end subroutine aero_amb_mmr_name
239 :
240 : !------------------------------------------------------------------------------
241 : ! returns radius^3 (m3) of a given bin number
242 : !------------------------------------------------------------------------------
243 : pure elemental real(r8) function aero_amcube(self, bin_ndx, volconc, numconc)
244 : import :: aerosol_properties, r8
245 :
246 : class(aerosol_properties), intent(in) :: self
247 : integer, intent(in) :: bin_ndx ! bin number
248 : real(r8), intent(in) :: volconc ! volume conc (m3/m3)
249 : real(r8), intent(in) :: numconc ! number conc (1/m3)
250 :
251 : end function aero_amcube
252 :
253 : !------------------------------------------------------------------------------
254 : ! returns TRUE if Ice Nucleation tendencies are applied to given aerosol bin number
255 : !------------------------------------------------------------------------------
256 : function aero_icenuc_updates_num(self, bin_ndx) result(res)
257 : import :: aerosol_properties
258 : class(aerosol_properties), intent(in) :: self
259 : integer, intent(in) :: bin_ndx ! bin number
260 :
261 : logical :: res
262 :
263 : end function aero_icenuc_updates_num
264 :
265 : !------------------------------------------------------------------------------
266 : ! returns TRUE if Ice Nucleation tendencies are applied to a given species within a bin
267 : !------------------------------------------------------------------------------
268 : function aero_icenuc_updates_mmr(self, bin_ndx, species_ndx) result(res)
269 : import :: aerosol_properties
270 : class(aerosol_properties), intent(in) :: self
271 : integer, intent(in) :: bin_ndx ! bin number
272 : integer, intent(in) :: species_ndx ! species number
273 :
274 : logical :: res
275 :
276 : end function aero_icenuc_updates_mmr
277 :
278 : !------------------------------------------------------------------------------
279 : ! apply max / min to number concentration
280 : !------------------------------------------------------------------------------
281 : subroutine aero_apply_num_limits( self, naerosol, vaerosol, istart, istop, m )
282 : import :: aerosol_properties, r8
283 : class(aerosol_properties), intent(in) :: self
284 : real(r8), intent(inout) :: naerosol(:) ! number conc (1/m3)
285 : real(r8), intent(in) :: vaerosol(:) ! volume conc (m3/m3)
286 : integer, intent(in) :: istart ! start column index (1 <= istart <= istop <= pcols)
287 : integer, intent(in) :: istop ! stop column index
288 : integer, intent(in) :: m ! mode or bin index
289 :
290 : end subroutine aero_apply_num_limits
291 :
292 : !------------------------------------------------------------------------------
293 : ! returns TRUE if species `spc_ndx` in aerosol subset `bin_ndx` contributes to
294 : ! the particles' ability to act as heterogeneous freezing nuclei
295 : !------------------------------------------------------------------------------
296 : function aero_hetfrz_species(self, bin_ndx, spc_ndx) result(res)
297 : import :: aerosol_properties
298 : class(aerosol_properties), intent(in) :: self
299 : integer, intent(in) :: bin_ndx ! bin number
300 : integer, intent(in) :: spc_ndx ! species number
301 :
302 : logical :: res
303 :
304 : end function aero_hetfrz_species
305 :
306 : !------------------------------------------------------------------------------
307 : ! returns minimum mass mean radius (meters)
308 : !------------------------------------------------------------------------------
309 : function aero_min_mass_mean_rad(self,bin_ndx,species_ndx) result(minrad)
310 : import :: aerosol_properties, r8
311 : class(aerosol_properties), intent(in) :: self
312 : integer, intent(in) :: bin_ndx ! bin number
313 : integer, intent(in) :: species_ndx ! species number
314 :
315 : real(r8) :: minrad ! meters
316 :
317 : end function aero_min_mass_mean_rad
318 :
319 : !------------------------------------------------------------------------------
320 : ! returns TRUE if soluble
321 : !------------------------------------------------------------------------------
322 : logical function aero_soluble(self,bin_ndx)
323 : import :: aerosol_properties
324 : class(aerosol_properties), intent(in) :: self
325 : integer, intent(in) :: bin_ndx ! bin number
326 :
327 : end function aero_soluble
328 :
329 : !------------------------------------------------------------------------------
330 : ! returns the total number of bins for a given radiation list index
331 : !------------------------------------------------------------------------------
332 : function aero_nbins_rlist(self, list_ndx) result(res)
333 : import :: aerosol_properties
334 : class(aerosol_properties), intent(in) :: self
335 : integer, intent(in) :: list_ndx ! radiation list number
336 :
337 : integer :: res
338 :
339 : end function aero_nbins_rlist
340 :
341 : !------------------------------------------------------------------------------
342 : ! returns number of species in a bin for a given radiation list index
343 : !------------------------------------------------------------------------------
344 : function aero_nspecies_rlist(self, list_ndx, bin_ndx) result(res)
345 : import :: aerosol_properties
346 : class(aerosol_properties), intent(in) :: self
347 : integer, intent(in) :: list_ndx ! radiation list number
348 : integer, intent(in) :: bin_ndx ! bin number
349 :
350 : integer :: res
351 :
352 : end function aero_nspecies_rlist
353 :
354 : !------------------------------------------------------------------------------
355 : ! returns the natural log of geometric standard deviation of the number
356 : ! distribution for radiation list number and aerosol bin
357 : !------------------------------------------------------------------------------
358 : function aero_alogsig_rlist(self, list_ndx, bin_ndx) result(res)
359 : import :: aerosol_properties, r8
360 : class(aerosol_properties), intent(in) :: self
361 : integer, intent(in) :: list_ndx ! radiation list number
362 : integer, intent(in) :: bin_ndx ! bin number
363 :
364 : real(r8) :: res
365 :
366 : end function aero_alogsig_rlist
367 :
368 : !------------------------------------------------------------------------------
369 : ! returns name for a given radiation list number and aerosol bin
370 : !------------------------------------------------------------------------------
371 : function aero_bin_name(self, list_ndx, bin_ndx) result(name)
372 : import :: aerosol_properties, r8
373 : class(aerosol_properties), intent(in) :: self
374 : integer, intent(in) :: list_ndx ! radiation list number
375 : integer, intent(in) :: bin_ndx ! bin number
376 :
377 : character(len=32) name
378 :
379 : end function aero_bin_name
380 :
381 : end interface
382 :
383 : contains
384 :
385 : !------------------------------------------------------------------------------
386 : ! object initializer
387 : !------------------------------------------------------------------------------
388 4608 : subroutine aero_props_init(self, nbin, ncnst, nspec, nmasses, alogsig, f1,f2, ierr )
389 : class(aerosol_properties), intent(inout) :: self
390 : integer, intent(in) :: nbin ! number of bins
391 : integer, intent(in) :: ncnst ! total number of constituents
392 : integer, intent(in) :: nspec(nbin) ! number of species in each bin
393 : integer, intent(in) :: nmasses(nbin) ! number of masses in each bin
394 : real(r8),intent(in) :: alogsig(nbin) ! natural log of the standard deviation (sigma) of the aerosol bins
395 : real(r8),intent(in) :: f1(nbin) ! eq 28 Abdul-Razzak et al 1998
396 : real(r8),intent(in) :: f2(nbin) ! eq 29 Abdul-Razzak et al 1998
397 : integer,intent(out) :: ierr
398 :
399 : integer :: imas,ibin,indx
400 : character(len=*),parameter :: prefix = 'aerosol_properties::aero_props_init: '
401 :
402 : real(r8), parameter :: spechygro_so4 = 0.507_r8 ! Sulfate hygroscopicity
403 : real(r8), parameter :: spechygro_soa = 0.14_r8 ! SOA hygroscopicity
404 : real(r8), parameter :: spechygro_pom = 0.1_r8 ! POM hygroscopicity
405 :
406 4608 : ierr = 0
407 :
408 13824 : allocate(self%nspecies_(nbin),stat=ierr)
409 4608 : if( ierr /= 0 ) then
410 : return
411 : end if
412 9216 : allocate(self%nmasses_(nbin),stat=ierr)
413 4608 : if( ierr /= 0 ) then
414 : return
415 : end if
416 13824 : allocate(self%alogsig_(nbin),stat=ierr)
417 4608 : if( ierr /= 0 ) then
418 : return
419 : end if
420 9216 : allocate(self%f1_(nbin),stat=ierr)
421 4608 : if( ierr /= 0 ) then
422 : return
423 : end if
424 9216 : allocate(self%f2_(nbin),stat=ierr)
425 4608 : if( ierr /= 0 ) then
426 : return
427 : end if
428 :
429 36864 : allocate( self%indexer_(nbin,0:maxval(nmasses)),stat=ierr )
430 4608 : if( ierr /= 0 ) then
431 : return
432 : end if
433 :
434 : ! Local indexing compresses the mode and number/mass indices into one index.
435 : ! This indexing is used by the pointer arrays used to reference state and pbuf
436 : ! fields. We add number = 0, total mass = 1 (if available), and mass from each
437 : ! constituency into mm.
438 :
439 165888 : self%indexer_ = -1
440 : indx = 0
441 :
442 23040 : do ibin=1,nbin
443 110592 : do imas = 0,nmasses(ibin)
444 87552 : indx = indx+1
445 105984 : self%indexer_(ibin,imas) = indx
446 : end do
447 : end do
448 :
449 4608 : self%nbins_ = nbin
450 4608 : self%ncnst_tot_ = ncnst
451 23040 : self%nmasses_(:) = nmasses(:)
452 23040 : self%nspecies_(:) = nspec(:)
453 23040 : self%alogsig_(:) = alogsig(:)
454 23040 : self%f1_(:) = f1(:)
455 23040 : self%f2_(:) = f2(:)
456 :
457 4608 : self%soa_equivso4_factor_ = spechygro_soa/spechygro_so4
458 4608 : self%pom_equivso4_factor_ = spechygro_pom/spechygro_so4
459 :
460 : end subroutine aero_props_init
461 :
462 : !------------------------------------------------------------------------------
463 : ! Object clean
464 : !------------------------------------------------------------------------------
465 1536 : subroutine aero_props_final(self)
466 : class(aerosol_properties), intent(inout) :: self
467 :
468 1536 : if (allocated(self%nspecies_)) then
469 1536 : deallocate(self%nspecies_)
470 : end if
471 1536 : if (allocated(self%nmasses_)) then
472 1536 : deallocate(self%nmasses_)
473 : end if
474 1536 : if (allocated(self%indexer_)) then
475 1536 : deallocate(self%indexer_)
476 : endif
477 1536 : if (allocated(self%alogsig_)) then
478 1536 : deallocate(self%alogsig_)
479 : endif
480 1536 : if (allocated(self%f1_)) then
481 1536 : deallocate(self%f1_)
482 : endif
483 1536 : if (allocated(self%f2_)) then
484 1536 : deallocate(self%f2_)
485 : endif
486 :
487 1536 : self%nbins_ = 0
488 1536 : self%ncnst_tot_ = 0
489 :
490 1536 : end subroutine aero_props_final
491 :
492 : !------------------------------------------------------------------------------
493 : ! returns number of species in a bin
494 : !------------------------------------------------------------------------------
495 481333724 : pure function nspecies_per_bin(self,bin_ndx) result(val)
496 : class(aerosol_properties), intent(in) :: self
497 : integer, intent(in) :: bin_ndx ! bin number
498 : integer :: val
499 :
500 481333724 : val = self%nspecies_(bin_ndx)
501 481333724 : end function nspecies_per_bin
502 :
503 : !------------------------------------------------------------------------------
504 : ! returns number of species for all bins
505 : !------------------------------------------------------------------------------
506 1536 : pure function nspecies_all_bins(self) result(arr)
507 : class(aerosol_properties), intent(in) :: self
508 : integer :: arr(self%nbins_)
509 :
510 7680 : arr(:) = self%nspecies_(:)
511 :
512 1536 : end function nspecies_all_bins
513 :
514 : !------------------------------------------------------------------------------
515 : ! returns number of species masses in a given bin number
516 : !------------------------------------------------------------------------------
517 142625432 : pure function n_masses_per_bin(self,bin_ndx) result(val)
518 : class(aerosol_properties), intent(in) :: self
519 : integer, intent(in) :: bin_ndx ! bin number
520 : integer :: val
521 :
522 142625432 : val = self%nmasses_(bin_ndx)
523 142625432 : end function n_masses_per_bin
524 :
525 : !------------------------------------------------------------------------------
526 : ! returns an array of number of species masses for all bins
527 : !------------------------------------------------------------------------------
528 1536 : pure function n_masses_all_bins(self) result(arr)
529 : class(aerosol_properties), intent(in) :: self
530 : integer :: arr(self%nbins_)
531 :
532 7680 : arr(:) = self%nmasses_(:)
533 1536 : end function n_masses_all_bins
534 :
535 : !------------------------------------------------------------------------------
536 : ! returns a single index for given bin and species
537 : !------------------------------------------------------------------------------
538 804069846 : pure integer function indexer(self,bin_ndx,species_ndx)
539 : class(aerosol_properties), intent(in) :: self
540 : integer, intent(in) :: bin_ndx ! bin number
541 : integer, intent(in) :: species_ndx ! species number
542 :
543 804069846 : indexer = self%indexer_(bin_ndx,species_ndx)
544 804069846 : end function indexer
545 :
546 : !------------------------------------------------------------------------------
547 : ! returns the total number of bins
548 : !------------------------------------------------------------------------------
549 181849596 : pure function nbins_0list(self) result(nbins)
550 : class(aerosol_properties), intent(in) :: self
551 : integer :: nbins
552 :
553 181849596 : nbins = self%nbins_
554 181849596 : end function nbins_0list
555 :
556 : !------------------------------------------------------------------------------
557 : ! returns number of constituents (or elements) totaled across all bins
558 : !------------------------------------------------------------------------------
559 179544 : pure integer function ncnst_tot(self)
560 : class(aerosol_properties), intent(in) :: self
561 :
562 179544 : ncnst_tot = self%ncnst_tot_
563 179544 : end function ncnst_tot
564 :
565 : !------------------------------------------------------------------------------
566 : ! returns the natural log of geometric standard deviation of the number distribution for aerosol bin
567 : !------------------------------------------------------------------------------
568 127187320 : pure real(r8) function alogsig_0list(self, bin_ndx)
569 : class(aerosol_properties), intent(in) :: self
570 : integer, intent(in) :: bin_ndx ! bin number
571 :
572 127187320 : alogsig_0list = self%alogsig_(bin_ndx)
573 127187320 : end function alogsig_0list
574 :
575 : !------------------------------------------------------------------------------
576 : ! returns maximum supersaturation
577 : !------------------------------------------------------------------------------
578 13897850 : function maxsat(self, zeta,eta,smc) result(smax)
579 :
580 : !-------------------------------------------------------------------------
581 : ! Calculates maximum supersaturation for multiple competing aerosols.
582 : !
583 : ! Abdul-Razzak and Ghan, A parameterization of aerosol activation.
584 : ! 2. Multiple aerosol types. J. Geophys. Res., 105, 6837-6844., 2000
585 : !-------------------------------------------------------------------------
586 :
587 : class(aerosol_properties), intent(in) :: self
588 : real(r8), intent(in) :: zeta(self%nbins_) ! Abdul-Razzak and Ghan eq 10
589 : real(r8), intent(in) :: eta(self%nbins_) ! Abdul-Razzak and Ghan eq 11
590 : real(r8), intent(in) :: smc(self%nbins_) ! critical supersaturation
591 :
592 : real(r8) :: smax ! maximum supersaturation
593 :
594 : integer :: m
595 : integer :: nbins
596 : real(r8) :: sum, g1, g2, g1sqrt, g2sqrt
597 :
598 : real(r8), parameter :: small_maxsat = 1.e-20_r8 ! for weak forcing
599 : real(r8), parameter :: large_maxsat = 1.e20_r8 ! for small eta
600 :
601 13897850 : smax=0.0_r8
602 13897850 : nbins = self%nbins_
603 :
604 13897850 : check_loop: do m=1,nbins
605 13897850 : if((zeta(m) > 1.e5_r8*eta(m)) .or. (smc(m)*smc(m) > 1.e5_r8*eta(m))) then
606 : ! weak forcing -- essentially none activated
607 0 : smax=small_maxsat
608 : else
609 : ! significant activation of this mode -- calc activation all modes
610 : exit check_loop
611 : endif
612 : ! No significant activation in any mode. Do nothing.
613 13897850 : if (m == nbins) return
614 : enddo check_loop
615 :
616 : sum=0.0_r8
617 :
618 69489250 : do m=1,nbins
619 69489250 : if(eta(m) > 1.e-20_r8)then
620 : ! from Abdul-Razzak and Ghan 2000
621 55591400 : g1=zeta(m)/eta(m)
622 55591400 : g1sqrt=sqrt(g1)
623 55591400 : g1=g1sqrt*g1
624 55591400 : g2=smc(m)/sqrt(eta(m)+3._r8*zeta(m))
625 55591400 : g2sqrt=sqrt(g2)
626 55591400 : g2=g2sqrt*g2
627 55591400 : sum=sum+(self%f1_(m)*g1+self%f2_(m)*g2)/(smc(m)*smc(m))
628 : else
629 : sum=large_maxsat
630 : endif
631 : enddo
632 :
633 13897850 : smax=1._r8/sqrt(sum)
634 :
635 13897850 : end function maxsat
636 :
637 : !------------------------------------------------------------------------------
638 : ! returns the ratio of SOA Hygroscopicity / Sulfate Hygroscopicity
639 : !------------------------------------------------------------------------------
640 352944 : pure real(r8) function soa_equivso4_factor(self)
641 : class(aerosol_properties), intent(in) :: self
642 :
643 352944 : soa_equivso4_factor = self%soa_equivso4_factor_
644 :
645 352944 : end function soa_equivso4_factor
646 :
647 : !------------------------------------------------------------------------------
648 : ! returns the ratio of POM Hygroscopicity / Sulfate Hygroscopicity
649 : !------------------------------------------------------------------------------
650 529416 : pure real(r8) function pom_equivso4_factor(self)
651 : class(aerosol_properties), intent(in) :: self
652 :
653 529416 : pom_equivso4_factor = self%pom_equivso4_factor_
654 :
655 529416 : end function pom_equivso4_factor
656 :
657 0 : end module aerosol_properties_mod
|