added README_changes.txt
[wrffire.git] / wrfv2_fire / chem / cloudchem_driver.F
blob8a0e46e6ca104dd6ce008998d1f8957c35f0952a
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 information 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,                           &
16                moist, cldfra, ph_no2,                                &
17                chem, gas_aqfrac, numgas_aqfrac,                      &
18                ids,ide, jds,jde, kds,kde,                            &
19                ims,ime, jms,jme, kms,kme,                            &
20                its,ite, jts,jte, kts,kte                             )
22 !  wet removal by grid-resolved precipitation
23 !  scavenging of cloud-phase aerosols and gases by collection, freezing, ...
24 !  scavenging of interstitial-phase aerosols by impaction
25 !  scavenging of gas-phase gases by mass transfer and reaction
27 !----------------------------------------------------------------------
28    USE module_configure
29    USE module_state_description
30    USE module_model_constants
31    USE module_mosaic_cloudchem, only: mosaic_cloudchem_driver
33    !  This driver calls subroutines for wet scavenging.
34    !
35    !  1. MADE-SORGAM (not yet implemented)
36    !  2. MOSAIC
38 !----------------------------------------------------------------------
39    IMPLICIT NONE
40 !======================================================================
41 ! Grid structure in physics part of WRF
42 !----------------------------------------------------------------------
43 ! The horizontal velocities used in the physics are unstaggered
44 ! relative to temperature/moisture variables. All predicted
45 ! variables are carried at half levels except w, which is at full
46 ! levels. Some arrays with names (*8w) are at w (full) levels.
48 !----------------------------------------------------------------------
49 ! In WRF, kms (smallest number) is the bottom level and kme (largest
50 ! number) is the top level.  In your scheme, if 1 is at the top level,
51 ! then you have to reverse the order in the k direction.
53 !         kme      -   half level (no data at this level)
54 !         kme    ----- full level
55 !         kme-1    -   half level
56 !         kme-1  ----- full level
57 !         .
58 !         .
59 !         .
60 !         kms+2    -   half level
61 !         kms+2  ----- full level
62 !         kms+1    -   half level
63 !         kms+1  ----- full level
64 !         kms      -   half level
65 !         kms    ----- full level
67 !======================================================================
68 ! Definitions
69 !-----------
70 !-- alt       inverse density
71 !-- t_phy         temperature (K)
72 !-- w             vertical velocity (m/s)
73 !-- moist         moisture array (4D - last index is species) (kg/kg)
74 !-- dz8w          dz between full levels (m)
75 !-- p8w           pressure at full levels (Pa)  
76 !-- p_phy         pressure (Pa)
77 !                 points (dimensionless)
78 !-- z             3D height with lowest level being the terrain
79 !-- rho_phy       density (kg/m^3)
80 !-- qlsink        Fractional cloud water sink (/s)
81 !-- precr         rain precipitation rate at all levels (kg/m2/s)
82 !-- preci         ice precipitation rate at all levels (kg/m2/s)
83 !-- precs         snow precipitation rate at all levels (kg/m2/s)
84 !-- precg         graupel precipitation rate at all levels (kg/m2/s)                             &
85 !-- R_d           gas constant for dry air ( 287. J/kg/K)
86 !-- R_v           gas constant for water vapor (461 J/k/kg)
87 !-- Cp            specific heat at constant pressure (1004 J/k/kg)
88 !-- rvovrd        R_v divided by R_d (dimensionless)
89 !-- G             acceleration due to gravity (m/s^2)
90 !-- ids           start index for i in domain
91 !-- ide           end index for i in domain
92 !-- jds           start index for j in domain
93 !-- jde           end index for j in domain
94 !-- kds           start index for k in domain
95 !-- kde           end index for k in domain
96 !-- ims           start index for i in memory
97 !-- ime           end index for i in memory
98 !-- jms           start index for j in memory
99 !-- jme           end index for j in memory
100 !-- kms           start index for k in memory
101 !-- kme           end index for k in memory
102 !-- its           start index for i in tile
103 !-- ite           end index for i in tile
104 !-- jts           start index for j in tile
105 !-- jte           end index for j in tile
106 !-- kts           start index for k in tile
107 !-- kte           end index for k in tile
108 !-- config_flags%kemit  end index for k for emissions arrays
110 !======================================================================
112    TYPE(grid_config_rec_type),  INTENT(IN   )    :: config_flags
114    INTEGER,      INTENT(IN   )    ::                                &
115                                       ids,ide, jds,jde, kds,kde,    &
116                                       ims,ime, jms,jme, kms,kme,    &
117                                       its,ite, jts,jte, kts,kte,    &
118                                       id, ktau, ktauc,              &
119                                       numgas_aqfrac
120       REAL,      INTENT(IN   ) :: dtstep, dtstepc
122 ! moisture variables
124    REAL, DIMENSION( ims:ime, kms:kme, jms:jme, num_moist ),         &
125          INTENT(IN ) ::                                   moist
127 ! input from meteorology
128    REAL,  DIMENSION( ims:ime , kms:kme , jms:jme )         ,        &
129           INTENT(IN   ) ::                                          &
130                                 t_phy,                              &
131                                 p_phy,                              &
132                                 rho_phy,                            &
133                                 alt,                                &
134                                 cldfra,                             &
135                                 ph_no2
137 ! all advected chemical species
139    REAL, DIMENSION( ims:ime, kms:kme, jms:jme, num_chem ),          &
140          INTENT(INOUT ) ::                                chem
142    REAL, DIMENSION( ims:ime, kms:kme, jms:jme, numgas_aqfrac ),     &
143          INTENT(INOUT ) ::                                gas_aqfrac
147 ! LOCAL  VAR
148      integer :: ii,jj,kk
151 !-----------------------------------------------------------------
153 ! These are unneeded, since the default behavior is to do nothing.
154 ! If the default changes, then lines need to be added for CBMZ and
155 ! CBMZ_BB.
156 !   IF (config_flags%chem_opt .eq. 0) return
157 !   IF (config_flags%chem_opt .eq. 1) return
160 ! select which aerosol scheme to take
162    cps_select: SELECT CASE(config_flags%chem_opt)
164    CASE (CBMZ_MOSAIC_4BIN, CBMZ_MOSAIC_8BIN, CBMZ_MOSAIC_4BIN_AQ, CBMZ_MOSAIC_8BIN_AQ)
166        call wrf_debug(15,'cloudchem_driver calling mosaic_cloudchem_driver')
167        call mosaic_cloudchem_driver(                  &
168             id, ktau, ktauc, dtstepc, config_flags,   &
169             p_phy, t_phy, rho_phy, alt,               &
170             cldfra, ph_no2,                           &
171             moist, chem,                              &
172             gas_aqfrac, numgas_aqfrac,                &
173             ids,ide, jds,jde, kds,kde,                &
174             ims,ime, jms,jme, kms,kme,                &
175             its,ite, jts,jte, kts,kte )
177    CASE DEFAULT
179    END SELECT cps_select
181    END SUBROUTINE cloudchem_driver