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

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

last changes documented

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