Merge pull request #22 from wirc-sjsu/develop-w21
[WRF-Fire-merge.git] / chem / cloudchem_driver.F
blobc128c90f344689703183f882d00fd6405cf690ba
1 !**********************************************************************************  
2 ! This computer software was prepared by Battelle Memorial Institute, hereinafter
3 ! the Contractor, under Contract No. DE-AC05-76RL0 1830 with the Department of 
4 ! Energy (DOE). NEITHER THE GOVERNMENT NOR THE CONTRACTOR MAKES ANY WARRANTY,
5 ! EXPRESS OR IMPLIED, OR ASSUMES ANY LIABILITY FOR THE USE OF THIS SOFTWARE.
7 ! MOSAIC module: see module_mosaic_driver.F for references and terms of use
8 !**********************************************************************************  
10 !  file cloudchem_driver.F
13       SUBROUTINE cloudchem_driver(                                   &
14                id, ktau, ktauc, dtstep, dtstepc, config_flags,       &
15                t_phy, p_phy, rho_phy, alt, dz8w,                           &
16                p8w, prain3d,scalar,dvmrdt_sv13d,dvmrcwdt_sv13d,      & !Balwinder.Singh@pnnl.gov: Variables required for CAM-MAM cloud chemistry
17                f_ice_phy, f_rain_phy, cldfrai, cldfral,              &
18                moist, cldfra, cldfra_mp_all, ph_no2,                 &
19                chem, gas_aqfrac, numgas_aqfrac,                      &
20                is_CAMMGMP_used,                                      &!BSINGH:01/31/2013: Added is_CAMMGMP_used for CAM_MAM_cloudchem
21                ph_cw,                                                &
22                ids,ide, jds,jde, kds,kde,                            &
23                ims,ime, jms,jme, kms,kme,                            &
24                its,ite, jts,jte, kts,kte                             )
26 !  wet removal by grid-resolved precipitation
27 !  scavenging of cloud-phase aerosols and gases by collection, freezing, ...
28 !  scavenging of interstitial-phase aerosols by impaction
29 !  scavenging of gas-phase gases by mass transfer and reaction
31 !----------------------------------------------------------------------
32    USE module_configure
33    USE module_state_description
34    USE module_model_constants
35    USE module_cam_support, only: gas_pcnst => gas_pcnst_modal_aero, &
36         gas_pcnst_pos => gas_pcnst_modal_aero_pos
37    USE module_mosaic_cloudchem,  only: mosaic_cloudchem_driver
38    USE module_sorgam_cloudchem,  only: sorgam_cloudchem_driver
39    USE module_sorgam_vbs_cloudchem, only: sorgam_vbs_cloudchem_driver
40    USE module_cam_mam_cloudchem, only: cam_mam_cloudchem_driver
41    USE module_sorgam_aqchem, only: sorgam_aqchem_driver
42    USE module_sorgam_vbs_aqchem, only: sorgam_vbs_aqchem_driver
44    !  This driver calls subroutines for wet scavenging.
45    !
46    !  1. MADE-SORGAM
47    !  2. MOSAIC
49 !----------------------------------------------------------------------
50    IMPLICIT NONE
51 !======================================================================
52 ! Grid structure in physics part of WRF
53 !----------------------------------------------------------------------
54 ! The horizontal velocities used in the physics are unstaggered
55 ! relative to temperature/moisture variables. All predicted
56 ! variables are carried at half levels except w, which is at full
57 ! levels. Some arrays with names (*8w) are at w (full) levels.
59 !----------------------------------------------------------------------
60 ! In WRF, kms (smallest number) is the bottom level and kme (largest
61 ! number) is the top level.  In your scheme, if 1 is at the top level,
62 ! then you have to reverse the order in the k direction.
64 !         kme      -   half level (no data at this level)
65 !         kme    ----- full level
66 !         kme-1    -   half level
67 !         kme-1  ----- full level
68 !         .
69 !         .
70 !         .
71 !         kms+2    -   half level
72 !         kms+2  ----- full level
73 !         kms+1    -   half level
74 !         kms+1  ----- full level
75 !         kms      -   half level
76 !         kms    ----- full level
78 !======================================================================
79 ! Definitions
80 !-----------
81 !-- alt       inverse density
82 !-- t_phy         temperature (K)
83 !-- w             vertical velocity (m/s)
84 !-- moist         moisture array (4D - last index is species) (kg/kg)
85 !-- scalar        scalar array (4D) #/kg
86 !-- dz8w          dz between full levels (m)
87 !-- p8w           pressure at full levels (Pa)  
88 !-- p_phy         pressure (Pa)
89 !                 points (dimensionless)
90 !-- z             3D height with lowest level being the terrain
91 !-- rho_phy       density (kg/m^3)
92 !-- qlsink        Fractional cloud water sink (/s)
93 !-- precr         rain precipitation rate at all levels (kg/m2/s)
94 !-- preci         ice precipitation rate at all levels (kg/m2/s)
95 !-- precs         snow precipitation rate at all levels (kg/m2/s)
96 !-- precg         graupel precipitation rate at all levels (kg/m2/s)                             &
97 !-- R_d           gas constant for dry air ( 287. J/kg/K)
98 !-- R_v           gas constant for water vapor (461 J/k/kg)
99 !-- Cp            specific heat at constant pressure (1004 J/k/kg)
100 !-- rvovrd        R_v divided by R_d (dimensionless)
101 !-- G             acceleration due to gravity (m/s^2)
102 !-- ids           start index for i in domain
103 !-- ide           end index for i in domain
104 !-- jds           start index for j in domain
105 !-- jde           end index for j in domain
106 !-- kds           start index for k in domain
107 !-- kde           end index for k in domain
108 !-- ims           start index for i in memory
109 !-- ime           end index for i in memory
110 !-- jms           start index for j in memory
111 !-- jme           end index for j in memory
112 !-- kms           start index for k in memory
113 !-- kme           end index for k in memory
114 !-- its           start index for i in tile
115 !-- ite           end index for i in tile
116 !-- jts           start index for j in tile
117 !-- jte           end index for j in tile
118 !-- kts           start index for k in tile
119 !-- kte           end index for k in tile
120 !-- config_flags%kemit  end index for k for emissions arrays
122 !======================================================================
124    TYPE(grid_config_rec_type),  INTENT(IN   )    :: config_flags
125    LOGICAL,      INTENT(IN)       :: is_CAMMGMP_used
126    INTEGER,      INTENT(IN   )    ::                                &
127                                       ids,ide, jds,jde, kds,kde,    &
128                                       ims,ime, jms,jme, kms,kme,    &
129                                       its,ite, jts,jte, kts,kte,    &
130                                       id, ktau, ktauc,              &
131                                       numgas_aqfrac
132       REAL,      INTENT(IN   ) :: dtstep, dtstepc
134 ! moisture variables
136    REAL, DIMENSION( ims:ime, kms:kme, jms:jme, num_moist ),         &
137          INTENT(IN ) ::                                   moist
138    REAL, DIMENSION( ims:ime, kms:kme, jms:jme, num_scalar ),         &
139          INTENT(IN ) ::                                   scalar    !Balwinder.Singh@pnnl.gov: Variables required for CAM-MAM cloud chemistry
141 !tendencies:dvmrdt_sv13d,dvmrcwdt_sv13d are the tendencies which are passsed on from the CAM-MAM cloud chemistry
142 !           to gasaerexch subroutine in cam_mam_aerchem_driver
144    REAL, DIMENSION( ims:ime, kms:kme, jms:jme, gas_pcnst_pos ),          &
145         INTENT(OUT ) ::                                  dvmrdt_sv13d,dvmrcwdt_sv13d 
147 ! input from meteorology
148    REAL,  DIMENSION( ims:ime , kms:kme , jms:jme )         ,        &
149           INTENT(IN   ) ::                                          &
150                                 t_phy,                              &
151                                 p_phy,                              &
152                                 rho_phy,                            &
153                                 alt,                                &
154                                 dz8w,                               &
155                                 cldfra,                             &
156                                 ph_no2,                             &
157                                 p8w,                                & !Balwinder.Singh@pnnl.gov: Variables required for CAM-MAM cloud chemistry
158                                 prain3d,                            &
159                                 F_ICE_PHY,                          &
160                                 F_RAIN_PHY,                         &
161                                 cldfrai,                            &
162                                 cldfral,                            &
163                                 cldfra_mp_all
165 ! all advected chemical species
167    REAL, DIMENSION( ims:ime, kms:kme, jms:jme, num_chem ),          &
168          INTENT(INOUT ) ::                                chem
170    REAL, DIMENSION( ims:ime, kms:kme, jms:jme, numgas_aqfrac ),     &
171          INTENT(INOUT ) ::                                gas_aqfrac
173    REAL, DIMENSION( ims:ime, kms:kme, jms:jme ),                    &
174          INTENT(OUT) ::                            ph_cw            ! ph_cw - pH of cloud water
176 ! LOCAL  VAR
177      integer :: ii,jj,kk
180 !-----------------------------------------------------------------
182 ! These are unneeded, since the default behavior is to do nothing.
183 ! If the default changes, then lines need to be added for CBMZ and
184 ! CBMZ_BB.
185 !   IF (config_flags%chem_opt .eq. 0) return
186 !   IF (config_flags%chem_opt .eq. 1) return
189 ! select which aerosol scheme to take
191    cps_select: SELECT CASE(config_flags%chem_opt)
193    CASE ( CBMZ_MOSAIC_4BIN, CBMZ_MOSAIC_8BIN, CBMZ_MOSAIC_4BIN_AQ, CBMZ_MOSAIC_8BIN_AQ, &
194         CBMZ_MOSAIC_DMS_4BIN, CBMZ_MOSAIC_DMS_8BIN, CBMZ_MOSAIC_DMS_4BIN_AQ,            &
195         CBMZ_MOSAIC_DMS_8BIN_AQ, CRI_MOSAIC_8BIN_AQ_KPP, CRI_MOSAIC_4BIN_AQ_KPP, &
196         MOZART_MOSAIC_4BIN_AQ_KPP,        &
197         SAPRC99_MOSAIC_8BIN_VBS2_AQ_KPP)!BSINGH(12/03/2013): Added SAPRC 8 bin
199        call wrf_debug(15, &
200        'cloudchem_driver calling mosaic_cloudchem_driver')
201        call mosaic_cloudchem_driver(                  &
202             id, ktau, ktauc, dtstepc, config_flags,   &
203             p_phy, t_phy, rho_phy, alt,               &
204             cldfra, ph_no2,                           &
205             moist, chem, ph_cw,                       &
206             gas_aqfrac, numgas_aqfrac,                &
207             ids,ide, jds,jde, kds,kde,                &
208             ims,ime, jms,jme, kms,kme,                &
209             its,ite, jts,jte, kts,kte )
211    CASE ( RADM2SORG_AQ, RACMSORG_AQ, CBMZSORG_AQ )
213        call wrf_debug(15, &
214        'cloudchem_driver calling sorgam_cloudchem_driver')
215        call sorgam_cloudchem_driver(                  &
216             id, ktau, ktauc, dtstepc, config_flags,   &
217             p_phy, t_phy, rho_phy, alt,               &
218             cldfra, ph_no2,                           &
219             moist, chem,                              &
220             gas_aqfrac, numgas_aqfrac,                &
221             ids,ide, jds,jde, kds,kde,                &
222             ims,ime, jms,jme, kms,kme,                &
223             its,ite, jts,jte, kts,kte )
224     CASE (CBMZ_CAM_MAM3_NOAQ,CBMZ_CAM_MAM3_AQ,CBMZ_CAM_MAM7_NOAQ,CBMZ_CAM_MAM7_AQ)       
225        CALL wrf_debug(15,'cloudchem_driver calling mam_cloudchem_driver')       
226        call cam_mam_cloudchem_driver (                &
227             !Intent Outs
228             dvmrdt_sv13d,dvmrcwdt_sv13d,              & 
229             !Intent in-outs
230             chem,                                     &
231             !Intent ins
232             moist, scalar, p8w, prain3d, p_phy,       &
233             t_phy, dtstepc, ktau,alt, f_ice_phy,      &
234             f_rain_phy, cldfra, cldfra_mp_all,        &
235             cldfrai, cldfral, is_CAMMGMP_used,        & 
236             ids,ide, jds,jde, kds,kde,                &
237             ims,ime, jms,jme, kms,kme,                &
238             its,ite, jts,jte, kts,kte                 )
239    CASE ( CB05_SORG_VBS_AQ_KPP )
241        call wrf_debug(15, &
242        'cloudchem_driver calling sorgam_vbs_aqchem_driver')
243        call sorgam_vbs_aqchem_driver(                 &
244             id, ktau, ktauc, dtstepc, config_flags,   &
245             p_phy, t_phy, rho_phy, alt, dz8w,         &
246             moist, chem,                              &
247             gas_aqfrac, numgas_aqfrac,                &
248             ids,ide, jds,jde, kds,kde,                &
249             ims,ime, jms,jme, kms,kme,                &
250             its,ite, jts,jte, kts,kte )
253    CASE ( RADM2SORG_AQCHEM, RACMSORG_AQCHEM_KPP, RACM_ESRLSORG_AQCHEM_KPP, &
254           CB05_SORG_AQ_KPP,RACM_SOA_VBS_AQCHEM_KPP )
256        call wrf_debug(15, &
257        'cloudchem_driver calling sorgam_aqchem_driver')
258        call sorgam_aqchem_driver(                  &
259             id, ktau, ktauc, dtstepc, config_flags,   &
260             p_phy, t_phy, rho_phy, alt, dz8w,         &
261             moist, chem,                              &
262             gas_aqfrac, numgas_aqfrac,                &
263             ids,ide, jds,jde, kds,kde,                &
264             ims,ime, jms,jme, kms,kme,                &
265             its,ite, jts,jte, kts,kte )
267    CASE DEFAULT
269    END SELECT cps_select
271    END SUBROUTINE cloudchem_driver