I believe this was a bug, no idea how it was even working before
[WRF.git] / chem / module_data_soa_vbs.F
blobdd50ae0970a28cc621a2f4d489ac866a0675c76d
1 MODULE module_data_soa_vbs
2 ! This module is based on module_data_sorgam.F, it has been updated to use
3 ! for the new SOA scheme - SOA_VBS
5 !   USE module_data_radm2
7 !   param.inc start
8       IMPLICIT NONE
9       INTEGER NP                !bs maximum expected value of N
10       PARAMETER (NP = 8)
11 !      integer numaer
12 !      parameter (numaer=50)
14       INTEGER MAXITS            !bs maximum number of iterations
15       PARAMETER (MAXITS = 100)
17       REAL TOLF                 !bs convergence criterion on function values
18       PARAMETER (TOLF = 1.E-09)
20       REAL TOLMIN                 !bs criterion whether superios convergence to
21       PARAMETER (TOLMIN = 1.E-12) !bs a minimum of fmin has occurred
23       REAL TOLX                 !bs convergence criterion on delta_x
24       PARAMETER (TOLX = 1.E-10)
26       REAL STPMX                !bs scaled maximum step length allowed
27       PARAMETER (STPMX = 100.)
29       REAL c303, c302
30       PARAMETER (c303=19.83, c302=5417.4)
32       INTEGER lcva, lcvb, lspcv, ldesn
33       PARAMETER (lcva=4,lcvb=4, lspcv=lcva+lcvb)
34       PARAMETER (ldesn=13)
35 !mh    ldesn is number of deposition species
36 !mh    true number of deposited species may be larger since there
37 !mh    are species which are deposited with the same rate
39       INTEGER laerdvc, lnonaerdvc, l1ae, laero, imodes, aspec
40 !liqy
41        PARAMETER (laerdvc=46,lnonaerdvc=17+lspcv)
42 !liqy-20140912
43 !      PARAMETER (laerdvc=39,lnonaerdvc=8+lspcv)
44       PARAMETER (l1ae=laerdvc+lnonaerdvc)
45       PARAMETER (laero=4,imodes=4,aspec=1)
46 !     LAERDVC  number of advected aerosol dynamic parameters for a given
47 !     component species
48 !ia     L1AE        advected parameters+non-advected parameters
49 !ia     LAERO       number of aerosol component species
50 !ia     imodes      number of aerosol modes
51 !ia     ASPEC       number of gas phase comp. that are added dynamically
52 !ia                 currently only sulfate (=1)
53 !bs
54 !bs * BS ** BS ** BS ** BS ** BS ** BS ** BS ** BS ** BS ** BS ** BS **
55 !bs
56       INTEGER aemiss
57       PARAMETER (aemiss=4)
58 !bs *  AEMISS      # of aerosol species with emissions link to gas phase
59 !bs                currently ECI, ECJ, BCI, BCJ
60  ! updated ldrog numbers for the new SOA mechanism
61       INTEGER, PARAMETER :: ldroga=6    ! anthropogenic: ALK4,ALK5,OLE1,OLE2,ARO1,ARO2
62       INTEGER, PARAMETER :: ldrogb=3    ! biogenic: ISOP,SESQ,TERP
63       INTEGER, PARAMETER :: ldrogr=1    ! for branching ratio
64       INTEGER, PARAMETER :: ldrog_vbs=ldroga+ldrogb+ldrogr ! I've renamed this parameter to separate from "ldrog" for MADE/SORGAM
66 !      INTEGER ldroga
67 !      PARAMETER (ldroga=11)
68 !      INTEGER ldrogb
69 !      PARAMETER (ldrogb=6)
70 !      INTEGER ldrog
71 !bs * LDROGA      # of anthropogenic organic aerosol precursor gases (DR
72 !bs * LDROGB      # of biogenic organic aerosol precursor gases (DROG)
73 !bs * LSPCV       # of condensable organic vapor interacting between gas
74 !bs               aerosol phase with SORGAM
75 !bs
76 !     param.inc stop
78 ! //////////////////////////////////////////////////////////////////////
79 ! FSB include file
81 ! *** declare and set flag for organic aerosol production method
82 ! *** Two method are available:
84 ! *** The method of Pandis,Harley, Cass, and Seinfeld, 1992,
85 !     Secondary aerosol formation and transport, Atmos. Environ., 26A,
86 !     pp 2453-2466
87 !     Bowman et al. Atmospheric Environment
88 !     Vol 29, pp 579-589, 1995.
89 ! *** and
90 ! *** The method of Odum, Hoffmann, Bowman, Collins, Flagen and
91 !     Seinfeld, 1996, Gas/particle partitioning and secondary organic ae
92 !     yields, Environ. Sci, Technol, 30, pp 2580-2585.
93                             ! 1 = Pandis et al.  1992 method is used
94       INTEGER orgaer
95                             ! 2 = Pankow 1994/Odum et al. 1996 method is
96 ! ***
97 ! switch for organic aerosol method         
98       PARAMETER (orgaer=2)
100 ! *** information about visibility variables
101 ! number of visibility variables    
102       INTEGER n_ae_vis_spc
103       PARAMETER (n_ae_vis_spc=2)
105 ! index for visual range in deciview             
106       INTEGER idcvw
107       PARAMETER (idcvw=1)
108 ! index for extinction [ 1/km ]                  
109       INTEGER ibext
110       PARAMETER (ibext=2)
112 ! *** set up indices for array  CBLK
114 ! index for Accumulation mode sulfate aerosol
115       INTEGER vso4aj
116       PARAMETER (vso4aj=1)
118 ! index for Aitken mode sulfate concentration
119       INTEGER vso4ai
120       PARAMETER (vso4ai=2)
122 ! index for Accumulation mode aerosol ammonium
123       INTEGER vnh4aj
124       PARAMETER (vnh4aj=3)
126 ! index for Aitken mode ammonium concentration
127       INTEGER vnh4ai
128       PARAMETER (vnh4ai=4)
130 ! index for Accumulation mode aerosol nitrate
131       INTEGER vno3aj
132       PARAMETER (vno3aj=5)
134 ! index for Aitken mode nitrate concentration
135       INTEGER vno3ai
136       PARAMETER (vno3ai=6)
138 ! index for Accumulation mode aerosol sodium
139       INTEGER vnaaj
140       PARAMETER (vnaaj=7)
142 ! index for Aitken mode sodium concentration
143       INTEGER vnaai
144       PARAMETER (vnaai=8)
146 ! index for Accumulation mode aerosol chloride
147       INTEGER vclaj
148       PARAMETER (vclaj=9)
150 ! index for Aitken mode chloride concentration
151       INTEGER vclai
152       PARAMETER (vclai=10)
154 ! I've changed the names and simplified
155 ! indices for accumulation and aitken modes of anthropogenic SOA
156       INTEGER, PARAMETER ::  vasoa1j=11
157       INTEGER, PARAMETER ::  vasoa1i=12
159       INTEGER, PARAMETER ::  vasoa2j=13
160       INTEGER, PARAMETER ::  vasoa2i=14
162       INTEGER, PARAMETER ::  vasoa3j=15
163       INTEGER, PARAMETER ::  vasoa3i=16
165       INTEGER, PARAMETER ::  vasoa4j=17
166       INTEGER, PARAMETER ::  vasoa4i=18
168 ! indices for accumulation and aitken modes of biogenic SOA
169       INTEGER, PARAMETER ::  vbsoa1j=19
170       INTEGER, PARAMETER ::  vbsoa1i=20
172       INTEGER, PARAMETER ::  vbsoa2j=21
173       INTEGER, PARAMETER ::  vbsoa2i=22
174                                       
175       INTEGER, PARAMETER ::  vbsoa3j=23
176       INTEGER, PARAMETER ::  vbsoa3i=24
177                                       
178       INTEGER, PARAMETER ::  vbsoa4j=25
179       INTEGER, PARAMETER ::  vbsoa4i=26
180 !------------------------------------------------------------------------------
182 ! index for Accumulation mode primary anthropogenic
183       INTEGER vorgpaj
184       PARAMETER (vorgpaj=27)
186 ! index for Aitken mode primary anthropogenic
187       INTEGER vorgpai
188       PARAMETER (vorgpai=28)
190 ! index for Accumulation mode aerosol elemen
191       INTEGER vecj
192       PARAMETER (vecj=29)
194 ! index for Aitken mode elemental carbon    
195       INTEGER veci
196       PARAMETER (veci=30)
198 ! index for Accumulation mode primary PM2.5 
199       INTEGER vp25aj
200       PARAMETER (vp25aj=31)
202 ! index for Aitken mode primary PM2.5 concentration
203       INTEGER vp25ai
204       PARAMETER (vp25ai=32)
206 ! index for coarse mode anthropogenic aerososol
207       INTEGER vantha
208       PARAMETER (vantha=33)
210 ! index for coarse mode marine aerosol concentration
211       INTEGER vseas
212       PARAMETER (vseas=34)
214 ! index for coarse mode soil-derived aerosol
215       INTEGER vsoila
216       PARAMETER (vsoila=35)
218 ! index for Aitken mode number              
219       INTEGER vnu0
220       PARAMETER (vnu0=36)
222 ! index for accum  mode number              
223       INTEGER vac0
224       PARAMETER (vac0=37)
226 ! index for coarse mode number              
227       INTEGER vcorn
228       PARAMETER (vcorn=38)
230 ! index for Accumulation mode aerosol water 
231       INTEGER vh2oaj
232       PARAMETER (vh2oaj=39)
234 ! index for Aitken mode aerosol water concentration
235       INTEGER vh2oai
236       PARAMETER (vh2oai=40)
238 ! index for Aitken mode 3'rd moment         
239       INTEGER vnu3
240       PARAMETER (vnu3=41)
241 ! index for Accumulation mode 3'rd moment   
242       INTEGER vac3
243       PARAMETER (vac3=42)
245 ! index for coarse mode 3rd moment          
246       INTEGER vcor3
247       PARAMETER (vcor3=43)
249 ! index for sulfuric acid vapor concentration
250       INTEGER vsulf
251       PARAMETER (vsulf=44)
253 ! index for nitric acid vapor concentration
254       INTEGER vhno3
255       PARAMETER (vhno3=45)
257 ! index for ammonia gas concentration
258       INTEGER vnh3
259       PARAMETER (vnh3=46)
261 ! index for N2O5 gas concentration
262         INTEGER vn2o5
263         PARAMETER (vn2o5=47)
265 ! index for the inverse of air density, used to transform ug/m3 to and from
266 ! ug/kg dry air.
268         INTEGER valt_in
269         PARAMETER (valt_in=48)
271 INTEGER, PARAMETER :: vcvasoa1=49
272 INTEGER, PARAMETER :: vcvasoa2=50
273 INTEGER, PARAMETER :: vcvasoa3=51
274 INTEGER, PARAMETER :: vcvasoa4=52
275 INTEGER, PARAMETER :: vcvbsoa1=53
276 INTEGER, PARAMETER :: vcvbsoa2=54
277 INTEGER, PARAMETER :: vcvbsoa3=55
278 INTEGER, PARAMETER :: vcvbsoa4=56
279 !liqy-20140912
280 !-----------------------------------------------------------------------------
282 ! *** set up species dimension and indices for sedimentation
283 !     velocity array VSED
285 ! number of sedimentation velocities         
286       INTEGER naspcssed
287       PARAMETER (naspcssed=6)
289 ! index for Aitken mode number                  
290       INTEGER vsnnuc
291       PARAMETER (vsnnuc=1)
293 ! index for Accumulation mode number            
294       INTEGER vsnacc
295       PARAMETER (vsnacc=2)
297 ! index for coarse mode number                  
298       INTEGER vsncor
299       PARAMETER (vsncor=3)
301 ! index for Aitken mode mass                     
302       INTEGER vsmnuc
303       PARAMETER (vsmnuc=4)
305 ! index for accumulation mode mass               
306       INTEGER vsmacc
307       PARAMETER (vsmacc=5)
309 ! index for coarse mass                         
310       INTEGER vsmcor
311       PARAMETER (vsmcor=6)
313 ! *** set up species dimension and indices for deposition
314 !     velocity array VDEP
316 ! number of deposition velocities            
317       INTEGER naspcsdep
318       PARAMETER (naspcsdep=7)
320 ! index for Aitken mode number                  
321       INTEGER vdnnuc
322       PARAMETER (vdnnuc=1)
324 ! index for accumulation mode number            
325       INTEGER vdnacc
326       PARAMETER (vdnacc=2)
328 ! index for coarse mode number                  
329       INTEGER vdncor
330       PARAMETER (vdncor=3)
332 ! index for Aitken mode mass                    
333       INTEGER vdmnuc
334       PARAMETER (vdmnuc=4)
336 ! index for accumulation mode                   
337       INTEGER vdmacc
338       PARAMETER (vdmacc=5)
340 ! index for fine mode mass (Aitken + accumulation)
341       INTEGER vdmfine
342       PARAMETER (vdmfine=6)
344 ! index for coarse mode mass                    
345       INTEGER vdmcor
346       PARAMETER (vdmcor=7)
348 ! SOA precursors + OH, O3, NO3
349 ! anthropogenic
350 INTEGER, PARAMETER :: palk4=1
351 INTEGER, PARAMETER :: palk5=2
352 INTEGER, PARAMETER :: pole1=3
353 INTEGER, PARAMETER :: pole2=4
354 INTEGER, PARAMETER :: paro1=5
355 INTEGER, PARAMETER :: paro2=6
357 ! biogenic
358 INTEGER, PARAMETER :: pisop=7
359 INTEGER, PARAMETER :: pterp=8
360 INTEGER, PARAMETER :: psesq=9
362 ! for branching
363 INTEGER, PARAMETER :: pbrch=10
365  ! new indices
366 INTEGER, PARAMETER :: pasoa1=1
367 INTEGER, PARAMETER :: pasoa2=2
368 INTEGER, PARAMETER :: pasoa3=3
369 INTEGER, PARAMETER :: pasoa4=4
370       
371 INTEGER, PARAMETER :: pbsoa1=5
372 INTEGER, PARAMETER :: pbsoa2=6
373 INTEGER, PARAMETER :: pbsoa3=7
374 INTEGER, PARAMETER :: pbsoa4=8
375 !-----------------------------------------------
378 !bs * end of AERO_SOA.EXT *
381 ! *** include file for aerosol routines
384 !....................................................................
386 !  CONTAINS: Fundamental constants for air quality modeling
388 !  DEPENDENT UPON:  none
390 !  REVISION HISTORY:
392 !    Adapted 6/92 by CJC from ROM's PI.EXT.
394 !    Revised 3/1/93 John McHenry to include constants needed by
395 !    LCM aqueous chemistry
396 !    Revised 9/93 by John McHenry to include additional constants
397 !    needed for FMEM clouds and aqueous chemistry
399 !    Revised 3/4/96 by Dr. Francis S. Binkowski to reflect current
400 !    Models3 view that MKS units should be used wherever possible,
401 !    and that sources be documentated. Some variables have been added
402 !    names changed, and values revised.
404 !    Revised 3/7/96 to have universal gas constant input and compute
405 !    gas constant is chemical form. TWOPI is now calculated rather than
407 !    Revised 3/13/96 to group declarations and parameter statements.
409 !    Revised 9/13/96 to include more physical constants.
410 !    Revised 12/24/96 eliminate silly EPSILON, AMISS
412 !    Revised 1/06/97 to eliminate most derived constants
413 !    10/12/11- Modified to use with soa_vbs, by Ravan Ahmadov
415 ! FSB REFERENCES:
417 !      CRC76,        CRC Handbook of Chemistry and Physics (76th Ed),
418 !                     CRC Press, 1995
419 !      Hobbs, P.V.   Basic Physical Chemistry for the Atmospheric Scien
420 !                     Cambridge Univ. Press, 206 pp, 1995.
421 !      Snyder, J.P., Map Projections-A Working Manual, U.S. Geological
422 !                     Paper 1395 U.S.GPO, Washington, DC, 1987.
423 !      Stull, R. B., An Introduction to Bounday Layer Meteorology, Klu
424 !                     Dordrecht, 1988
426 ! Geometric Constants:
428       REAL*8 & ! PI (single precision 3.141593)
429         pirs
430       PARAMETER (pirs=3.14159265358979324)
431 !      REAL     PIRS ! PI (single precision 3.141593)
432 !      PARAMETER ( PIRS = 3.141593 )
433 ! Fundamental Constants: ( Source: CRC76, pp 1-1 to 1-6)
435 ! Avogadro's Constant [ 1/mol ]
436       REAL avo
437       PARAMETER (avo=6.0221367E23)
439 ! universal gas constant [ J/mol-K ]
440       REAL rgasuniv
441       PARAMETER (rgasuniv=8.314510)
443 ! standard atmosphere  [ Pa ]
444       REAL stdatmpa
445       PARAMETER (stdatmpa=101325.0)
447 ! Standard Temperature [ K ]
448       REAL stdtemp
449       PARAMETER (stdtemp=273.15)
451 ! Stefan-Boltzmann [ W/(m**2 K**4) ]
452       REAL stfblz
453       PARAMETER (stfblz=5.67051E-8)
456 ! mean gravitational acceleration [ m/sec**2 ]
457       REAL grav
458       PARAMETER (grav=9.80622)
459 ! FSB Non MKS qualtities:
461 ! Molar volume at STP [ L/mol ] Non MKS units
462       REAL molvol
463       PARAMETER (molvol=22.41410)
466 ! Atmospheric Constants:
468 ! FSB                     78.06%  N2, 21% O2 and 0.943% A on a mole
469       REAL mwair
470                         ! fraction basis. ( Source : Hobbs, 1995) pp 69-
471 ! mean molecular weight for dry air [ g/mol ]
472       PARAMETER (mwair=28.9628)
474 ! dry-air gas constant [ J / kg-K ]
475       REAL rdgas
476       PARAMETER (rdgas=1.0E3*rgasuniv/mwair)
478 !  3*PI
479       REAL threepi
480       PARAMETER (threepi=3.0*pirs)
482 !  6/PI
483       REAL f6dpi
484       PARAMETER (f6dpi=6.0/pirs)
486 !  1.0e9 * 6/PIRS
487       REAL f6dpi9
488       PARAMETER (f6dpi9=1.0E9*f6dpi)
490 ! 1.0e-9 * 6/PIRS
491       REAL f6dpim9
492       PARAMETER (f6dpim9=1.0E-9*f6dpi)
494 !  SQRT( PI )
495       REAL sqrtpi
496       PARAMETER (sqrtpi=1.7724539)
498 !  SQRT( 2 )
499       REAL sqrt2
500       PARAMETER (sqrt2=1.4142135623731)
502 !  ln( sqrt( 2 ) )
503       REAL lgsqt2
504       PARAMETER (lgsqt2=0.34657359027997)
506 !  1/ln( sqrt( 2 ) )
507       REAL dlgsqt2
508       PARAMETER (dlgsqt2=1.0/lgsqt2)
510 !  1/3
511       REAL one3
512       PARAMETER (one3=1.0/3.0)
514 !  2/3
515       REAL two3
516       PARAMETER (two3=2.0/3.0)
519 ! *** physical constants:
521 ! Boltzmann's Constant [ J / K ]
522       REAL boltz
523       PARAMETER (boltz=rgasuniv/avo)
526 ! *** component densities [ kg/m**3 ] :
529 !  bulk density of aerosol sulfate
530       REAL rhoso4
531       PARAMETER (rhoso4=1.8E3)
533 !  bulk density of aerosol ammonium
534       REAL rhonh4
535       PARAMETER (rhonh4=1.8E3)
537 ! bulk density of aerosol nitrate
538       REAL rhono3
539       PARAMETER (rhono3=1.8E3)
541 !  bulk density of aerosol water
542       REAL rhoh2o
543       PARAMETER (rhoh2o=1.0E3)
545 ! bulk density for aerosol organics
546       REAL rhoorg
547       PARAMETER (rhoorg=1.0E3)
549 ! bulk density for aerosol soil dust
550       REAL rhosoil
551       PARAMETER (rhosoil=2.6E3)
553 ! bulk density for marine aerosol
554       REAL rhoseas
555       PARAMETER (rhoseas=2.2E3)
557 ! bulk density for anthropogenic aerosol
558       REAL rhoanth
559       PARAMETER (rhoanth=2.2E3)
561 ! bulk density of aerosol sodium
562       REAL rhona
563       PARAMETER (rhona=2.2E3)
565 ! bulk density of aerosol chloride
566       REAL rhocl
567       PARAMETER (rhocl=2.2E3)
569 !liqy
570 ! bulk density of aerosol casium. equals to dust.
571                 REAL rhoca
572                 PARAMETER (rhoca=2.6E3)
574 ! bulk density of aerosol k. equals to dust.
575                 REAL rhok
576                 PARAMETER (rhok=2.6E3)
578 ! bulk density of aerosol mg. equals to dust.
579                 REAL rhomg
580                 PARAMETER (rhomg=2.6E3)
581 !liqy-20140616
582 ! *** Factors for converting aerosol mass concentration [ ug m**-3] to
583 !         to 3rd moment concentration [ m**3 m^-3]
585       REAL so4fac
586       PARAMETER (so4fac=f6dpim9/rhoso4)
588       REAL nh4fac
589       PARAMETER (nh4fac=f6dpim9/rhonh4)
591       REAL h2ofac
592       PARAMETER (h2ofac=f6dpim9/rhoh2o)
594       REAL no3fac
595       PARAMETER (no3fac=f6dpim9/rhono3)
597       REAL orgfac
598       PARAMETER (orgfac=f6dpim9/rhoorg)
600       REAL soilfac
601       PARAMETER (soilfac=f6dpim9/rhosoil)
603       REAL seasfac
604       PARAMETER (seasfac=f6dpim9/rhoseas)
606       REAL anthfac
607       PARAMETER (anthfac=f6dpim9/rhoanth)
609       REAL nafac
610       PARAMETER (nafac=f6dpim9/rhona)
612       REAL clfac
613       PARAMETER (clfac=f6dpim9/rhocl)
615 !liqy-20140616
616 !  starting standard surface pressure [ Pa ]  
617       REAL pss0
618       PARAMETER (pss0=101325.0)
620 !  starting standard surface temperature [ K ]
621       REAL tss0
622       PARAMETER (tss0=288.15)
624 !  initial sigma-G for nucleimode                 
625       REAL sginin
626       PARAMETER (sginin=1.70)
628 !  initial sigma-G for accumulation mode          
629       REAL sginia
630       PARAMETER (sginia=2.00)
632 ! initial sigma-G for coarse mode               
633       REAL sginic
634       PARAMETER (sginic=2.5)
636 !  initial mean diameter for nuclei mode [ m ]    
637       REAL dginin
638       PARAMETER (dginin=0.01E-6)
640 !  initial mean diameter for accumulation mode [ m ]
641       REAL dginia
642       PARAMETER (dginia=0.07E-6)
644 ! initial mean diameter for coarse mode [ m ]  
645       REAL dginic
646       PARAMETER (dginic=1.0E-6)
648 !................   end   AERO3box.EXT   ...............................
649 !///////////////////////////////////////////////////////////////////////
651 !     LOGICAL diagnostics
652 ! *** Scalar variables for fixed standard deviations.
654 ! Flag for writing diagnostics to file       
655 ! nuclei mode exp( log^2( sigmag )/8 )  
656       REAL en1
657 ! accumulation mode exp( log^2( sigmag )
658       REAL ea1
660       REAL ec1
661 ! coarse mode exp( log^2( sigmag )/8 )  
662 ! nuclei        **4                    
663       REAL esn04
664 ! accumulation                         
665       REAL esa04
667       REAL esc04
668 ! coarse                               
669 ! nuclei        **5                    
670       REAL esn05
672       REAL esa05
673 ! accumulation                         
674 ! nuclei        **8                    
675       REAL esn08
676 ! accumulation                         
677       REAL esa08
679       REAL esc08
680 ! coarse                               
681 ! nuclei        **9                    
682       REAL esn09
684       REAL esa09
685 ! accumulation                         
686 ! nuclei        **12                   
687       REAL esn12
688 ! accumulation                         
689       REAL esa12
691       REAL esc12
692 ! coarse mode                          
693 ! nuclei        **16                   
694       REAL esn16
695 ! accumulation                         
696       REAL esa16
698       REAL esc16
699 ! coarse                               
700 ! nuclei        **20                   
701       REAL esn20
702 ! accumulation                         
703       REAL esa20
705       REAL esc20
706 ! coarse                               
707 ! nuclei        **25                   
708       REAL esn25
710       REAL esa25
711 ! accumulation                         
712 ! nuclei        **24                   
713       REAL esn24
714 ! accumulation                         
715       REAL esa24
717       REAL esc24
718 ! coarse                               
719 ! nuclei        **28                   
720       REAL esn28
721 ! accumulation                         
722       REAL esa28
724       REAL esc28
725 ! coarse                               
726 ! nuclei        **32                   
727       REAL esn32
728 ! accumulation                         
729       REAL esa32
731       REAL esc32
732 ! coarese                              
733 ! nuclei        **36                   
734       REAL esn36
735 ! accumulation                         
736       REAL esa36
738       REAL esc36
739 ! coarse                               
740 ! nuclei        **49                   
741       REAL esn49
743       REAL esa49
744 ! accumulation                         
745 ! nuclei        **52                   
746       REAL esn52
748       REAL esa52
749 ! accumulation                         
750 ! nuclei        **64                   
751       REAL esn64
752 ! accumulation                         
753       REAL esa64
755       REAL esc64
756 ! coarse                               
758       REAL esn100
759 ! nuclei        **100                  
760 ! nuclei        **(-20)                
761       REAL esnm20
762 ! accumulation                         
763       REAL esam20
765       REAL escm20
766 ! coarse                               
767 ! nuclei        **(-32)                
768       REAL esnm32
769 ! accumulation                         
770       REAL esam32
772       REAL escm32
773 ! coarse                               
774 ! log(sginin)                           
775       REAL xxlsgn
776 ! log(sginia)                           
777       REAL xxlsga
779       REAL xxlsgc
780 ! log(sginic )                          
781 ! log(sginin ) ** 2                           
782       REAL l2sginin
783 ! log(sginia ) ** 2                           
784       REAL l2sginia
786       REAL l2sginic
788 ! *** set up COMMON blocks for esg's:
790 ! log(sginic ) ** 2
792 ! *** SET NUCLEATION FLAG:
794                             ! INUCL = 0, Kerminen & Wexler Mechanism
795       INTEGER inucl
796                             ! INUCL = 1, Youngblood and Kreidenweis mech
797                             ! INUCL = 2, Kulmala et al. mechanism
798 ! Flag for Choice of nucleation Mechanism   
799       PARAMETER (inucl=2)
801 ! *** Set flag for sedimentation velocities:
803       LOGICAL icoarse
804       PARAMETER (icoarse=.FALSE.) ! *** END AERO_INTERNAL.EXT
805 ! *** Diameters and standard deviations for emissions
806 !     the diameters are the volume (mass) geometric mean diameters
808 ! *** Aitken mode:
809 ! special factor to compute mass transfer           
810       REAL dgvem_i
811       PARAMETER (dgvem_i=0.03E-6) ! [ m ]                            
812       REAL sgem_i
813       PARAMETER (sgem_i=1.7)
815 ! *** Accumulation mode:
816       REAL dgvem_j
817       PARAMETER (dgvem_j=0.3E-6) ! [ m ]                             
818       REAL sgem_j
819       PARAMETER (sgem_j=2.0)
821 ! *** Coarse mode
822       REAL dgvem_c
823       PARAMETER (dgvem_c=6.0E-6) ! [ m ] <<< Corrected 11/19/97      
824       REAL sgem_c
825       PARAMETER (sgem_c=2.2)
827 ! *** factors for getting number emissions rate from mass emissions rate
828 ! Aitken mode                                       
829       REAL factnumn
830 ! accumulation mode                                 
831       REAL factnuma
833       REAL factnumc
834 ! coarse mode                                       
835       REAL facatkn_min, facacc_min
836       PARAMETER (facatkn_min=0.04,facacc_min=1.0-facatkn_min)
837       REAL xxm3
838       REAL, PARAMETER ::  conmin = 1.E-16
839       REAL, PARAMETER ::  epsilc = 1.E-16
840 ! [ ug/m**3 ] ! changed 1/6/98 
841       REAL*8 & ! factor to set minimum for Aitken mode number  
842         nummin_i
843       REAL*8 & ! factor to set minimum for accumulation mode nu
844         nummin_j
845       REAL*8 & 
846         nummin_c
847 ! factor to set minimum for coarse mode number  
849 !bs      REAL ALPHSULF ! Accommodation coefficient for sulfuric acid
850 !bs      PARAMETER ( ALPHSULF = 0.05 ) ! my be set to one in future
852 !bs      REAL DIFFSULF ! molecular diffusivity for sulfuric acid [ m**2
853 !bs      PARAMETER( DIFFSULF = 0.08E-4 ) ! may be changed in future
855 !bs * 23/03/99 updates of ALPHSULF and DIFFSULF adopted fro new code fro
856 !bs * DIFFSULF is calculated from Reid, Prausnitz, and Poling, The prope
857 !bs * of gases and liquids, 4th edition, McGraw-Hill, 1987, pp 587-588.
858 !bs * Equation (11-4.4) was used.
859 !bs * The value is at T = 273.16 K and P = 1.01325E05 Pa
860 !bs * Temperature dependence is included for DIFFSULF via DIFFCORR (see
862 ! Accommodation coefficient for sulfuric
863       REAL alphsulf
864       PARAMETER (alphsulf=1.0) 
865 !bs updated from code of FSB         
866 ! molecular weight for sulfuric acid [ kg/mole ] MKS 
867       REAL mwh2so4
868       PARAMETER (mwh2so4=98.07354E-3) 
869 !cia corrected error 24/11/97
870 ! molecular diffusivity for sulfuric acid [ m**2 /se
871       REAL diffsulf
872       PARAMETER (diffsulf=9.362223E-06) 
873 !bs updated from code of FSB 
874 !bs Accomodation coefficient for organic
875       REAL alphaorg
876       PARAMETER (alphaorg=1.0)                                    !bs Kleeman et al. '99 propose alpha
877 !bs Bowman et al. '97 uses alpha = 1.
878 !bs mean molecular weight of organics [k
879       REAL mworg
880       PARAMETER (mworg=175.0E-03)
882 !bs * DIFFORG is calculated from the same formula as DIFFSULF.
883 !bs * An average elemental composition of C=8, O=3, N=1, H=17 is asuumed
884 !bs * to calculate DIFFORG at T = 273.16K and  P = 1.01325E05 Pa.
885 !bs * Temperature dependence is included below.
886 !bs molecular diffusivity for organics [
887       REAL difforg
888       PARAMETER (difforg=5.151174E-06)
889 ! *** CCONC is the factor for near-continuum condensation.
890 ! ccofm * sqrt( ta )                    
891       REAL cconc
892       PARAMETER (cconc=2.0*pirs*diffsulf) 
893 !bs * factor for NC condensation for organics
894 ! [ m**2 / sec ]       
895       REAL cconc_org
896       PARAMETER (cconc_org=2.0*pirs*difforg) 
897 ! [ m**2 / sec ]    
898 !bs analogue to CCOFM but for organics  
899       REAL ccofm_org
900 ! FSB  CCOFM is  the accommodation coefficient
901 !      times the mean molecular velocity for h2so4 without the temperatu
902 !      after some algebra
904 !bs CCOFM_ORG * sqrt(TA)                
905 ! set to a value below                  
906       REAL ccofm
907 ! minimum aerosol sulfate concentration          
908       REAL aeroconcmin
909       PARAMETER (aeroconcmin=0.0001) 
911 !*******************************************************************
912 !*                                                                 *
913 !*  start parameters and variables for aerosol-cloud interactions  *
914 !*                                                                 *
915 !*******************************************************************
917 !   maxd_atype = maximum allowable number of aerosol types
918 !   maxd_asize = maximum allowable number of aerosol size bins
919 !   maxd_acomp = maximum allowable number of chemical components
920 !       in each aerosol size bin
921 !   maxd_aphase = maximum allowable number of aerosol phases (gas, cloud, ice, rain, ...)
923 !   ntype_aer = number of aerosol types
924 !   nsize_aer(t) = number of aerosol size bins for aerosol type t. each bin w/ same set of components
925 !   nphase_aer = number of aerosol phases
927 !   msectional - if positive, moving-center sectional code is utilized,
928 !       and each mode is actually a section.
929 !   maerosolincw - if positive, both unactivated/interstitial and activated
930 !       aerosol species are simulated.  if zero/negative, only the
931 !       unactivated are simulated.
933 !   ncomp_aer(t) = number of chemical components for aerosol type t
934 !   ncomp_aer_nontracer(t) = number of "non-tracer" chemical components while in gchm code
935 !   mastercompptr_aer(c,t) = mastercomp type/i.d. for chemical component c
936 !       (1=sulfate, others to be defined) and aerosol type t.
937 !   massptr_aer(c,s,t,p) = gchm r-array index for the mixing ratio
938 !       (moles-x/mole-air) for chemical component c in size bin s for type t and phase p
940 !   waterptr_aer(s,t) = mixing ratio (moles-water/mole-air) for water
941 !       associated with aerosol size bin s and type t
942 !   hygroptr_aer(s,t) = gchm r-array index for the bulk hygroscopicity of the size bin and type
943 !   numptr_aer(s,t,p) = gchm r-array index for the number mixing ratio
944 !       (particles/mole-air) for aerosol size bin s, type t, and phase p
945 !       If zero or negative, then number is not being simulated.
947 !   mprognum_aer(s,t,p) - if positive, number mixing-ratio for size s, type t,
948 !       and phase p will be prognosed.  Otherwise, no.
950 !   ntot_mastercomp_aer = number of aerosol chemical components defined
951 !   dens_mastercomp_aer(mc) = dry density (g/cm^3) of aerosol master chemical component type c
952 !   mw_mastercomp_aer(mc) = molecular weight of aerosol master chemical component type mc
953 !   name_mastercomp_aer(mc) = name of aerosol master chemical component type mc
954 !   mc=mastercompptr_aer(c,t)
955 !   dens_aer(c,t) = dry density (g/cm^3) of aerosol chemical component type c and type t
956 !   mw_aer(c,t) = molecular weight of aerosol chemical component type c and type t
957 !   name_aer(c,t) = name of aerosol chemical component type c and type t
959 !   lptr_so4_aer(s,t,p) = gchm r-array index for the
960 !       mixing ratio for sulfate associated with aerosol size bin s, type t, and phase p
961 !   (similar for msa, oc, bc, nacl, dust)
963 !-----------------------------------------------------------------------
965 !   volumcen_sect(s,t)= volume (cm^3) at center of section m
966 !   volumlo_sect(s,t) = volume (cm^3) at lower boundary of section m
967 !   volumhi_sect(s,t) = volume (cm^3) at upper boundary of section m
969 !   dlo_sect(s,t) = diameter (cm) at lower boundary of section m
970 !   dhi_sect(s,t) = diameter (cm) at upper boundary of section m
971 !   dcen_sect(s,t) = volume arithmetic-mean diameter (cm) of section m
972 !       (corresponds to volumcen_sect == 0.5*(volumlo_sect + volumhi_sect)
974 !-----------------------------------------------------------------------
975 !   nov-04 sg ! replaced amode with aer and expanded aerosol dimension to include type and phase
977         integer, parameter :: maxd_atype = 2
978         integer, parameter :: maxd_asize = 2
979         integer, parameter :: maxd_acomp = 19
980         integer, parameter :: maxd_aphase = 2
981         integer, save :: ai_phase ! interstitial phase of aerosol
982         integer, save :: cw_phase ! cloud water phase of aerosol
983         integer, save :: ci_phase ! cloud ice  phase of aerosol
984         integer, save :: cr_phase ! rain  phase of aerosol
985         integer, save :: cs_phase ! snow  phase of aerosol
986         integer, save :: cg_phase ! graupel phase of aerosol
988         integer, save :: ntype_aer = 0 ! number of types
989         integer, save :: ntot_mastercomp_aer = 0 ! number of master components
990         integer, save :: nphase_aer = 0 ! number of phases
992         integer, save ::   &
993           msectional, maerosolincw,   &
994           nsize_aer( maxd_atype ),   & ! number of size bins
995           ncomp_aer( maxd_atype ),   & ! number of chemical components
996           ncomp_aer_nontracer( maxd_atype ),   &
997           mastercompptr_aer(maxd_acomp, maxd_atype), &   !  mastercomp index
998           massptr_aer( maxd_acomp, maxd_asize, maxd_atype, maxd_aphase ), & ! index for mixing ratio
999           waterptr_aer( maxd_asize, maxd_atype ), & ! index for aerosol water
1000           hygroptr_aer( maxd_asize, maxd_atype ), & ! index for aerosol hygroscopicity
1001           numptr_aer( maxd_asize, maxd_atype, maxd_aphase ), & ! index for the number mixing ratio
1002           mprognum_aer(maxd_asize,maxd_atype,maxd_aphase)
1004         real, save ::   &
1005           dens_aer( maxd_acomp, maxd_atype ),   &
1006           dens_mastercomp_aer( maxd_acomp ),   &
1007           mw_mastercomp_aer( maxd_acomp ), &
1008           mw_aer( maxd_acomp, maxd_atype ),  &
1009           hygro_mastercomp_aer( maxd_acomp ), &
1010           hygro_aer( maxd_acomp, maxd_atype )
1011         character*10, save ::   &
1012           name_mastercomp_aer( maxd_acomp ), &
1013           name_aer( maxd_acomp, maxd_atype )
1015         real, save ::   &
1016           volumcen_sect( maxd_asize, maxd_atype ),   &
1017           volumlo_sect( maxd_asize, maxd_atype ),   &
1018           volumhi_sect( maxd_asize, maxd_atype ),   &
1019           dcen_sect( maxd_asize, maxd_atype ),   &
1020           dlo_sect( maxd_asize, maxd_atype ),   &
1021           dhi_sect( maxd_asize, maxd_atype ),   &
1022           sigmag_aer(maxd_asize, maxd_atype)
1024         integer, save ::                     &
1025           lptr_so4_aer(maxd_asize,maxd_atype,maxd_aphase),        &
1026           lptr_nh4_aer(maxd_asize,maxd_atype,maxd_aphase),        &
1027           lptr_no3_aer(maxd_asize,maxd_atype,maxd_aphase),        &
1029           lptr_asoa1_aer(maxd_asize,maxd_atype,maxd_aphase),    &
1030           lptr_asoa2_aer(maxd_asize,maxd_atype,maxd_aphase),    &
1031           lptr_asoa3_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1032           lptr_asoa4_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1033           lptr_bsoa1_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1034           lptr_bsoa2_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1035           lptr_bsoa3_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1036           lptr_bsoa4_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1038           lptr_orgpa_aer(maxd_asize,maxd_atype,maxd_aphase),      &
1039           lptr_ec_aer(maxd_asize,maxd_atype,maxd_aphase),         &
1040           lptr_p25_aer(maxd_asize,maxd_atype,maxd_aphase),        &
1041           lptr_anth_aer(maxd_asize,maxd_atype,maxd_aphase),       &
1042           lptr_cl_aer(maxd_asize,maxd_atype,maxd_aphase),         &
1043           lptr_na_aer(maxd_asize,maxd_atype,maxd_aphase),         &
1044           lptr_seas_aer(maxd_asize,maxd_atype,maxd_aphase),       &
1045           lptr_soil_aer(maxd_asize,maxd_atype,maxd_aphase)
1047         logical, save ::                     &
1048           do_cloudchem_aer(maxd_asize,maxd_atype)
1051 !   molecular weights (g/mol)
1052         real, parameter :: mw_so4_aer   = 96.066
1053         real, parameter :: mw_no3_aer   = 62.007
1054         real, parameter :: mw_nh4_aer   = 18.042
1055         real, parameter :: mw_oc_aer    = 250.0
1056         real, parameter :: mw_ec_aer    = 1.0
1057         real, parameter :: mw_oin_aer   = 1.0
1058         real, parameter :: mw_dust_aer  = 100.087
1059         real, parameter :: mw_seas_aer  = 58.440
1060         real, parameter :: mw_cl_aer    = 35.450
1061         real, parameter :: mw_na_aer    = 22.990
1062         real, parameter :: mw_water_aer = 18.016
1064 !   dry densities (g/cm3)
1065         real, parameter :: dens_so4_aer  = 1.80   ! = rhoso4
1066         real, parameter :: dens_no3_aer  = 1.80   ! = rhono3
1067         real, parameter :: dens_nh4_aer  = 1.80   ! = rhonh4
1068         real, parameter :: dens_oc_aer   = 1.5    ! = rhoorg ! changed from 1.0
1069         real, parameter :: dens_ec_aer   = 1.70
1070         real, parameter :: dens_dust_aer = 2.60  ! = rhosoil
1071         real, parameter :: dens_oin_aer  = 2.20  ! = rhoanth
1072         real, parameter :: dens_seas_aer = 2.20  ! = rhoseas
1073         real, parameter :: dens_cl_aer   = 2.20
1074         real, parameter :: dens_na_aer   = 2.20
1076 !   water density (g/cm3)
1077         real, parameter :: dens_water_aer  = 1.0
1079 !   hygroscopicity (dimensionless)
1080         real, parameter :: hygro_so4_aer  = 0.5
1081         real, parameter :: hygro_no3_aer  = 0.5
1082         real, parameter :: hygro_nh4_aer  = 0.5
1083         real, parameter :: hygro_oc_aer   = 0.14
1084         real, parameter :: hygro_ec_aer   = 1.e-6
1085         real, parameter :: hygro_oin_aer  = 0.14
1086         real, parameter :: hygro_dust_aer = 0.1
1087         real, parameter :: hygro_seas_aer = 1.16
1088         real, parameter :: hygro_cl_aer   = 1.16
1089         real, parameter :: hygro_na_aer   = 1.16
1091 ! table lookup of aerosol impaction/interception scavenging rates
1092         real dlndg_nimptblgrow
1093         integer nimptblgrow_mind, nimptblgrow_maxd
1094         parameter (nimptblgrow_mind=-14, nimptblgrow_maxd=24)
1095         real scavimptblnum(4, nimptblgrow_mind:nimptblgrow_maxd, maxd_asize, maxd_atype), &
1096              scavimptblvol(4, nimptblgrow_mind:nimptblgrow_maxd, maxd_asize, maxd_atype)
1098 !SAM 10/08 Gaussian quadrature constants for SOA_VBS deposition numerical integration
1099       INTEGER NGAUSdv
1100       PARAMETER( NGAUSdv = 7 )  ! Number of Gaussian Quadrature Points - constants defined in aerosols_sorgam_init
1101       REAL Y_GQ(NGAUSdv), WGAUS(NGAUSdv)
1103 !*****************************************************************
1104 !*                                                               *
1105 !*  end parameters and variables for aerosol-cloud interactions  *
1106 !*                                                               *
1107 !*****************************************************************
1110 END Module module_data_soa_vbs