Update version info for release v4.6.1 (#2122)
[WRF.git] / chem / aerorate_so2.F
blob0bddd92c66179f9da7098cdd81aca226574074d9
1 !*********************************************************************** 
2       SUBROUTINE AERORATE_SO2( BTEMP, BPRESS, RTDAT_AE ) 
3 !*********************************************************************** 
5       USE AERODATA
6       USE HETAERO
7 !      USE CONST_MADRID              !CMAQ constants
9       IMPLICIT NONE
11 !...........  ARGUMENTS and their descriptions 
12       REAL BTEMP     ! in degK 
13       REAL BPRESS    ! in Pa
14       REAL RTDAT_AE ( NRXNAERO )  ! heterogeneous reaction rate constant
15                                   ! first-order (if no reactant specified)
16                                   ! second-order (if reactant specified)
18 ! Local variables 
20       INTEGER :: INASEC, IRXN  ! loop variables
22       REAL VSP                  ! mean molecular speed (m/s) 
23       REAL DG                   ! gas-phase moleular diffusion 
24                                 ! coefficient (m2/s) 
25       REAL, SAVE :: GAMMA( NRXNAERO )    ! reaction probability
27       REAL RS_TOT               ! first order heterogeneous reaction 
28                                 ! rate constant (1/s) over the size distribution 
29       REAL RS                   ! first order heterogeneous reaction
30                                 ! rate constant (1/s) for each size section
31       REAL TOTMA                ! Total particle mass concentration, ug/m3 
32       REAL RCL                  ! mean radius of exch size section, in meter
33       REAL*8      PI ! pi (single precision 3.141593)
34       PARAMETER ( PI = 3.14159265358979324 )
36       LOGICAL, SAVE :: FIRSTIME = .TRUE.
38 !*********************************************************************** 
39 !  begin body of main program 
41       IF ( IAERORATE == 0 ) RETURN  ! Turn off gas-aerosol 
42                                     ! heterogeneous reactions 
43       IF ( FIRSTIME ) THEN
45          FIRSTIME = .FALSE.
47 ! Assign the reaction probability
48 ! according to Jacob, 2000, Atmos. Environ, 34, 2131-2159
49 ! NGAMMA is assigned in module HETAERO
50 ! NGAMMA = 1 Using the recommended median value
51 ! NGAMMA = 2 Using the low bound value
52 ! NGAMMA = 3 Using the high bound value
54          IF ( NGAMMA == 1 ) THEN        !  Using the median value
55             GAMMA( ISO2 )  = 1.0E-4
57          ELSE IF ( NGAMMA == 2 ) THEN   !  Using the low bound value
58             GAMMA( ISO2 )  = 1.0E-5
60          ELSE IF ( NGAMMA == 3 ) THEN   !  Using the high bound value
61             GAMMA( ISO2 )  = 0.1
62          END IF
64       END IF  ! If first time
66 ! Calculate total aerosol conc., total surface area, and heterogeneous
67 ! loss rates
69       DO INASEC  =  1,  NASECT
71          TOTMA = 0.0
72 ! Following loop is deactivated
73 ! Temporarily use input PM concentrations
74 !         DO J = 1, NASPEC
75 !            TOTMA = TOTMA + PMCONC( J, INASEC )
76 !         END DO
78          TOTMA = PMCONC( INASEC )
79 ! calculate surface area of a single particle in each section 
81          SURFP  = 4.0 * PI * ( DPCTR( INASEC ) / 2.0 )**2.0  ! um2
82          VOL    = ( 4.0 * PI / 3.0 ) * ( DPCTR( INASEC )  &
83                              / 2.0 )**3.0  ! um3
84          AEROMA = VOL * DENSP * 1.0E-6 !  ug
86          IF ( AEROMA > 0.0 ) THEN
87             XNUM  = TOTMA / AEROMA
88             AREA( INASEC ) = SURFP * XNUM * 1.0E-12               ! m2/m3  
89          ELSE
90             AREA( INASEC ) = 0.0
91          END IF
93       END DO
95 ! Calculate diffusion coefficients for reacting species in m2/s,
96 ! molecular speed in m/s, and heterogeneous loss rate in 1/s
97       DO IRXN = 1, NRXNAERO
98          RS_TOT = 0.0
99          DG = ( DG0( IRXN ) * ( PRESS0 / BPRESS ) * &
100                ( BTEMP / TEMP0 )**1.75 ) * 1.0E-4
101          VSP = SQRT( 8.0 * RG * BTEMP / PI / XMOLWEI( IRXN ) )
102          DO INASEC = 1, NASECT
103             RCL = ( DPCTR( INASEC ) / 2.0) * 1.0E-6
104             RS  = 1.0 / ( RCL / DG + 4.0 / VSP / &
105                           GAMMA( IRXN ) ) * AREA( INASEC )
106 !            RS = 0.25 * VSP * AREA( INASEC ) * GAMMA( IRXN )
107             RS_TOT = RS_TOT + RS
108          END DO
110 ! assign the heterogeneous loss rates to RTDAT_AE in 1/sec for first-order
111 ! reaction (no specified reactant) or 1/sec/mol-cc for second-order reaction
112          
113             RTDAT_AE( IRXN ) = RS_TOT
115       END DO
117       RETURN
118       END