source: palm/trunk/SOURCE/chem_modules.f90 @ 4109

Last change on this file since 4109 was 4109, checked in by suehring, 5 years ago

Control discretization of advection term: separate initialization of WS advection flags for momentum and scalars. In this context, resort the bits and do some minor formatting; Make initialization of scalar-advection flags more flexible, i.e. introduce an arguemnt list to indicate non-cyclic boundaries (required for decycled scalars such as chemical species or aerosols); Introduce extended 'degradation zones', where horizontal advection of passive scalars is discretized by first-order scheme at all grid points that in the vicinity of buildings (<= 3 grid points). Even though no building is within the numerical stencil, first-order scheme is used. At fourth and fifth grid point the order of the horizontal advection scheme is successively upgraded. These extended degradation zones are used to avoid stationary numerical oscillations, which are responsible for high concentration maxima that may appear under shear-free stable conditions. Therefore, an additional 3D interger array used to store control flags is introduced; Change interface for scalar advection routine; Bugfix, avoid uninitialized value sk_num in vector version of WS scalar advection; Chemistry: Decycling boundary conditions are only set at the ghost points not on the prognostic grid points; Land-surface model: Relax checks for non-consistent initialization in case static or dynamic input is provided. For example, soil_temperature or deep_soil_temperature is not mandatory any more if dynamic input is available. Also, improper settings of x_type in namelist are only checked if no static file is available.

  • Property svn:keywords set to Id
File size: 14.8 KB
Line 
1!> @file chem_modules.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 2018-2019 Leibniz Universitaet Hannover
18! Copyright 2018-2019 Karlsruhe Institute of Technology
19! Copyright 2018-2019 Freie Universitaet Berlin
20!------------------------------------------------------------------------------!
21!
22! Current revisions:
23! -----------------
24! +cs_advc_flags_s
25!
26! Former revisions:
27! -----------------
28! $Id: chem_modules.f90 4109 2019-07-22 17:00:34Z suehring $
29! - introduced namelist item chem_modules@emiss_lod as future
30! - replacement to chem_modules@mode_emis.  Currently keeping both
31!   for backward compatibility.  chem_modules@mode_emis will be
32!   depreciated upon migration of all dependent modules (e.g., salsa)
33!   to chem_modules@emiss_lod
34!
35! (ecc) 20190513 replaced nspec_out with n_matched_vars
36!
37! 3877 2019-04-08 19:09:16Z knoop
38! Formatting, clean-up, clarified/corrected comments
39!
40! 3833 2019-03-28 15:04:04Z forkel
41! removed USE chem_gasphase_mod
42!
43! 3827 2019-03-27 17:20:32Z forkel
44! some formatting  and reordering (ecc)
45!
46! 3820 2019-03-27 11:53:41Z forkel
47! renamed do_emis to emissions_anthropogenic, removed USE statistics, variables sorted by type
48!
49!
50! 3780 2019-03-05 11:19:45Z forkel
51! added cs_mech
52!
53! 3652 2019-01-07 15:29:59Z forkel
54! parameter chem_mechanism added (basit)
55!
56! 3636 2018-12-19 13:48:34Z raasch
57! nopointer option removed
58!
59! 3611 2018-12-07 14:14:11Z banzhafs
60! Minor formatting
61!
62! 3458 2018-10-30 14:51:23Z kanani
63! from chemistry branch r3443:
64! ??
65!
66! 3298 2018-10-02 12:21:11Z kanani
67! - Minor formatting
68! - Introduced Variables for Chemistry emissions Module (Russo)
69! - Variables and parameters added for 2d and profile output (basit)
70! - Converted scalar  emission factors  to 1-D array of 99 elements each (basit)
71! - Removed "__chem" directive (basit)
72!
73! 3282 2018-09-27 10:49:12Z basit
74! Initial revision
75!
76! Authors:
77! --------
78! @author Farah Kanani-Suehring
79! @author Basit Khan
80! @author Sabine Banzhaf
81! @author Emmanuele Russo
82! @author Edward C. Chan
83!
84!------------------------------------------------------------------------------!
85! Description:
86! ------------
87!> Definition of global PALM-4U chemistry variables
88!------------------------------------------------------------------------------!
89!
90 MODULE chem_modules
91
92    USE kinds
93
94    IMPLICIT NONE
95
96    CHARACTER (LEN=20) ::  bc_cs_b        = 'dirichlet'         !< namelist parameter: surface boundary condition for concentration
97    CHARACTER (LEN=20) ::  bc_cs_t        = 'initial_gradient'  !< namelist parameter: top boudary condition for concentration
98    CHARACTER (LEN=30) ::  chem_mechanism = 'phstatp'           !< namelist parameter: chemistry mechanism
99    CHARACTER (LEN=80) ::  daytype_mdh    = 'workday'           !< namelist parameter: type of day - workday, weekend, holiday
100    CHARACTER (LEN=80) ::  mode_emis      = 'PARAMETERIZED'     !< namelist parameter: mode of chemistry emissions - DEFAULT, EXPERT, PARAMETERIZED
101    CHARACTER (LEN=80) ::  time_fac_type  = 'MDH'               !< namelist parameter: type of time treatment in the mode_emis DEFAULT - HOUR, MDH
102    CHARACTER (LEN=10) ::  photolysis_scheme                    !< 'constant',
103                                                                !< 'simple' (Simple parameterisation from MCM, Saunders et al., 2003, Atmos. Chem. Phys., 3, 161-180
104                                                                !< 'fastj'  (Wild et al., 2000, J. Atmos. Chem., 37, 245-282) STILL NOT IMPLEMENTED
105
106    CHARACTER (LEN=11), DIMENSION(99) ::  cs_name             = 'novalue'  !< namelist parameter: names of species with given fluxes (see csflux)
107    CHARACTER (LEN=11), DIMENSION(99) ::  cs_profile_name     = 'novalue'  !< namelist parameter: tbc...???
108    CHARACTER (LEN=11), DIMENSION(99) ::  data_output_pr_cs   = 'novalue'  !< namelist parameter: tbc...???
109    CHARACTER (LEN=11), DIMENSION(99) ::  surface_csflux_name = 'novalue'  !< namelist parameter: tbc...???
110
111    INTEGER(iwp) ::  cs_pr_count                           = 0      !< counter for chemical species profiles
112    INTEGER(iwp) ::  cs_vertical_gradient_level_ind(99,10) = -9999  !< grid index values of cs_vertical_gradient_level
113    INTEGER(iwp) ::  emiss_lod                             = -1     !< namelist parameter: chem emission LOD (same as mode_emis)
114                                                                    !< -1 = unassigned, 0 = parameterized, 1 = default, 2 = pre-processed
115    INTEGER(iwp) ::  ibc_cs_b                                       !< integer flag for bc_cs_b
116    INTEGER(iwp) ::  ibc_cs_t                                       !< integer flag for bc_cs_t
117    INTEGER(iwp) ::  main_street_id                        = 0      !< namelist parameter: lower bound of main street IDs (OpenStreetMaps) for PARAMETERIZED mode
118    INTEGER(iwp) ::  max_pr_cs                             = 0      !<
119    INTEGER(iwp) ::  max_street_id                         = 0      !< namelist parameter: upper bound of main street IDs (OpenStreetMaps) for PARAMETERIZED mode     
120    INTEGER(iwp) ::  n_matched_vars                                 !< number of matched emissions variables
121    INTEGER(iwp) ::  side_street_id                        = 0      !< namelist parameter: lower bound of side street IDs (OpenStreetMaps) for PARAMETERIZED mode
122
123    INTEGER(iwp), DIMENSION(99) ::  cs_pr_index  = 0      !< index for chemical species profiles
124    INTEGER(iwp), DIMENSION(:)  ::  match_spec_nox(1:2)   !< results of matching the input and model's NOx
125    INTEGER(iwp), DIMENSION(:)  ::  match_spec_pm(1:3)    !< results of matching the input and model's PMs
126    INTEGER(iwp), DIMENSION(:)  ::  match_spec_sox(1:2)   !< results of matching the input and model's SOx!
127
128    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_spec_input      !< index of input chem species for matching routine
129    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_spec_model      !< index of model chem species for matching routine
130    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_spec_voc_input  !< index of VOC input components matching the model's VOCs
131    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_spec_voc_model  !< index of VOC model species matching the input VOCs comp.
132   
133    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE  ::  cs_advc_flags_s !< flags used to degrade order of advection scheme for
134                                                                     !< chemical species near walls and lateral boundaries
135
136    LOGICAL ::  constant_top_csflux(99)   = .TRUE.   !< internal flag, set to .FALSE. if no top_csflux is prescribed
137    LOGICAL ::  constant_csflux(99)       = .TRUE.   !< internal flag, set to .FALSE. if no surface_csflux is prescribed
138    LOGICAL ::  call_chem_at_all_substeps = .FALSE.  !< namelist parameter: ....???
139    LOGICAL ::  chem_debug0               = .FALSE.  !< namelist parameter: flag for minimum print output
140    LOGICAL ::  chem_debug1               = .FALSE.  !< namelist parameter: flag for print output
141    LOGICAL ::  chem_debug2               = .FALSE.  !< namelist parameter: flag for further print output
142    LOGICAL ::  chem_gasphase_on          = .TRUE.   !< namelist parameter: flag to switch off chemical reactions
143    LOGICAL ::  cs_pr_namelist_found      = .FALSE.  !< ...???
144    LOGICAL ::  deposition_dry            = .FALSE.  !< namelist parameter: flag for activation of deposition calculation
145    LOGICAL ::  emissions_anthropogenic   = .FALSE.  !< namelist parameter: flag for turning on anthropogenic emissions
146    LOGICAL ::  emission_output_required  = .TRUE.   !< internal flag for requiring emission outputs
147
148    REAL(wp) ::  cs_surface_initial_change(99)     = 0.0_wp        !< namelist parameter: ...???
149    REAL(wp) ::  cs_vertical_gradient(99,10)       = 0.0_wp        !< namelist parameter: ...???
150    REAL(wp) ::  cs_vertical_gradient_level(99,10) = -999999.9_wp  !< namelist parameter: ...???
151    REAL(wp) ::  emiss_factor_main(99)             = -9999.0_wp    !< namelist parameter: ...???
152    REAL(wp) ::  emiss_factor_side(99)             = -9999.0_wp    !< namelist parameter: ...???
153    REAL(wp) ::  surface_csflux(99)                = 0.0_wp        !< namelist parameter: ...???
154    REAL(wp) ::  top_csflux(99)                    = 0.0_wp        !< namelist parameter: ...???
155    REAL(wp) ::  wall_csflux(99,0:5)               = 0.0_wp        !< namelist parameter: ...???
156
157    REAL(wp), DIMENSION(99)     ::  cs_surface = 0.0_wp        !< namelist parameter: chem species concentration at surface
158    REAL(wp), DIMENSION(99,100) ::  cs_heights = 9999999.9_wp  !< namelist parameter: height levels for initial chem species concentrations
159    REAL(wp), DIMENSION(99,100) ::  cs_profile = 9999999.9_wp  !< namelist parameter: chem species concentration values at cs_heights levels
160
161    REAL(wp), DIMENSION(:), ALLOCATABLE ::  bc_cs_t_val  !< vertical gradient of chemical species near domain top
162    REAL(wp), DIMENSION(:), ALLOCATABLE ::  css          !< scaling parameter for chem species
163
164    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  emis_distribution  !< emissions final values (main module output) ???
165                                 
166    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_1  !< pointer for swapping of timelevels for respective quantity
167    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_2  !< pointer for swapping of timelevels for respective quantity
168    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_3  !< pointer for swapping of timelevels for respective quantity
169
170    REAL(wp), DIMENSION(:,:,:), POINTER ::  cs     !< pointer: sgs chem spcs  ???
171    REAL(wp), DIMENSION(:,:,:), POINTER ::  cs_p   !< pointer: prognostic value of sgs chem spcs ???
172    REAL(wp), DIMENSION(:,:,:), POINTER ::  tcs_m  !< pointer: to tcs array (temp)
173
174    REAL, PARAMETER ::  xm_air   =   28.964e-3             !< air      molecular weight (kg/mol)
175    REAL, PARAMETER ::  xm_C     =   12.01115e-3           !< C        molecular weight (kg/mol)
176    REAL, PARAMETER ::  xm_Ca    =   40.07800e-3           !< Ca       molecular weight (kg/mol)
177    REAL, PARAMETER ::  xm_Cd    =  112.41000e-3           !< Cd       molecular weight (kg/mol)
178    REAL, PARAMETER ::  xm_Cl    =   35.45300e-3           !< Cl       molecular weight (kg/mol)
179    REAL, PARAMETER ::  xm_dummy = 1000.0e-3               !< dummy    molecular weight (kg/mol)
180    REAL, PARAMETER ::  xm_F     =   18.99840e-3           !< F        molecular weight (kg/mol)
181    REAL, PARAMETER ::  xm_H     =    1.00790e-3           !< H        molecular weight (kg/mol)
182    REAL, PARAMETER ::  xm_K     =   39.09800e-3           !< K        molecular weight (kg/mol)
183    REAL, PARAMETER ::  xm_Mg    =   24.30500e-3           !< Mg       molecular weight (kg/mol)
184    REAL, PARAMETER ::  xm_N     =   14.00670e-3           !< N        molecular weight (kg/mol)
185    REAL, PARAMETER ::  xm_Na    =   22.98977e-3           !< Na       molecular weight (kg/mol)
186    REAL, PARAMETER ::  xm_O     =   15.99940e-3           !< O        molecular weight (kg/mol)
187    REAL, PARAMETER ::  xm_Pb    =  207.20000e-3           !< Pb       molecular weight (kg/mol)
188    REAL, PARAMETER ::  xm_Pb210 =  210.00000e-3           !< Pb (210) molecular weight (kg/mol)
189    REAL, PARAMETER ::  xm_Rn222 =  222.00000e-3           !< Rn (222) molecular weight (kg/mol)
190    REAL, PARAMETER ::  xm_S     =   32.06400e-3           !< S        molecular weight (kg/mol)
191    REAL, PARAMETER ::  xm_CO2   = xm_C + xm_O * 2         !< CO2      molecular weight (kg/mol)
192    REAL, PARAMETER ::  xm_h2o   = xm_H * 2 + xm_O         !< H2O      molecular weight (kg/mol)
193    REAL, PARAMETER ::  xm_HNO3  = xm_H + xm_N + xm_O * 3  !< HNO3     molecular weight (kg/mol)
194    REAL, PARAMETER ::  xm_o3    = xm_O * 3                !< O3       molecular weight (kg/mol)
195    REAL, PARAMETER ::  xm_N2O5  = xm_N * 2 + xm_O * 5     !< N2O5     molecular weight (kg/mol)
196    REAL, PARAMETER ::  xm_NH4   = xm_N + xm_H * 4         !< NH4      molecular weight (kg/mol)
197    REAL, PARAMETER ::  xm_NO3   = xm_N + xm_O * 3         !< NO3      molecular weight (kg/mol)
198    REAL, PARAMETER ::  xm_SO4   = xm_S + xm_O * 4         !< SO4      molecular weight (kg/mol)
199!
200!-  Define chemical variables within chem_species
201    TYPE species_def
202       CHARACTER(LEN=15)                            ::  name         !< name of chemical species
203       CHARACTER(LEN=15)                            ::  unit         !< unit (ppm for gases, kg m^-3 for aerosol tracers)
204       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  conc         !< concentrations of trace gases
205       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  conc_av      !< averaged concentrations
206       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  conc_p       !< conc at prognostic time level
207       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  tconc_m      !< weighted tendency of conc for previous sub-timestep (Runge-Kutta)
208       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  cssws_av     !< averaged fluxes of trace gases at surface
209       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  flux_s_cs    !< 6th-order advective flux at south face of grid box of chemical species (='cs')
210       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  diss_s_cs    !< artificial numerical dissipation flux at south face of grid box of chemical species
211       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:) ::  flux_l_cs    !< 6th-order advective flux at left face of grid box of chemical species (='cs')
212       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:) ::  diss_l_cs    !< artificial numerical dissipation flux at left face of grid box of chemical species
213       REAL(kind=wp), ALLOCATABLE, DIMENSION(:)     ::  conc_pr_init !< initial profile of chemical species
214    END TYPE species_def
215!
216!-- Define photolysis frequencies in phot_frequen
217    TYPE photols_def
218       CHARACTER(LEN=15)                            :: name          !< name of pgotolysis frequency
219       CHARACTER(LEN=15)                            :: unit          !< unit (1/s)
220       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     :: freq          !< photolysis frequency
221    END TYPE photols_def
222
223
224    TYPE(species_def), ALLOCATABLE, DIMENSION(:), TARGET ::  chem_species
225    TYPE(photols_def), ALLOCATABLE, DIMENSION(:), TARGET ::  phot_frequen
226
227    SAVE
228
229 END MODULE chem_modules
Note: See TracBrowser for help on using the repository browser.