updated top-level README and version_decl for V4.5 (#1847)
[WRF.git] / chem / module_data_sorgam_vbs.F
blob88bd0413662fa3a279c0f5c4153e18bc5218a833
1 MODULE module_data_sorgam_vbs
2 ! This module is based on module_data_soa_vbs.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       PARAMETER (laerdvc=39,lnonaerdvc=8+lspcv)
41       PARAMETER (l1ae=laerdvc+lnonaerdvc)
42       PARAMETER (laero=4,imodes=4,aspec=1)
43 !     LAERDVC  number of advected aerosol dynamic parameters for a given
44 !     component species
45 !ia     L1AE        advected parameters+non-advected parameters
46 !ia     LAERO       number of aerosol component species
47 !ia     imodes      number of aerosol modes
48 !ia     ASPEC       number of gas phase comp. that are added dynamically
49 !ia                 currently only sulfate (=1)
50 !bs
51 !bs * BS ** BS ** BS ** BS ** BS ** BS ** BS ** BS ** BS ** BS ** BS **
52 !bs
53       INTEGER aemiss
54       PARAMETER (aemiss=4)
55 !bs *  AEMISS      # of aerosol species with emissions link to gas phase
56 !bs                currently ECI, ECJ, BCI, BCJ
57  ! updated ldrog numbers for the new SOA mechanism
58       INTEGER, PARAMETER :: ldroga=6    ! anthropogenic: ALK4,ALK5,OLE1,OLE2,ARO1,ARO2
59       INTEGER, PARAMETER :: ldrogb=3    ! biogenic: ISOP,SESQ,TERP
60       INTEGER, PARAMETER :: ldrogr=1    ! for branching ratio
61       INTEGER, PARAMETER :: ldrog_vbs=ldroga+ldrogb+ldrogr ! I've renamed this parameter to separate from "ldrog" for MADE/SORGAM
63 !      INTEGER ldroga
64 !      PARAMETER (ldroga=11)
65 !      INTEGER ldrogb
66 !      PARAMETER (ldrogb=6)
67 !      INTEGER ldrog
68 !bs * LDROGA      # of anthropogenic organic aerosol precursor gases (DR
69 !bs * LDROGB      # of biogenic organic aerosol precursor gases (DROG)
70 !bs * LSPCV       # of condensable organic vapor interacting between gas
71 !bs               aerosol phase with SORGAM
72 !bs
73 !     param.inc stop
75 ! //////////////////////////////////////////////////////////////////////
76 ! FSB include file
78 ! *** declare and set flag for organic aerosol production method
79 ! *** Two method are available:
81 ! *** The method of Pandis,Harley, Cass, and Seinfeld, 1992,
82 !     Secondary aerosol formation and transport, Atmos. Environ., 26A,
83 !     pp 2453-2466
84 !     Bowman et al. Atmospheric Environment
85 !     Vol 29, pp 579-589, 1995.
86 ! *** and
87 ! *** The method of Odum, Hoffmann, Bowman, Collins, Flagen and
88 !     Seinfeld, 1996, Gas/particle partitioning and secondary organic ae
89 !     yields, Environ. Sci, Technol, 30, pp 2580-2585.
90                             ! 1 = Pandis et al.  1992 method is used
91       INTEGER orgaer
92                             ! 2 = Pankow 1994/Odum et al. 1996 method is
93 ! ***
94 ! switch for organic aerosol method         
95       PARAMETER (orgaer=2)
97 ! *** information about visibility variables
98 ! number of visibility variables    
99       INTEGER n_ae_vis_spc
100       PARAMETER (n_ae_vis_spc=2)
102 ! index for visual range in deciview             
103       INTEGER idcvw
104       PARAMETER (idcvw=1)
105 ! index for extinction [ 1/km ]                  
106       INTEGER ibext
107       PARAMETER (ibext=2)
109 ! *** set up indices for array  CBLK
111 ! index for Accumulation mode sulfate aerosol
112       INTEGER vso4aj
113       PARAMETER (vso4aj=1)
115 ! index for Aitken mode sulfate concentration
116       INTEGER vso4ai
117       PARAMETER (vso4ai=2)
119 ! index for Accumulation mode aerosol ammonium
120       INTEGER vnh4aj
121       PARAMETER (vnh4aj=3)
123 ! index for Aitken mode ammonium concentration
124       INTEGER vnh4ai
125       PARAMETER (vnh4ai=4)
127 ! index for Accumulation mode aerosol nitrate
128       INTEGER vno3aj
129       PARAMETER (vno3aj=5)
131 ! index for Aitken mode nitrate concentration
132       INTEGER vno3ai
133       PARAMETER (vno3ai=6)
135 ! index for Accumulation mode aerosol sodium
136       INTEGER vnaaj
137       PARAMETER (vnaaj=7)
139 ! index for Aitken mode sodium concentration
140       INTEGER vnaai
141       PARAMETER (vnaai=8)
143 ! index for Accumulation mode aerosol chloride
144       INTEGER vclaj
145       PARAMETER (vclaj=9)
147 ! index for Aitken mode chloride concentration
148       INTEGER vclai
149       PARAMETER (vclai=10)
151 ! I've changed the names and simplified
152 ! indices for accumulation and aitken modes of anthropogenic SOA
153       INTEGER, PARAMETER ::  vasoa1j=11
154       INTEGER, PARAMETER ::  vasoa1i=12
156       INTEGER, PARAMETER ::  vasoa2j=13
157       INTEGER, PARAMETER ::  vasoa2i=14
159       INTEGER, PARAMETER ::  vasoa3j=15
160       INTEGER, PARAMETER ::  vasoa3i=16
162       INTEGER, PARAMETER ::  vasoa4j=17
163       INTEGER, PARAMETER ::  vasoa4i=18
165 ! indices for accumulation and aitken modes of biogenic SOA
166       INTEGER, PARAMETER ::  vbsoa1j=19
167       INTEGER, PARAMETER ::  vbsoa1i=20
169       INTEGER, PARAMETER ::  vbsoa2j=21
170       INTEGER, PARAMETER ::  vbsoa2i=22
172       INTEGER, PARAMETER ::  vbsoa3j=23
173       INTEGER, PARAMETER ::  vbsoa3i=24
175       INTEGER, PARAMETER ::  vbsoa4j=25
176       INTEGER, PARAMETER ::  vbsoa4i=26
177 !------------------------------------------------------------------------------
179 ! index for Accumulation mode primary anthropogenic
180       INTEGER vorgpaj
181       PARAMETER (vorgpaj=27)
183 ! index for Aitken mode primary anthropogenic
184       INTEGER vorgpai
185       PARAMETER (vorgpai=28)
187 ! index for Accumulation mode aerosol elemen
188       INTEGER vecj
189       PARAMETER (vecj=29)
191 ! index for Aitken mode elemental carbon    
192       INTEGER veci
193       PARAMETER (veci=30)
195 ! index for Accumulation mode primary PM2.5 
196       INTEGER vp25aj
197       PARAMETER (vp25aj=31)
199 ! index for Aitken mode primary PM2.5 concentration
200       INTEGER vp25ai
201       PARAMETER (vp25ai=32)
203 ! index for coarse mode anthropogenic aerososol
204       INTEGER vantha
205       PARAMETER (vantha=33)
207 ! index for coarse mode marine aerosol concentration
208       INTEGER vseas
209       PARAMETER (vseas=34)
211 ! index for coarse mode soil-derived aerosol
212       INTEGER vsoila
213       PARAMETER (vsoila=35)
215 ! index for Aitken mode number              
216       INTEGER vnu0
217       PARAMETER (vnu0=36)
219 ! index for accum  mode number              
220       INTEGER vac0
221       PARAMETER (vac0=37)
223 ! index for coarse mode number              
224       INTEGER vcorn
225       PARAMETER (vcorn=38)
227 ! index for Accumulation mode aerosol water 
228       INTEGER vh2oaj
229       PARAMETER (vh2oaj=39)
231 ! index for Aitken mode aerosol water concentration
232       INTEGER vh2oai
233       PARAMETER (vh2oai=40)
235 ! index for Aitken mode 3'rd moment         
236       INTEGER vnu3
237       PARAMETER (vnu3=41)
239 ! index for Accumulation mode 3'rd moment   
240       INTEGER vac3
241       PARAMETER (vac3=42)
243 ! index for coarse mode 3rd moment          
244       INTEGER vcor3
245       PARAMETER (vcor3=43)
247 ! index for sulfuric acid vapor concentration
248       INTEGER vsulf
249       PARAMETER (vsulf=44)
251 ! index for nitric acid vapor concentration
252       INTEGER vhno3
253       PARAMETER (vhno3=45)
255 ! index for ammonia gas concentration
256       INTEGER vnh3
257       PARAMETER (vnh3=46)
259 ! index for HCL gas concentration
260       INTEGER vhcl
261       PARAMETER (vhcl=47)
263 INTEGER, PARAMETER :: vcvasoa1=48
264 INTEGER, PARAMETER :: vcvasoa2=49
265 INTEGER, PARAMETER :: vcvasoa3=50
266 INTEGER, PARAMETER :: vcvasoa4=51
267 INTEGER, PARAMETER :: vcvbsoa1=52
268 INTEGER, PARAMETER :: vcvbsoa2=53
269 INTEGER, PARAMETER :: vcvbsoa3=54
270 INTEGER, PARAMETER :: vcvbsoa4=55
271 !-----------------------------------------------------------------------------
273 ! *** set up species dimension and indices for sedimentation
274 !     velocity array VSED
276 ! number of sedimentation velocities         
277       INTEGER naspcssed
278       PARAMETER (naspcssed=6)
280 ! index for Aitken mode number                  
281       INTEGER vsnnuc
282       PARAMETER (vsnnuc=1)
284 ! index for Accumulation mode number            
285       INTEGER vsnacc
286       PARAMETER (vsnacc=2)
288 ! index for coarse mode number                  
289       INTEGER vsncor
290       PARAMETER (vsncor=3)
292 ! index for Aitken mode mass                     
293       INTEGER vsmnuc
294       PARAMETER (vsmnuc=4)
296 ! index for accumulation mode mass               
297       INTEGER vsmacc
298       PARAMETER (vsmacc=5)
300 ! index for coarse mass                         
301       INTEGER vsmcor
302       PARAMETER (vsmcor=6)
304 ! *** set up species dimension and indices for deposition
305 !     velocity array VDEP
307 ! number of deposition velocities            
308       INTEGER naspcsdep
309       PARAMETER (naspcsdep=7)
311 ! index for Aitken mode number                  
312       INTEGER vdnnuc
313       PARAMETER (vdnnuc=1)
315 ! index for accumulation mode number            
316       INTEGER vdnacc
317       PARAMETER (vdnacc=2)
319 ! index for coarse mode number                  
320       INTEGER vdncor
321       PARAMETER (vdncor=3)
323 ! index for Aitken mode mass                    
324       INTEGER vdmnuc
325       PARAMETER (vdmnuc=4)
327 ! index for accumulation mode                   
328       INTEGER vdmacc
329       PARAMETER (vdmacc=5)
331 ! index for fine mode mass (Aitken + accumulation)
332       INTEGER vdmfine
333       PARAMETER (vdmfine=6)
335 ! index for coarse mode mass                    
336       INTEGER vdmcor
337       PARAMETER (vdmcor=7)
339 ! SOA precursors + OH, O3, NO3
340 ! anthropogenic
341 INTEGER, PARAMETER :: palk4=1
342 INTEGER, PARAMETER :: palk5=2
343 INTEGER, PARAMETER :: pole1=3
344 INTEGER, PARAMETER :: pole2=4
345 INTEGER, PARAMETER :: paro1=5
346 INTEGER, PARAMETER :: paro2=6
348 ! biogenic
349 INTEGER, PARAMETER :: pisop=7
350 INTEGER, PARAMETER :: pterp=8
351 INTEGER, PARAMETER :: psesq=9
353 ! for branching
354 INTEGER, PARAMETER :: pbrch=10
356  ! new indices
357 INTEGER, PARAMETER :: pasoa1=1
358 INTEGER, PARAMETER :: pasoa2=2
359 INTEGER, PARAMETER :: pasoa3=3
360 INTEGER, PARAMETER :: pasoa4=4
361       
362 INTEGER, PARAMETER :: pbsoa1=5
363 INTEGER, PARAMETER :: pbsoa2=6
364 INTEGER, PARAMETER :: pbsoa3=7
365 INTEGER, PARAMETER :: pbsoa4=8
366 !-----------------------------------------------
369 !bs * end of AERO_SOA.EXT *
372 ! *** include file for aerosol routines
375 !....................................................................
377 !  CONTAINS: Fundamental constants for air quality modeling
379 !  DEPENDENT UPON:  none
381 !  REVISION HISTORY:
383 !    Adapted 6/92 by CJC from ROM's PI.EXT.
385 !    Revised 3/1/93 John McHenry to include constants needed by
386 !    LCM aqueous chemistry
387 !    Revised 9/93 by John McHenry to include additional constants
388 !    needed for FMEM clouds and aqueous chemistry
390 !    Revised 3/4/96 by Dr. Francis S. Binkowski to reflect current
391 !    Models3 view that MKS units should be used wherever possible,
392 !    and that sources be documentated. Some variables have been added
393 !    names changed, and values revised.
395 !    Revised 3/7/96 to have universal gas constant input and compute
396 !    gas constant is chemical form. TWOPI is now calculated rather than
398 !    Revised 3/13/96 to group declarations and parameter statements.
400 !    Revised 9/13/96 to include more physical constants.
401 !    Revised 12/24/96 eliminate silly EPSILON, AMISS
403 !    Revised 1/06/97 to eliminate most derived constants
404 !    10/12/11- Modified to use with soa_vbs, by Ravan Ahmadov
406 !    Revised 10/08/14-Modified to use with CB05-MADE/VBS, by Kai Wang
408 ! FSB REFERENCES:
410 !      CRC76,        CRC Handbook of Chemistry and Physics (76th Ed),
411 !                     CRC Press, 1995
412 !      Hobbs, P.V.   Basic Physical Chemistry for the Atmospheric Scien
413 !                     Cambridge Univ. Press, 206 pp, 1995.
414 !      Snyder, J.P., Map Projections-A Working Manual, U.S. Geological
415 !                     Paper 1395 U.S.GPO, Washington, DC, 1987.
416 !      Stull, R. B., An Introduction to Bounday Layer Meteorology, Klu
417 !                     Dordrecht, 1988
419 ! Geometric Constants:
421       REAL*8 & ! PI (single precision 3.141593)
422         pirs
423       PARAMETER (pirs=3.14159265358979324)
424 !      REAL     PIRS ! PI (single precision 3.141593)
425 !      PARAMETER ( PIRS = 3.141593 )
426 ! Fundamental Constants: ( Source: CRC76, pp 1-1 to 1-6)
428 ! Avogadro's Constant [ 1/mol ]
429       REAL avo
430       PARAMETER (avo=6.0221367E23)
432 ! universal gas constant [ J/mol-K ]
433       REAL rgasuniv
434       PARAMETER (rgasuniv=8.314510)
436 ! standard atmosphere  [ Pa ]
437       REAL stdatmpa
438       PARAMETER (stdatmpa=101325.0)
440 ! Standard Temperature [ K ]
441       REAL stdtemp
442       PARAMETER (stdtemp=273.15)
444 ! Stefan-Boltzmann [ W/(m**2 K**4) ]
445       REAL stfblz
446       PARAMETER (stfblz=5.67051E-8)
449 ! mean gravitational acceleration [ m/sec**2 ]
450       REAL grav
451       PARAMETER (grav=9.80622)
452 ! FSB Non MKS qualtities:
454 ! Molar volume at STP [ L/mol ] Non MKS units
455       REAL molvol
456       PARAMETER (molvol=22.41410)
459 ! Atmospheric Constants:
461 ! FSB                     78.06%  N2, 21% O2 and 0.943% A on a mole
462       REAL mwair
463                         ! fraction basis. ( Source : Hobbs, 1995) pp 69-
464 ! mean molecular weight for dry air [ g/mol ]
465       PARAMETER (mwair=28.9628)
467 ! dry-air gas constant [ J / kg-K ]
468       REAL rdgas
469       PARAMETER (rdgas=1.0E3*rgasuniv/mwair)
471 !  3*PI
472       REAL threepi
473       PARAMETER (threepi=3.0*pirs)
475 !  6/PI
476       REAL f6dpi
477       PARAMETER (f6dpi=6.0/pirs)
479 !  1.0e9 * 6/PIRS
480       REAL f6dpi9
481       PARAMETER (f6dpi9=1.0E9*f6dpi)
483 ! 1.0e-9 * 6/PIRS
484       REAL f6dpim9
485       PARAMETER (f6dpim9=1.0E-9*f6dpi)
487 !  SQRT( PI )
488       REAL sqrtpi
489       PARAMETER (sqrtpi=1.7724539)
491 !  SQRT( 2 )
492       REAL sqrt2
493       PARAMETER (sqrt2=1.4142135623731)
495 !  ln( sqrt( 2 ) )
496       REAL lgsqt2
497       PARAMETER (lgsqt2=0.34657359027997)
499 !  1/ln( sqrt( 2 ) )
500       REAL dlgsqt2
501       PARAMETER (dlgsqt2=1.0/lgsqt2)
503 !  1/3
504       REAL one3
505       PARAMETER (one3=1.0/3.0)
507 !  2/3
508       REAL two3
509       PARAMETER (two3=2.0/3.0)
512 ! *** physical constants:
514 ! Boltzmann's Constant [ J / K ]
515       REAL boltz
516       PARAMETER (boltz=rgasuniv/avo)
519 ! *** component densities [ kg/m**3 ] :
522 !  bulk density of aerosol sulfate
523       REAL rhoso4
524       PARAMETER (rhoso4=1.8E3)
526 !  bulk density of aerosol ammonium
527       REAL rhonh4
528       PARAMETER (rhonh4=1.8E3)
530 ! bulk density of aerosol nitrate
531       REAL rhono3
532       PARAMETER (rhono3=1.8E3)
534 !  bulk density of aerosol water
535       REAL rhoh2o
536       PARAMETER (rhoh2o=1.0E3)
538 ! bulk density for aerosol organics
539       REAL rhoorg
540       PARAMETER (rhoorg=1.0E3)
542 ! bulk density for aerosol soil dust
543       REAL rhosoil
544       PARAMETER (rhosoil=2.6E3)
546 ! bulk density for marine aerosol
547       REAL rhoseas
548       PARAMETER (rhoseas=2.2E3)
550 ! bulk density for anthropogenic aerosol
551       REAL rhoanth
552       PARAMETER (rhoanth=2.2E3)
554 ! bulk density of aerosol sodium
555       REAL rhona
556       PARAMETER (rhona=2.2E3)
558 ! bulk density of aerosol chloride
559       REAL rhocl
560       PARAMETER (rhocl=2.2E3)
562 ! *** Factors for converting aerosol mass concentration [ ug m**-3] to
563 !         to 3rd moment concentration [ m**3 m^-3]
565       REAL so4fac
566       PARAMETER (so4fac=f6dpim9/rhoso4)
568       REAL nh4fac
569       PARAMETER (nh4fac=f6dpim9/rhonh4)
571       REAL h2ofac
572       PARAMETER (h2ofac=f6dpim9/rhoh2o)
574       REAL no3fac
575       PARAMETER (no3fac=f6dpim9/rhono3)
577       REAL orgfac
578       PARAMETER (orgfac=f6dpim9/rhoorg)
580       REAL soilfac
581       PARAMETER (soilfac=f6dpim9/rhosoil)
583       REAL seasfac
584       PARAMETER (seasfac=f6dpim9/rhoseas)
586       REAL anthfac
587       PARAMETER (anthfac=f6dpim9/rhoanth)
589       REAL nafac
590       PARAMETER (nafac=f6dpim9/rhona)
592       REAL clfac
593       PARAMETER (clfac=f6dpim9/rhocl)
595 !  starting standard surface pressure [ Pa ]  
596       REAL pss0
597       PARAMETER (pss0=101325.0)
599 !  starting standard surface temperature [ K ]
600       REAL tss0
601       PARAMETER (tss0=288.15)
603 !  initial sigma-G for nucleimode                 
604       REAL sginin
605       PARAMETER (sginin=1.70)
607 !  initial sigma-G for accumulation mode          
608       REAL sginia
609       PARAMETER (sginia=2.00)
611 ! initial sigma-G for coarse mode               
612       REAL sginic
613       PARAMETER (sginic=2.5)
615 !  initial mean diameter for nuclei mode [ m ]    
616       REAL dginin
617       PARAMETER (dginin=0.01E-6)
619 !  initial mean diameter for accumulation mode [ m ]
620       REAL dginia
621       PARAMETER (dginia=0.07E-6)
623 ! initial mean diameter for coarse mode [ m ]  
624       REAL dginic
625       PARAMETER (dginic=1.0E-6)
627 !................   end   AERO3box.EXT   ...............................
628 !///////////////////////////////////////////////////////////////////////
630 !     LOGICAL diagnostics
631 ! *** Scalar variables for fixed standard deviations.
633 ! Flag for writing diagnostics to file       
634 ! nuclei mode exp( log^2( sigmag )/8 )  
635       REAL en1
636 ! accumulation mode exp( log^2( sigmag )
637       REAL ea1
639       REAL ec1
640 ! coarse mode exp( log^2( sigmag )/8 )  
641 ! nuclei        **4                    
642       REAL esn04
643 ! accumulation                         
644       REAL esa04
646       REAL esc04
647 ! coarse                               
648 ! nuclei        **5                    
649       REAL esn05
651       REAL esa05
652 ! accumulation                         
653 ! nuclei        **8                    
654       REAL esn08
655 ! accumulation                         
656       REAL esa08
658       REAL esc08
659 ! coarse                               
660 ! nuclei        **9                    
661       REAL esn09
663       REAL esa09
664 ! accumulation                         
665 ! nuclei        **12                   
666       REAL esn12
667 ! accumulation                         
668       REAL esa12
670       REAL esc12
671 ! coarse mode                          
672 ! nuclei        **16                   
673       REAL esn16
674 ! accumulation                         
675       REAL esa16
677       REAL esc16
678 ! coarse                               
679 ! nuclei        **20                   
680       REAL esn20
681 ! accumulation                         
682       REAL esa20
684       REAL esc20
685 ! coarse                               
686 ! nuclei        **25                   
687       REAL esn25
689       REAL esa25
690 ! accumulation                         
691 ! nuclei        **24                   
692       REAL esn24
693 ! accumulation                         
694       REAL esa24
696       REAL esc24
697 ! coarse                               
698 ! nuclei        **28                   
699       REAL esn28
700 ! accumulation                         
701       REAL esa28
703       REAL esc28
704 ! coarse                               
705 ! nuclei        **32                   
706       REAL esn32
707 ! accumulation                         
708       REAL esa32
710       REAL esc32
711 ! coarese                              
712 ! nuclei        **36                   
713       REAL esn36
714 ! accumulation                         
715       REAL esa36
717       REAL esc36
718 ! coarse                               
719 ! nuclei        **49                   
720       REAL esn49
722       REAL esa49
723 ! accumulation                         
724 ! nuclei        **52                   
725       REAL esn52
727       REAL esa52
728 ! accumulation                         
729 ! nuclei        **64                   
730       REAL esn64
731 ! accumulation                         
732       REAL esa64
734       REAL esc64
735 ! coarse                               
737       REAL esn100
738 ! nuclei        **100                  
739 ! nuclei        **(-20)                
740       REAL esnm20
741 ! accumulation                         
742       REAL esam20
744       REAL escm20
745 ! coarse                               
746 ! nuclei        **(-32)                
747       REAL esnm32
748 ! accumulation                         
749       REAL esam32
751       REAL escm32
752 ! coarse                               
753 ! log(sginin)                           
754       REAL xxlsgn
755 ! log(sginia)                           
756       REAL xxlsga
758       REAL xxlsgc
759 ! log(sginic )                          
760 ! log(sginin ) ** 2                           
761       REAL l2sginin
762 ! log(sginia ) ** 2                           
763       REAL l2sginia
765       REAL l2sginic
767 ! *** set up COMMON blocks for esg's:
769 ! log(sginic ) ** 2
771 ! *** SET NUCLEATION FLAG:
773                             ! INUCL = 0, Kerminen & Wexler Mechanism
774       INTEGER inucl
775                             ! INUCL = 1, Youngblood and Kreidenweis mech
776                             ! INUCL = 2, Kulmala et al. mechanism
777 ! Flag for Choice of nucleation Mechanism   
778       PARAMETER (inucl=2)
780 ! *** Set flag for sedimentation velocities:
782       LOGICAL icoarse
783       PARAMETER (icoarse=.FALSE.) ! *** END AERO_INTERNAL.EXT
784 ! *** Diameters and standard deviations for emissions
785 !     the diameters are the volume (mass) geometric mean diameters
787 ! *** Aitken mode:
788 ! special factor to compute mass transfer           
789       REAL dgvem_i
790       PARAMETER (dgvem_i=0.03E-6) ! [ m ]                            
791       REAL sgem_i
792       PARAMETER (sgem_i=1.7)
794 ! *** Accumulation mode:
795       REAL dgvem_j
796       PARAMETER (dgvem_j=0.3E-6) ! [ m ]                             
797       REAL sgem_j
798       PARAMETER (sgem_j=2.0)
800 ! *** Coarse mode
801       REAL dgvem_c
802       PARAMETER (dgvem_c=6.0E-6) ! [ m ] <<< Corrected 11/19/97      
803       REAL sgem_c
804       PARAMETER (sgem_c=2.2)
806 ! *** factors for getting number emissions rate from mass emissions rate
807 ! Aitken mode                                       
808       REAL factnumn
809 ! accumulation mode                                 
810       REAL factnuma
812       REAL factnumc
813 ! coarse mode                                       
814       REAL facatkn_min, facacc_min
815       PARAMETER (facatkn_min=0.04,facacc_min=1.0-facatkn_min)
816       REAL xxm3
817       REAL, PARAMETER ::  conmin = 1.E-16
818       REAL, PARAMETER ::  epsilc = 1.E-16
819 ! [ ug/m**3 ] ! changed 1/6/98 
820       REAL*8 & ! factor to set minimum for Aitken mode number  
821         nummin_i
822       REAL*8 & ! factor to set minimum for accumulation mode nu
823         nummin_j
824       REAL*8 & 
825         nummin_c
826 ! factor to set minimum for coarse mode number  
828 !bs      REAL ALPHSULF ! Accommodation coefficient for sulfuric acid
829 !bs      PARAMETER ( ALPHSULF = 0.05 ) ! my be set to one in future
831 !bs      REAL DIFFSULF ! molecular diffusivity for sulfuric acid [ m**2
832 !bs      PARAMETER( DIFFSULF = 0.08E-4 ) ! may be changed in future
834 !bs * 23/03/99 updates of ALPHSULF and DIFFSULF adopted fro new code fro
835 !bs * DIFFSULF is calculated from Reid, Prausnitz, and Poling, The prope
836 !bs * of gases and liquids, 4th edition, McGraw-Hill, 1987, pp 587-588.
837 !bs * Equation (11-4.4) was used.
838 !bs * The value is at T = 273.16 K and P = 1.01325E05 Pa
839 !bs * Temperature dependence is included for DIFFSULF via DIFFCORR (see
841 ! Accommodation coefficient for sulfuric
842       REAL alphsulf
843       PARAMETER (alphsulf=1.0) 
844 !bs updated from code of FSB         
845 ! molecular weight for sulfuric acid [ kg/mole ] MKS 
846       REAL mwh2so4
847       PARAMETER (mwh2so4=98.07354E-3) 
848 !cia corrected error 24/11/97
849 ! molecular diffusivity for sulfuric acid [ m**2 /se
850       REAL diffsulf
851       PARAMETER (diffsulf=9.362223E-06) 
852 !bs updated from code of FSB 
853 !bs Accomodation coefficient for organic
854       REAL alphaorg
855       PARAMETER (alphaorg=1.0)                                    !bs Kleeman et al. '99 propose alpha
856 !bs Bowman et al. '97 uses alpha = 1.
857 !bs mean molecular weight of organics [k
858       REAL mworg
859       PARAMETER (mworg=175.0E-03)
861 !bs * DIFFORG is calculated from the same formula as DIFFSULF.
862 !bs * An average elemental composition of C=8, O=3, N=1, H=17 is asuumed
863 !bs * to calculate DIFFORG at T = 273.16K and  P = 1.01325E05 Pa.
864 !bs * Temperature dependence is included below.
865 !bs molecular diffusivity for organics [
866       REAL difforg
867       PARAMETER (difforg=5.151174E-06)
868 ! *** CCONC is the factor for near-continuum condensation.
869 ! ccofm * sqrt( ta )                    
870       REAL cconc
871       PARAMETER (cconc=2.0*pirs*diffsulf) 
872 !bs * factor for NC condensation for organics
873 ! [ m**2 / sec ]       
874       REAL cconc_org
875       PARAMETER (cconc_org=2.0*pirs*difforg) 
876 ! [ m**2 / sec ]    
877 !bs analogue to CCOFM but for organics  
878       REAL ccofm_org
879 ! FSB  CCOFM is  the accommodation coefficient
880 !      times the mean molecular velocity for h2so4 without the temperatu
881 !      after some algebra
883 !bs CCOFM_ORG * sqrt(TA)                
884 ! set to a value below                  
885       REAL ccofm
886 ! minimum aerosol sulfate concentration          
887       REAL aeroconcmin
888       PARAMETER (aeroconcmin=0.0001) 
890 !*******************************************************************
891 !*                                                                 *
892 !*  start parameters and variables for aerosol-cloud interactions  *
893 !*                                                                 *
894 !*******************************************************************
896 !   maxd_atype = maximum allowable number of aerosol types
897 !   maxd_asize = maximum allowable number of aerosol size bins
898 !   maxd_acomp = maximum allowable number of chemical components
899 !       in each aerosol size bin
900 !   maxd_aphase = maximum allowable number of aerosol phases (gas, cloud, ice, rain, ...)
902 !   ntype_aer = number of aerosol types
903 !   nsize_aer(t) = number of aerosol size bins for aerosol type t. each bin w/ same set of components
904 !   nphase_aer = number of aerosol phases
906 !   msectional - if positive, moving-center sectional code is utilized,
907 !       and each mode is actually a section.
908 !   maerosolincw - if positive, both unactivated/interstitial and activated
909 !       aerosol species are simulated.  if zero/negative, only the
910 !       unactivated are simulated.
912 !   ncomp_aer(t) = number of chemical components for aerosol type t
913 !   ncomp_aer_nontracer(t) = number of "non-tracer" chemical components while in gchm code
914 !   mastercompptr_aer(c,t) = mastercomp type/i.d. for chemical component c
915 !       (1=sulfate, others to be defined) and aerosol type t.
916 !   massptr_aer(c,s,t,p) = gchm r-array index for the mixing ratio
917 !       (moles-x/mole-air) for chemical component c in size bin s for type t and phase p
919 !   waterptr_aer(s,t) = mixing ratio (moles-water/mole-air) for water
920 !       associated with aerosol size bin s and type t
921 !   hygroptr_aer(s,t) = gchm r-array index for the bulk hygroscopicity of the size bin and type
922 !   numptr_aer(s,t,p) = gchm r-array index for the number mixing ratio
923 !       (particles/mole-air) for aerosol size bin s, type t, and phase p
924 !       If zero or negative, then number is not being simulated.
926 !   mprognum_aer(s,t,p) - if positive, number mixing-ratio for size s, type t,
927 !       and phase p will be prognosed.  Otherwise, no.
929 !   ntot_mastercomp_aer = number of aerosol chemical components defined
930 !   dens_mastercomp_aer(mc) = dry density (g/cm^3) of aerosol master chemical component type c
931 !   mw_mastercomp_aer(mc) = molecular weight of aerosol master chemical component type mc
932 !   name_mastercomp_aer(mc) = name of aerosol master chemical component type mc
933 !   mc=mastercompptr_aer(c,t)
934 !   dens_aer(c,t) = dry density (g/cm^3) of aerosol chemical component type c and type t
935 !   mw_aer(c,t) = molecular weight of aerosol chemical component type c and type t
936 !   name_aer(c,t) = name of aerosol chemical component type c and type t
938 !   lptr_so4_aer(s,t,p) = gchm r-array index for the
939 !       mixing ratio for sulfate associated with aerosol size bin s, type t, and phase p
940 !   (similar for msa, oc, bc, nacl, dust)
942 !-----------------------------------------------------------------------
944 !   volumcen_sect(s,t)= volume (cm^3) at center of section m
945 !   volumlo_sect(s,t) = volume (cm^3) at lower boundary of section m
946 !   volumhi_sect(s,t) = volume (cm^3) at upper boundary of section m
948 !   dlo_sect(s,t) = diameter (cm) at lower boundary of section m
949 !   dhi_sect(s,t) = diameter (cm) at upper boundary of section m
950 !   dcen_sect(s,t) = volume arithmetic-mean diameter (cm) of section m
951 !       (corresponds to volumcen_sect == 0.5*(volumlo_sect + volumhi_sect)
953 !-----------------------------------------------------------------------
954 !   nov-04 sg ! replaced amode with aer and expanded aerosol dimension to include type and phase
956         integer, parameter :: maxd_atype = 2
957         integer, parameter :: maxd_asize = 2
958         integer, parameter :: maxd_acomp = 19
959         integer, parameter :: maxd_aphase = 2
960         integer, save :: ai_phase ! interstitial phase of aerosol
961         integer, save :: cw_phase ! cloud water phase of aerosol
962         integer, save :: ci_phase ! cloud ice  phase of aerosol
963         integer, save :: cr_phase ! rain  phase of aerosol
964         integer, save :: cs_phase ! snow  phase of aerosol
965         integer, save :: cg_phase ! graupel phase of aerosol
967         integer, save :: ntype_aer = 0 ! number of types
968         integer, save :: ntot_mastercomp_aer = 0 ! number of master components
969         integer, save :: nphase_aer = 0 ! number of phases
971         integer, save ::   &
972           msectional, maerosolincw,   &
973           nsize_aer( maxd_atype ),   & ! number of size bins
974           ncomp_aer( maxd_atype ),   & ! number of chemical components
975           ncomp_aer_nontracer( maxd_atype ),   &
976           mastercompptr_aer(maxd_acomp, maxd_atype), &   !  mastercomp index
977           massptr_aer( maxd_acomp, maxd_asize, maxd_atype, maxd_aphase ), & ! index for mixing ratio
978           waterptr_aer( maxd_asize, maxd_atype ), & ! index for aerosol water
979           hygroptr_aer( maxd_asize, maxd_atype ), & ! index for aerosol hygroscopicity
980           numptr_aer( maxd_asize, maxd_atype, maxd_aphase ), & ! index for the number mixing ratio
981           mprognum_aer(maxd_asize,maxd_atype,maxd_aphase)
983         real, save ::   &
984           dens_aer( maxd_acomp, maxd_atype ),   &
985           dens_mastercomp_aer( maxd_acomp ),   &
986           mw_mastercomp_aer( maxd_acomp ), &
987           mw_aer( maxd_acomp, maxd_atype ),  &
988           hygro_mastercomp_aer( maxd_acomp ), &
989           hygro_aer( maxd_acomp, maxd_atype )
990         character*10, save ::   &
991           name_mastercomp_aer( maxd_acomp ), &
992           name_aer( maxd_acomp, maxd_atype )
994         real, save ::   &
995           volumcen_sect( maxd_asize, maxd_atype ),   &
996           volumlo_sect( maxd_asize, maxd_atype ),   &
997           volumhi_sect( maxd_asize, maxd_atype ),   &
998           dcen_sect( maxd_asize, maxd_atype ),   &
999           dlo_sect( maxd_asize, maxd_atype ),   &
1000           dhi_sect( maxd_asize, maxd_atype ),   &
1001           sigmag_aer(maxd_asize, maxd_atype)
1003         integer, save ::                     &
1004           lptr_so4_aer(maxd_asize,maxd_atype,maxd_aphase),        &
1005           lptr_nh4_aer(maxd_asize,maxd_atype,maxd_aphase),        &
1006           lptr_no3_aer(maxd_asize,maxd_atype,maxd_aphase),        &
1008           lptr_asoa1_aer(maxd_asize,maxd_atype,maxd_aphase),    &
1009           lptr_asoa2_aer(maxd_asize,maxd_atype,maxd_aphase),    &
1010           lptr_asoa3_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1011           lptr_asoa4_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1012           lptr_bsoa1_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1013           lptr_bsoa2_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1014           lptr_bsoa3_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1015           lptr_bsoa4_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1017 !         lptr_orgaro1_aer(maxd_asize,maxd_atype,maxd_aphase),    &
1018 !         lptr_orgaro2_aer(maxd_asize,maxd_atype,maxd_aphase),    &
1019 !         lptr_orgalk_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1020 !         lptr_orgole_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1021 !         lptr_orgba1_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1022 !         lptr_orgba2_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1023 !         lptr_orgba3_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1024 !         lptr_orgba4_aer(maxd_asize,maxd_atype,maxd_aphase),     &
1026           lptr_orgpa_aer(maxd_asize,maxd_atype,maxd_aphase),      &
1027           lptr_ec_aer(maxd_asize,maxd_atype,maxd_aphase),         &
1028           lptr_p25_aer(maxd_asize,maxd_atype,maxd_aphase),        &
1029           lptr_anth_aer(maxd_asize,maxd_atype,maxd_aphase),       &
1030           lptr_cl_aer(maxd_asize,maxd_atype,maxd_aphase),         &
1031           lptr_na_aer(maxd_asize,maxd_atype,maxd_aphase),         &
1032           lptr_seas_aer(maxd_asize,maxd_atype,maxd_aphase),       &
1033           lptr_soil_aer(maxd_asize,maxd_atype,maxd_aphase)
1035         logical, save ::                     &
1036           do_cloudchem_aer(maxd_asize,maxd_atype)
1039 !   molecular weights (g/mol)
1040         real, parameter :: mw_so4_aer   = 96.066
1041         real, parameter :: mw_no3_aer   = 62.007
1042         real, parameter :: mw_nh4_aer   = 18.042
1043         real, parameter :: mw_oc_aer    = 250.0
1044         real, parameter :: mw_ec_aer    = 1.0
1045         real, parameter :: mw_oin_aer   = 1.0
1046         real, parameter :: mw_dust_aer  = 100.087
1047         real, parameter :: mw_seas_aer  = 58.440
1048         real, parameter :: mw_cl_aer    = 35.450
1049         real, parameter :: mw_na_aer    = 22.990
1050         real, parameter :: mw_water_aer = 18.016
1052 !   dry densities (g/cm3)
1053         real, parameter :: dens_so4_aer  = 1.80   ! = rhoso4
1054         real, parameter :: dens_no3_aer  = 1.80   ! = rhono3
1055         real, parameter :: dens_nh4_aer  = 1.80   ! = rhonh4
1056         real, parameter :: dens_oc_aer   = 1.5    ! = rhoorg ! changed from 1.0
1057         real, parameter :: dens_ec_aer   = 1.70
1058         real, parameter :: dens_dust_aer = 2.60  ! = rhosoil
1059         real, parameter :: dens_oin_aer  = 2.20  ! = rhoanth
1060         real, parameter :: dens_seas_aer = 2.20  ! = rhoseas
1061         real, parameter :: dens_cl_aer   = 2.20
1062         real, parameter :: dens_na_aer   = 2.20
1064 !   water density (g/cm3)
1065         real, parameter :: dens_water_aer  = 1.0
1067 !   hygroscopicity (dimensionless)
1068         real, parameter :: hygro_so4_aer  = 0.5
1069         real, parameter :: hygro_no3_aer  = 0.5
1070         real, parameter :: hygro_nh4_aer  = 0.5
1071         real, parameter :: hygro_oc_aer   = 0.14
1072         real, parameter :: hygro_ec_aer   = 1.e-6
1073         real, parameter :: hygro_oin_aer  = 0.14
1074         real, parameter :: hygro_dust_aer = 0.1
1075         real, parameter :: hygro_seas_aer = 1.16
1076         real, parameter :: hygro_cl_aer   = 1.16
1077         real, parameter :: hygro_na_aer   = 1.16
1079 ! table lookup of aerosol impaction/interception scavenging rates
1080         real dlndg_nimptblgrow
1081         integer nimptblgrow_mind, nimptblgrow_maxd
1082         parameter (nimptblgrow_mind=-14, nimptblgrow_maxd=24)
1083         real scavimptblnum(4, nimptblgrow_mind:nimptblgrow_maxd, maxd_asize, maxd_atype), &
1084              scavimptblvol(4, nimptblgrow_mind:nimptblgrow_maxd, maxd_asize, maxd_atype)
1086 !SAM 10/08 Gaussian quadrature constants for SOA_VBS deposition numerical integration
1087       INTEGER NGAUSdv
1088       PARAMETER( NGAUSdv = 7 )  ! Number of Gaussian Quadrature Points - constants defined in aerosols_sorgam_init
1089       REAL Y_GQ(NGAUSdv), WGAUS(NGAUSdv)
1091 !*****************************************************************
1092 !*                                                               *
1093 !*  end parameters and variables for aerosol-cloud interactions  *
1094 !*                                                               *
1095 !*****************************************************************
1098 END Module module_data_sorgam_vbs