updated top-level README and version_decl for V4.5 (#1847)
[WRF.git] / phys / module_data_cam_mam_aero.F
blob61d2934734de809b63ac987cc736b0817213cbac
1 ! module_data_cam_mam_aero.F
2 ! adapted from cam3 modal_aero_data.F90 by r.c.easter, june 2010
3 ! Updated to CESM1.0.3 (CAM5.1.01) by Balwinder.Singh@pnnl.gov
4 !--------------------------------------------------------------
5 #define WRF_PORT
6 #if ( WRF_CHEM == 1 )
7 #       include "../chem/MODAL_AERO_CPP_DEFINES.h"
8 #else
9 #       define MODAL_AERO
10 #       define MODAL_AERO_3MODE
11 #endif
12       module modal_aero_data
14 !--------------------------------------------------------------
15 ! ... Basic aerosol mode parameters and arrays
16 !--------------------------------------------------------------
17       use shr_kind_mod,  only: r8 => shr_kind_r8
18 #ifndef WRF_PORT
19       use constituents,  only: pcnst
20 #else
21       use module_cam_support, only : pcnst => pcnst_runtime
22 #endif
23       use radconstants,  only: nswbands, nlwbands
25       implicit none
26       save
28      integer, parameter ::  maxd_aspectype = 14
29     ! aerosol mode definitions
30     !
31 #if ( defined MODAL_AERO_7MODE )
32     integer, parameter :: ntot_amode = 7
33 #elif ( defined MODAL_AERO_3MODE )
34     integer, parameter :: ntot_amode = 3
35 #endif
37     !
38     ! definitions for aerosol chemical components
39     !
40   integer, parameter ::  ntot_aspectype = 8
41   character(len=*),parameter ::  specname_amode(ntot_aspectype) = (/ 'sulfate   ', 'ammonium  ', 'nitrate   ', &
42        'p-organic ', 's-organic ', 'black-c   ', &
43        'seasalt   ', 'dust      ' /)
44     ! set specdens_amode from physprop files via rad_cnst_get_aer_props
45     !specdens_amode(:ntot_aspectype) = (/1770.0,1770.0,1770.0, 1000.0, 1000.0, 1700.0,1900.0,2600.0 /)
47     ! rce - 06-aug-2007 - changed specmw for almost everything to match mozart
48 #if ( defined MODAL_AERO_7MODE )
49 #ifndef WRF_PORT  
50     real(r8), parameter :: specmw_amode(ntot_aspectype)   = (/  96.0,  18.0,  62.0,   12.0,   12.0,   12.0,  58.5, 135.0 /)
51 #else
52     real(r8) :: specmw_amode(ntot_aspectype)   = (/  96.0,  18.0,  62.0,   12.0,   12.0,   12.0,  58.5, 135.0 /)
53 #endif    
54 #elif ( defined MODAL_AERO_3MODE )
55 #ifndef WRF_PORT
56     real(r8), parameter :: specmw_amode(ntot_aspectype)   = (/ 115.0, 115.0,  62.0,   12.0,   12.0,   12.0,  58.5, 135.0 /)
57 #else
58     !Balwinder.Singh@pnnl.gov: For prescribed aerosols, these values are modified in the aerosol initialization subroutine
59     real(r8) :: specmw_amode(ntot_aspectype)   = (/ 115.0, 115.0,  62.0,   12.0,   12.0,   12.0,  58.5, 135.0 /)
60 #endif
61 #endif
64     !   input modename_amode, nspec_amode
65 #if ( defined MODAL_AERO_7MODE )
66     character(len=*), parameter :: modename_amode(ntot_amode) = (/'accum           ', &
67          'aitken          ', &
68          'primary carbon  ', &
69          'fine seasalt    ', &
70          'fine dust       ', &
71          'coarse seasalt  ', &
72          'coarse dust     '/)
73 #elif ( defined MODAL_AERO_3MODE )
74     character(len=*), parameter :: modename_amode(ntot_amode) = (/'accum           ', &
75          'aitken          ', &
76          'coarse          '/)
77 #endif
79 #if ( defined MODAL_AERO_7MODE )
80 #ifndef WRF_PORT
81     !Balwinder.Singh@pnnl.gov: For prescribed aerosols, these values are modified in the aerosol initialization subroutine
82     integer, parameter :: nspec_amode(ntot_amode)           = (/ 6, 4, 2, 3, 3, 3, 3 /)  ! SS
83 #else
84     integer :: nspec_amode(ntot_amode)           = (/ 6, 4, 2, 3, 3, 3, 3 /)  ! SS
85 #endif
86 #elif ( defined MODAL_AERO_3MODE )
87 #ifndef WRF_PORT
88     !Balwinder.Singh@pnnl.gov: For prescribed aerosols, these values are modified in the aerosol initialization subroutine
89     integer, parameter :: nspec_amode(ntot_amode)           = (/ 6, 3, 3 /)
90 #else
91     integer :: nspec_amode(ntot_amode) = (/ 6, 3, 3 /)
92 #endif
93 #endif
94     integer, parameter :: nspec_amode_max = 6
95     !   input mprognum_amode, mdiagnum_amode, mprogsfc_amode, mcalcwater_amode
96 #if ( defined MODAL_AERO_7MODE )
97     integer, parameter ::     mprognum_amode(ntot_amode)   = (/ 1, 1, 1, 1, 1, 1, 1/)
98     integer, parameter ::     mdiagnum_amode(ntot_amode)   = (/ 0, 0, 0, 0, 0, 0, 0/)
99     integer, parameter ::     mprogsfc_amode(ntot_amode)   = (/ 0, 0, 0, 0, 0, 0, 0/)
100     integer, parameter ::     mcalcwater_amode(ntot_amode) = (/ 1, 1, 1, 1, 1, 1, 1/)
101 #elif ( defined MODAL_AERO_3MODE )
102     integer, parameter ::     mprognum_amode(ntot_amode)   = (/ 1, 1, 1/)
103     integer, parameter ::     mdiagnum_amode(ntot_amode)   = (/ 0, 0, 0/)
104     integer, parameter ::     mprogsfc_amode(ntot_amode)   = (/ 0, 0, 0/)
105     integer, parameter ::     mcalcwater_amode(ntot_amode) = (/ 0, 0, 0/)
106 #endif
108     !   input dgnum_amode, dgnumlo_amode, dgnumhi_amode (units = m)
109 #if ( defined MODAL_AERO_7MODE )
110     real(r8), parameter :: dgnum_amode(ntot_amode)   = (/ 0.1100e-6, 0.0260e-6, 0.050e-6, 0.200e-6, 0.100e-6, 2.000e-6, 1.000e-6 /)
111     real(r8), parameter :: dgnumlo_amode(ntot_amode) = (/ 0.0535e-6, 0.0087e-6, 0.010e-6, 0.050e-6, 0.050e-6, 1.000e-6, 0.500e-6 /)
112     real(r8), parameter :: dgnumhi_amode(ntot_amode) = (/ 0.4400e-6, 0.0520e-6, 0.100e-6, 1.000e-6, 0.500e-6, 4.000e-6, 2.000e-6 /)
113 #elif ( defined MODAL_AERO_3MODE )
114     real(r8), parameter ::     dgnum_amode(ntot_amode)   = (/ 0.1100e-6, 0.0260e-6, 2.000e-6 /)
115     real(r8), parameter ::     dgnumlo_amode(ntot_amode) = (/ 0.0535e-6, 0.0087e-6, 1.000e-6 /)
116     real(r8), parameter ::     dgnumhi_amode(ntot_amode) = (/ 0.4400e-6, 0.0520e-6, 4.000e-6 /)
117 #endif
119     !   input sigmag_amode, sigmaglo_amode, sigmaghi_amode
120 #if ( defined MODAL_AERO_7MODE )
121     real(r8), parameter ::     sigmag_amode(ntot_amode)   = (/ 1.800, 1.600, 1.600, 2.000, 1.800, 2.000, 1.800 /)
122 #elif ( defined MODAL_AERO_3MODE )
123     real(r8), parameter ::     sigmag_amode(ntot_amode)   = (/ 1.800, 1.600, 1.800 /)
124 #endif
126     !   input crystalization and deliquescence points
127 #if ( defined MODAL_AERO_7MODE )
128     real(r8), parameter ::     rhcrystal_amode(ntot_amode)  = (/ 0.350, 0.350, 0.350, 0.350, 0.350, 0.350, 0.350 /)
129     real(r8), parameter ::     rhdeliques_amode(ntot_amode) = (/ 0.800, 0.800, 0.800, 0.800, 0.800, 0.800, 0.800 /)
130 #elif ( defined MODAL_AERO_3MODE )
131     real(r8), parameter ::     rhcrystal_amode(ntot_amode)  = (/ 0.350, 0.350, 0.350 /)
132     real(r8), parameter ::     rhdeliques_amode(ntot_amode) = (/ 0.800, 0.800, 0.800 /)
133 #endif
136     integer :: msectional = -1
139       integer                                               &   !
140           lspectype_amode( maxd_aspectype, ntot_amode ),    &   !
141           lmassptr_amode( maxd_aspectype, ntot_amode ),     &   !
142           lmassptrcw_amode( maxd_aspectype, ntot_amode ),   &   !
143           numptr_amode( ntot_amode ),                       &   !
144           numptrcw_amode( ntot_amode )
147       real(r8) ::                                 &   !
148           alnsg_amode( ntot_amode ),              &   !
149           voltonumb_amode( ntot_amode ),          &   !
150           voltonumblo_amode( ntot_amode ),        &   !
151           voltonumbhi_amode( ntot_amode ),        &   !
152           alnv2n_amode( ntot_amode ),             &   !
153           alnv2nlo_amode( ntot_amode ),           &   !
154           alnv2nhi_amode( ntot_amode ),           &   !
155           specdens_amode( maxd_aspectype ),       &   !
156           spechygro( maxd_aspectype )
159       complex                                     &   !
160           specrefndxsw( nswbands, maxd_aspectype ),           &   !
161           specrefndxlw( nlwbands, maxd_aspectype )
163 #ifndef WRF_PORT
164       character(len=16) :: cnst_name_cw( pcnst )
165 #else
166       character(len=16), allocatable :: cnst_name_cw( : )
167 #endif
169       character(len=8) :: aodvisname(ntot_amode ),       &
170                           ssavisname(ntot_amode )
171       character(len=48) :: aodvislongname(ntot_amode ),  &
172                            ssavislongname(ntot_amode )
174       character(len=8) :: fnactname(ntot_amode ),   &
175                           fmactname(ntot_amode ),   &
176                           nactname(ntot_amode )
177       character(len=48) :: fnactlongname(ntot_amode ),   &
178                            fmactlongname(ntot_amode ),   &
179                            nactlongname(ntot_amode )
181       integer                                       &   !
182           lptr_so4_a_amode(ntot_amode),  lptr_so4_cw_amode(ntot_amode), &   !
183           lptr_msa_a_amode(ntot_amode),  lptr_msa_cw_amode(ntot_amode), &   !
184           lptr_nh4_a_amode(ntot_amode),  lptr_nh4_cw_amode(ntot_amode), &   !
185           lptr_no3_a_amode(ntot_amode),  lptr_no3_cw_amode(ntot_amode), &   !
186           lptr_pom_a_amode(ntot_amode),  lptr_pom_cw_amode(ntot_amode), &   !
187           lptr_soa_a_amode(ntot_amode),  lptr_soa_cw_amode(ntot_amode), &   !
188           lptr_bc_a_amode(ntot_amode),   lptr_bc_cw_amode(ntot_amode),  &   !
189           lptr_nacl_a_amode(ntot_amode), lptr_nacl_cw_amode(ntot_amode),&   !
190           lptr_dust_a_amode(ntot_amode), lptr_dust_cw_amode(ntot_amode),&   !
191           modeptr_accum,  modeptr_aitken,                               &   !
192           modeptr_ufine,  modeptr_coarse,                               &   !
193           modeptr_pcarbon,                                              &   !
194           modeptr_finedust,  modeptr_fineseas,                          &   !
195           modeptr_coardust,  modeptr_coarseas
197       real(r8) ::             &
198           specmw_so4_amode,     specdens_so4_amode,       &
199           specmw_nh4_amode,     specdens_nh4_amode,       &
200           specmw_no3_amode,     specdens_no3_amode,       &
201           specmw_pom_amode,     specdens_pom_amode,       &
202           specmw_soa_amode,     specdens_soa_amode,       &
203           specmw_bc_amode,      specdens_bc_amode,        &
204           specmw_dust_amode,    specdens_dust_amode,      &
205           specmw_seasalt_amode, specdens_seasalt_amode
206 #ifndef WRF_PORT
207       integer species_class(pcnst)      ! indicates species class (
208                                 !     cldphysics, aerosol, gas )
209 #else
210       integer, allocatable:: species_class(:)   ! indicates species class (
211                                 !     cldphysics, aerosol, gas )
212 #endif
214         integer     spec_class_undefined
215         parameter ( spec_class_undefined = 0 )
216         integer     spec_class_cldphysics
217         parameter ( spec_class_cldphysics = 1 )
218         integer     spec_class_aerosol
219         parameter ( spec_class_aerosol = 2 )
220         integer     spec_class_gas
221         parameter ( spec_class_gas = 3 )
222         integer     spec_class_other
223         parameter ( spec_class_other = 4 )
226 !   threshold for reporting negatives from subr qneg3
227 #ifndef WRF_PORT
228       real(r8) :: qneg3_worst_thresh_amode(pcnst)   
229 #else
230       real(r8), allocatable :: qneg3_worst_thresh_amode(:)
231 #endif
233 #ifdef WRF_PORT
234       !Following variables are defined to assist CAMMGMP decoupled from
235       !CAM MAM package. 
236       character(len=16), allocatable :: cnst_name_cw_mp(:)
238       integer  :: msectional_mp = -1
239       integer  :: modeptr_accum_mp    
240       integer  :: modeptr_coarse_mp   
241       integer  :: modeptr_coardust_mp !BSINGH - declared for MAM7 complaince
242       integer  :: modeptr_aitken_mp   
243       integer  :: ntot_amode_mp = ntot_amode
245       integer  :: numptrcw_amode_mp(ntot_amode) 
246       integer  :: lptr_dust_a_amode_mp(ntot_amode)
247       integer  :: lptr_nacl_a_amode_mp(ntot_amode)
248       integer  :: numptr_amode_mp(ntot_amode)    
249 #if ( defined MODAL_AERO_7MODE )
250       integer  :: nspec_amode_mp(ntot_amode)  = (/ 6, 4, 2, 3, 3, 3, 3 /)  ! SS
251 #elif ( defined MODAL_AERO_3MODE )
252       integer  :: nspec_amode_mp(ntot_amode)  = (/ 6, 3, 3 /)
253 #endif    
254       integer  :: lmassptr_amode_mp(maxd_aspectype, ntot_amode) 
255       integer  :: lspectype_amode_mp(maxd_aspectype, ntot_amode)       
256       integer  :: lmassptrcw_amode_mp(maxd_aspectype, ntot_amode)
257       
258       real(r8) :: voltonumb_amode_mp( ntot_amode )
259       real(r8) :: alnsg_amode_mp( ntot_amode )
260       real(r8) :: voltonumbhi_amode_mp(ntot_amode)
261       real(r8) :: voltonumblo_amode_mp(ntot_amode)
262       real(r8) :: sigmag_amode_mp(ntot_amode)  = sigmag_amode(1:ntot_amode)
263       real(r8) :: dgnum_amode_mp(ntot_amode)   = dgnum_amode(1:ntot_amode)
264       real(r8) :: dgnumlo_amode_mp(ntot_amode) = dgnumlo_amode(1:ntot_amode)
265       real(r8) :: dgnumhi_amode_mp(ntot_amode) = dgnumhi_amode(ntot_amode) 
266       real(r8) :: specdens_amode_mp( maxd_aspectype )
267       real(r8) :: specmw_amode_mp(ntot_aspectype)  
268       real(r8) :: spechygro_mp( maxd_aspectype )
269 #endif
273 #ifndef WRF_PORT
274       integer, private :: qqcw(pcnst)=-1 ! Remaps modal_aero indices into pbuf
275       contains
277         subroutine qqcw_set_ptr(index, iptr)
278           use abortutils, only : endrun
279           use time_manager, only : is_first_step
280           use phys_buffer, only : pbuf
282           integer, intent(in) :: index, iptr
284           if(index>0 .and. index <= pcnst ) then
285              qqcw(index)=iptr
286           else
287              call endrun('attempting to set qqcw pointer already defined')
288           end if
289         end subroutine qqcw_set_ptr
291         function qqcw_get_field(index, lchnk, errorhandle)
292           use abortutils, only : endrun
293           use phys_buffer, only : pbuf
294           integer, intent(in) :: index, lchnk
295           real(r8), pointer :: qqcw_get_field(:,:)
296           logical, optional :: errorhandle
298           if(index>0 .and. index <= pcnst .and. qqcw(index)>0) then
299              qqcw_get_field => pbuf(qqcw(index))%fld_ptr(1,:,:,lchnk,1)
300           else if(.not. present(errorhandle)) then
301              call endrun('attempt to access undefined qqcw')
302           else
303              nullify(qqcw_get_field)
304           end if
306         end function qqcw_get_field
307 #endif
308       end module modal_aero_data
310 !----------------------------------------------------------------
312 !   maxd_aspectype = maximum allowable number of chemical species
313 !       in each aerosol mode
315 !   ntot_amode = number of aerosol modes
316 !   ( ntot_amode_gchm = number of aerosol modes in gchm
317 !     ntot_amode_ccm2 = number of aerosol modes to be made known to ccm2
318 !       These are temporary until multi-mode activation scavenging is going.
319 !       Until then, ntot_amode is set to either ntot_amode_gchm or
320 !       ntot_amode_ccm2 depending on which code is active )
322 !   msectional - if positive, moving-center sectional code is utilized,
323 !       and each mode is actually a section.
324 !   msectional_concinit - if positive, special code is used to initialize
325 !       the mixing ratios of all the sections.
327 !   nspec_amode(m) = number of chemical species in aerosol mode m
328 !   nspec_amode_ccm2(m) = . . .  while in ccm2 code
329 !   nspec_amode_gchm(m) = . . .  while in gchm code
330 !   nspec_amode_nontracer(m) = number of "non-tracer" chemical
331 !       species while in gchm code
332 !   lspectype_amode(l,m) = species type/i.d. for chemical species l
333 !       in aerosol mode m.  (1=sulfate, others to be defined)
334 !   lmassptr_amode(l,m) = gchm r-array index for the mixing ratio
335 !       (moles-x/mole-air) for chemical species l in aerosol mode m
336 !       that is in clear air or interstitial air (but not in cloud water)
337 !   lmassptrcw_amode(l,m) = gchm r-array index for the mixing ratio
338 !       (moles-x/mole-air) for chemical species l in aerosol mode m
339 !       that is currently bound/dissolved in cloud water
340 !   lwaterptr_amode(m) = gchm r-array index for the mixing ratio
341 !       (moles-water/mole-air) for water associated with aerosol mode m
342 !       that is in clear air or interstitial air
343 !   lkohlercptr_amode(m) = gchm r-array index for the kohler "c" parameter
344 !       for aerosol mode m.  This is defined on a per-dry-particle-mass basis:
345 !           c = r(i,j,k,lkohlercptr_amode) * [rhodry * (4*pi/3) * rdry^3]
346 !   numptr_amode(m) = gchm r-array index for the number mixing ratio
347 !       (particles/mole-air) for aerosol mode m that is in clear air or
348 !       interstitial are (but not in cloud water).  If zero or negative,
349 !       then number is not being simulated.
350 !   ( numptr_amode_gchm(m) = same thing but for within gchm
351 !     numptr_amode_ccm2(m) = same thing but for within ccm2
352 !       These are temporary, to allow testing number in gchm before ccm2 )
353 !   numptrcw_amode(m) = gchm r-array index for the number mixing ratio
354 !       (particles/mole-air) for aerosol mode m
355 !       that is currently bound/dissolved in cloud water
356 !   lsfcptr_amode(m) = gchm r-array index for the surface area mixing ratio
357 !       (cm^2/mole-air) for aerosol mode m that is in clear air or
358 !       interstitial are (but not in cloud water).  If zero or negative,
359 !       then surface area is not being simulated.
360 !   lsfcptrcw_amode(m) = gchm r-array index for the surface area mixing ratio
361 !       (cm^2/mole-air) for aerosol mode m that is currently
362 !       bound/dissolved in cloud water.
363 !   lsigptr_amode(m) = gchm r-array index for sigmag for aerosol mode m
364 !       that is in clear air or interstitial are (but not in cloud water).
365 !       If zero or negative, then the constant sigmag_amode(m) is used.
366 !   lsigptrcw_amode(m) = gchm r-array index for sigmag for aerosol mode m
367 !       that is currently bound/dissolved in cloud water.
368 !       If zero or negative, then the constant sigmag_amode(m) is used.
369 !   lsigptrac_amode(m) = gchm r-array index for sigmag for aerosol mode m
370 !       for combined clear-air/interstial plus bound/dissolved in cloud water.
371 !       If zero or negative, then the constant sigmag_amode(m) is used.
373 !   dgnum_amode(m) = geometric dry mean diameter (m) of the number
374 !       distribution for aerosol mode m.
375 !       (Only used when numptr_amode(m) is zero or negative.)
376 !   dgnumlo_amode(m), dgnumhi_amode(m) = lower and upper limits on the
377 !       geometric dry mean diameter (m) of the number distribution
378 !       (Used when mprognum_amode>0, to limit dgnum to reasonable values)
379 !   sigmag_amode(m) = geometric standard deviation for aerosol mode m
380 !   sigmaglo_amode(m), sigmaghi_amode(m) = lower and upper limits on the
381 !       geometric standard deviation of the number distribution
382 !       (Used when mprogsfc_amode>0, to limit sigmag to reasonable values)
383 !   alnsg_amode(m) = alog( sigmag_amode(m) )
384 !   alnsglo_amode(m), alnsghi_amode(m) = alog( sigmaglo/hi_amode(m) )
385 !   voltonumb_amode(m) = ratio of number to volume for mode m
386 !   voltonumblo_amode(m), voltonumbhi_amode(m) = ratio of number to volume
387 !       when dgnum = dgnumlo_amode or dgnumhi_amode, respectively
388 !   voltosfc_amode(m), voltosfclo_amode(m), voltosfchi_amode(m) - ratio of
389 !       surface to volume for mode m (like the voltonumb_amode's)
390 !   alnv2n_amode(m), alnv2nlo_amode(m), alnv2nhi_amode(m) -
391 !       alnv2n_amode(m) = alog( voltonumblo_amode(m) ), ...
392 !   alnv2s_amode(m), alnv2slo_amode(m), alnv2shi_amode(m) -
393 !       alnv2s_amode(m) = alog( voltosfclo_amode(m) ), ...
394 !   rhcrystal_amode(m) = crystalization r.h. for mode m
395 !   rhdeliques_amode(m) = deliquescence r.h. for mode m
396 !   (*** these r.h. values are 0-1 fractions, not 0-100 percentages)
398 !   mcalcwater_amode(m) - if positive, water content for mode m will be
399 !       calculated and stored in rclm(k,lwaterptr_amode(m)).  Otherwise, no.
400 !   mprognum_amode(m) - if positive, number mixing-ratio for mode m will
401 !       be prognosed.  Otherwise, no.
402 !   mdiagnum_amode(m) - if positive, number mixing-ratio for mode m will
403 !       be diagnosed and put into rclm(k,numptr_amode(m)).  Otherwise, no.
404 !   mprogsfc_amode(m) - if positive, surface area mixing-ratio for mode m will
405 !       be prognosed, and sigmag will vary temporally and spatially.
406 !       Otherwise, sigmag is constant.
407 !       *** currently surface area is not prognosed when msectional>0 ***
409 !   ntot_aspectype = overall number of aerosol chemical species defined (over all modes)
410 !   specdens_amode(l) = dry density (kg/m^3) of aerosol chemical species type l
411 !   specmw_amode(l) = molecular weight (kg/kmol) of aerosol chemical species type l
412 !   specname_amode(l) = name of aerosol chemical species type l
413 !   specrefndxsw(l) = complex refractive index (visible wavelengths)
414 !                   of aerosol chemical species type l
415 !   specrefndxlw(l) = complex refractive index (infrared wavelengths)
416 !                   of aerosol chemical species type l
417 !   spechygro(l) = hygroscopicity of aerosol chemical species type l
419 !   lptr_so4_a_amode(m), lptr_so4_cw_amode(m) = gchm r-array index for the
420 !       mixing ratio for sulfate associated with aerosol mode m
421 !       ("a" and "cw" phases)
422 !   (similar for msa, oc, bc, nacl, dust)
424 !   modename_amode(m) = character-variable name for mode m,
425 !       read from mirage2.inp
426 !   modeptr_accum - mode index for the main accumulation mode
427 !       if modeptr_accum = 1, then mode 1 is the main accumulation mode,
428 !       and modename_amode(1) = "accum"
429 !   modeptr_aitken - mode index for the main aitken mode
430 !       if modeptr_aitken = 2, then mode 2 is the main aitken mode,
431 !       and modename_amode(2) = "aitken"
432 !   modeptr_ufine - mode index for the ultrafine mode
433 !       if modeptr_ufine = 3, then mode 3 is the ultrafine mode,
434 !       and modename_amode(3) = "ufine"
435 !   modeptr_coarseas - mode index for the coarse sea-salt mode
436 !       if modeptr_coarseas = 4, then mode 4 is the coarse sea-salt mode,
437 !       and modename_amode(4) = "coarse seasalt"
438 !   modeptr_coardust - mode index for the coarse dust mode
439 !       if modeptr_coardust = 5, then mode 5 is the coarse dust mode,
440 !       and modename_amode(5) = "coarse dust"
442 !   specdens_XX_amode = dry density (kg/m^3) of aerosol chemical species type XX
443 !       where XX is so4, om, bc, dust, seasalt
444 !       contains same values as the specdens_amode array
445 !       allows values to be referenced differently
446 !   specmw_XX_amode = molecular weight (kg/kmol) of aerosol chemical species type XX
447 !       contains same values as the specmw_amode array
449 !-----------------------------------------------------------------------
452 !--------------------------------------------------------------
454 ! ... aerosol size information for the current chunk
456 !--------------------------------------------------------------
458 !  dgncur = current geometric mean diameters (cm) for number distributions
459 !  dgncur_a - for unactivated particles, dry
460 !             (in physics buffer as DGNUM)
461 !  dgncur_awet - for unactivated particles, wet at grid-cell ambient RH
462 !             (in physics buffer as DGNUMWET)
464 !  the dgncur are computed from current mass and number
465 !  mixing ratios in the grid cell, BUT are then adjusted to be within
466 !  the bounds defined by dgnumlo/hi_amode
468 !  v2ncur = current (number/volume) ratio based on dgncur and sgcur
469 !              (volume in cm^3/whatever, number in particles/whatever)
470 !         == 1.0 / ( pi/6 * dgncur**3 * exp(4.5*((log(sgcur))**2)) )
471 !  v2ncur_a - for unactivated particles
472 !             (currently just defined locally)