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

Last change on this file since 4784 was 4581, checked in by suehring, 4 years ago

mesoscale nesting: omit explicit pressure forcing via geostrophic wind components; chemistry: enable profile output of vertical fluxes; urban-surface: bugfix in initialization in case of cyclic_fill

  • Property svn:keywords set to Id
File size: 21.9 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 terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
15!
16! Copyright 2018-2020 Leibniz Universitaet Hannover
17! Copyright 2018-2020 Karlsruhe Institute of Technology
18! Copyright 2018-2020 Freie Universitaet Berlin
19!--------------------------------------------------------------------------------------------------!
20!
21! Current revisions:
22! -----------------
23!
24!
25! Former revisions:
26! -----------------
27! $Id: chem_modules.f90 4581 2020-06-29 08:49:58Z suehring $
28! Enable output of vertical fluxes of chemical species.
29!
30! 4577 2020-06-25 09:53:58Z raasch
31! further re-formatting concerning Fortran parameter variables
32!
33! 4559 2020-06-11 08:51:48Z raasch
34! file re-formatted to follow the PALM coding standard
35!
36! 4544 2020-05-21 14:43:05Z raasch
37! conc_av changed from pointer to allocatable array
38!
39! 4511 2020-04-30 12:20:40Z raasch
40! new variables for explicit settings of lateral boundary conditions introduced
41!
42! 4481 2020-03-31 18:55:54Z maronga
43! added namelist flag 'emiss_read_legacy_mode' to allow concurrent functioning of new emission read
44! mode under development (ECC)
45!
46! 4273 2019-10-24 13:40:54Z monakurppa
47! Add logical switches nesting_chem and nesting_offline_chem (both .TRUE. by default)
48!
49! 4182 2019-08-22 15:20:23Z scharf
50! Corrected "Former revisions" section
51!
52! 4110 2019-07-22 17:05:21Z suehring
53! +cs_advc_flags_s
54!
55! 4109 2019-07-22 17:00:34Z suehring
56! - introduced namelist item chem_modules@emiss_lod as future
57! - replacement to chem_modules@mode_emis.  Currently keeping both for backward compatibility.
58!   chem_modules@mode_emis will be depreciated upon migration of all dependent modules (e.g., salsa)
59!   to chem_modules@emiss_lod
60!
61! (ecc) 20190513 replaced nspec_out with n_matched_vars
62!
63! 3877 2019-04-08 19:09:16Z knoop
64! Formatting, clean-up, clarified/corrected comments
65!
66! 3833 2019-03-28 15:04:04Z forkel
67! removed USE chem_gasphase_mod
68!
69! 3827 2019-03-27 17:20:32Z forkel
70! some formatting  and reordering (ecc)
71!
72! 3820 2019-03-27 11:53:41Z forkel
73! renamed do_emis to emissions_anthropogenic, removed USE statistics, variables sorted by type
74!
75! 3780 2019-03-05 11:19:45Z forkel
76! added cs_mech
77!
78! 3652 2019-01-07 15:29:59Z forkel
79! parameter chem_mechanism added (basit)
80!
81! 3282 2018-09-27 10:49:12Z basit
82! Initial revision
83!
84! Authors:
85! --------
86! @author Farah Kanani-Suehring
87! @author Basit Khan
88! @author Sabine Banzhaf
89! @author Emmanuele Russo
90! @author Edward C. Chan
91!
92!--------------------------------------------------------------------------------------------------!
93! Description:
94! ------------
95!> Definition of global PALM-4U chemistry variables
96!--------------------------------------------------------------------------------------------------!
97!
98 MODULE chem_modules
99
100    USE kinds
101
102    IMPLICIT NONE
103
104    REAL, PARAMETER ::  xm_air   =   28.964e-3             !< air      molecular weight (kg/mol)
105    REAL, PARAMETER ::  xm_C     =   12.01115e-3           !< C        molecular weight (kg/mol)
106    REAL, PARAMETER ::  xm_Ca    =   40.07800e-3           !< Ca       molecular weight (kg/mol)
107    REAL, PARAMETER ::  xm_Cd    =  112.41000e-3           !< Cd       molecular weight (kg/mol)
108    REAL, PARAMETER ::  xm_Cl    =   35.45300e-3           !< Cl       molecular weight (kg/mol)
109    REAL, PARAMETER ::  xm_dummy = 1000.0e-3               !< dummy    molecular weight (kg/mol)
110    REAL, PARAMETER ::  xm_F     =   18.99840e-3           !< F        molecular weight (kg/mol)
111    REAL, PARAMETER ::  xm_H     =    1.00790e-3           !< H        molecular weight (kg/mol)
112    REAL, PARAMETER ::  xm_K     =   39.09800e-3           !< K        molecular weight (kg/mol)
113    REAL, PARAMETER ::  xm_Mg    =   24.30500e-3           !< Mg       molecular weight (kg/mol)
114    REAL, PARAMETER ::  xm_N     =   14.00670e-3           !< N        molecular weight (kg/mol)
115    REAL, PARAMETER ::  xm_Na    =   22.98977e-3           !< Na       molecular weight (kg/mol)
116    REAL, PARAMETER ::  xm_O     =   15.99940e-3           !< O        molecular weight (kg/mol)
117    REAL, PARAMETER ::  xm_Pb    =  207.20000e-3           !< Pb       molecular weight (kg/mol)
118    REAL, PARAMETER ::  xm_Pb210 =  210.00000e-3           !< Pb (210) molecular weight (kg/mol)
119    REAL, PARAMETER ::  xm_Rn222 =  222.00000e-3           !< Rn (222) molecular weight (kg/mol)
120    REAL, PARAMETER ::  xm_S     =   32.06400e-3           !< S        molecular weight (kg/mol)
121    REAL, PARAMETER ::  xm_CO2   = xm_C + xm_O * 2         !< CO2      molecular weight (kg/mol)
122    REAL, PARAMETER ::  xm_h2o   = xm_H * 2 + xm_O         !< H2O      molecular weight (kg/mol)
123    REAL, PARAMETER ::  xm_HNO3  = xm_H + xm_N + xm_O * 3  !< HNO3     molecular weight (kg/mol)
124    REAL, PARAMETER ::  xm_o3    = xm_O * 3                !< O3       molecular weight (kg/mol)
125    REAL, PARAMETER ::  xm_N2O5  = xm_N * 2 + xm_O * 5     !< N2O5     molecular weight (kg/mol)
126    REAL, PARAMETER ::  xm_NH4   = xm_N + xm_H * 4         !< NH4      molecular weight (kg/mol)
127    REAL, PARAMETER ::  xm_NO3   = xm_N + xm_O * 3         !< NO3      molecular weight (kg/mol)
128    REAL, PARAMETER ::  xm_SO4   = xm_S + xm_O * 4         !< SO4      molecular weight (kg/mol)
129
130    CHARACTER (LEN=20) ::  bc_cs_b        = 'dirichlet'         !< namelist parameter: surface
131                                                                !< boundary condition for concentration
132    CHARACTER (LEN=20) ::  bc_cs_l        = 'undefined'         !< left boundary condition
133    CHARACTER (LEN=20) ::  bc_cs_n        = 'undefined'         !< north boundary condition
134    CHARACTER (LEN=20) ::  bc_cs_r        = 'undefined'         !< right boundary condition
135    CHARACTER (LEN=20) ::  bc_cs_s        = 'undefined'         !< south boundary condition
136    CHARACTER (LEN=20) ::  bc_cs_t        = 'initial_gradient'  !< namelist parameter: top boudary
137                                                                !< condition for concentration
138    CHARACTER (LEN=30) ::  chem_mechanism = 'phstatp'           !< namelist parameter: chemistry
139                                                                !< mechanism
140    CHARACTER (LEN=80) ::  daytype_mdh    = 'workday'           !< namelist parameter: type of day
141                                                                !< - workday, weekend, holiday
142    CHARACTER (LEN=80) ::  mode_emis      = 'PARAMETERIZED'     !< namelist parameter: mode of
143                                                                !< chemistry emissions -
144                                                                !< DEFAULT, EXPERT, PARAMETERIZED
145    CHARACTER (LEN=10) ::  photolysis_scheme                    !< 'constant',
146                                                                !< 'simple' (Simple parameterisation from MCM,
147                                                                !< Saunders et al., 2003, Atmos. Chem. Phys., 3, 161-180
148                                                                !< 'fastj'  (Wild et al., 2000, J. Atmos. Chem., 37, 245-282)
149                                                                !< STILL NOT IMPLEMENTED
150    CHARACTER (LEN=80) ::  time_fac_type  = 'MDH'               !< namelist parameter: type of time treatment in the mode_emis
151                                                                !< DEFAULT - HOUR, MDH
152
153    CHARACTER (LEN=11), DIMENSION(99) ::  cs_name             = 'novalue'  !< namelist parameter:
154                                                                           !<names of species with given fluxes
155                                                                           !< (see csflux)
156    CHARACTER (LEN=11), DIMENSION(99) ::  cs_profile_name     = 'novalue'  !< namelist parameter:
157                                                                           !< tbc...???
158    CHARACTER (LEN=11), DIMENSION(99) ::  data_output_pr_cs   = 'novalue'  !< namelist parameter:
159                                                                           !< tbc...???
160    CHARACTER (LEN=11), DIMENSION(99) ::  surface_csflux_name = 'novalue'  !< namelist parameter:
161                                                                           !< tbc...???
162
163    INTEGER(iwp) ::  communicator_chem      !< stores the number of the MPI communicator to be used
164                                            !< for ghost layer data exchange
165                                            !< 1: cyclic, 2: cyclic along x, 3: cyclic along y,
166                                            !< 4: non-cyclic
167
168    INTEGER(iwp) ::  cs_pr_count_fl_res                    = 0      !< counter for vertical flux profiles of chemical species (resolved-scale)
169    INTEGER(iwp) ::  cs_pr_count_fl_sgs                    = 0      !< counter for vertical flux profiles of chemical species (SGS)
170    INTEGER(iwp) ::  cs_pr_count_sp                        = 0      !< counter for chemical species profiles
171    INTEGER(iwp) ::  cs_vertical_gradient_level_ind(99,10) = -9999  !< grid index values of
172                                                                    !< cs_vertical_gradient_level
173    INTEGER(iwp) ::  emiss_lod                             = -1     !< namelist parameter: chem emission LOD (same as mode_emis)
174                                                                    !< -1 = unassigned, 0 = parameterized, 1 = default,
175                                                                    !< 2 = pre-processed
176    INTEGER(iwp) ::  ibc_cs_b                                       !< integer flag for bc_cs_b
177    INTEGER(iwp) ::  ibc_cs_t                                       !< integer flag for bc_cs_t
178    INTEGER(iwp) ::  main_street_id                        = 0      !< namelist parameter: lower bound of main street IDs
179                                                                    !< (OpenStreetMaps) for PARAMETERIZED mode
180    INTEGER(iwp) ::  max_pr_cs                             = 0      !< number of chemistry profiles in output
181    INTEGER(iwp) ::  max_street_id                         = 0      !< namelist parameter: upper bound of main street IDs
182                                                                    !< (OpenStreetMaps) for PARAMETERIZED mode
183    INTEGER(iwp) ::  n_matched_vars                                 !< number of matched emissions
184                                                                    !< variables
185    INTEGER(iwp) ::  side_street_id                        = 0      !< namelist parameter: lower bound of side street IDs
186                                                                    !< (OpenStreetMaps) for PARAMETERIZED mode
187
188    INTEGER(iwp), DIMENSION(99) ::  cs_pr_index_sp      = 0 !< index for chemical species mean profiles
189    INTEGER(iwp), DIMENSION(99) ::  cs_pr_index_fl_res  = 0 !< index for chemical species sgs-flux profiles
190    INTEGER(iwp), DIMENSION(99) ::  cs_pr_index_fl_sgs  = 0 !< index for chemical species resolved-scale flux profiles
191    INTEGER(iwp), DIMENSION(99) ::  hom_index_fl_res    = 0 !< index of the resolved-scale flux profile with respect to the hom array
192    INTEGER(iwp), DIMENSION(99) ::  hom_index_fl_sgs    = 0 !< index of the SGS flux profile with respect to the hom array
193    INTEGER(iwp), DIMENSION(99) ::  hom_index_spec      = 0 !< index of the profile with respect to the hom array
194    INTEGER(iwp), DIMENSION(:)  ::  match_spec_nox(1:2)     !< results of matching the input and model's NOx
195    INTEGER(iwp), DIMENSION(:)  ::  match_spec_pm(1:3)      !< results of matching the input and model's PMs
196    INTEGER(iwp), DIMENSION(:)  ::  match_spec_sox(1:2)     !< results of matching the input and model's SOx!
197
198    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_spec_input      !< index of input chem species
199                                                                      !< for matching routine
200    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_spec_model      !< index of model chem species#
201                                                                      !< for matching routine
202    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_spec_voc_input  !< index of VOC input
203                                                                      !< components matching the model's VOCs
204    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_spec_voc_model  !< index of VOC model species
205                                                                      !< matching the input VOCs comp.
206
207    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE  ::  cs_advc_flags_s !< flags used to degrade order of advection scheme for
208                                                                     !< chemical species near walls and lateral boundaries
209
210    LOGICAL ::  bc_dirichlet_cs_l         = .FALSE.  !< flag for indicating a dirichlet condition at
211                                                     !< the left boundary
212    LOGICAL ::  bc_dirichlet_cs_n         = .FALSE.  !< flag for indicating a dirichlet condition at
213                                                     !< the north boundary
214    LOGICAL ::  bc_dirichlet_cs_r         = .FALSE.  !< flag for indicating a dirichlet condition at
215                                                     !< the right boundary
216    LOGICAL ::  bc_dirichlet_cs_s         = .FALSE.  !< flag for indicating a dirichlet condition at
217                                                     !< the south boundary
218    LOGICAL ::  bc_radiation_cs_l         = .FALSE.  !< flag for indicating a radiation/neumann
219                                                     !< condition at the left boundary
220    LOGICAL ::  bc_radiation_cs_n         = .FALSE.  !< flag for indicating a radiation/neumann
221                                                     !< condition at the north boundary
222    LOGICAL ::  bc_radiation_cs_r         = .FALSE.  !< flag for indicating a radiation/neumann
223                                                     !< condition at the right boundary
224    LOGICAL ::  bc_radiation_cs_s         = .FALSE.  !< flag for indicating a radiation/neumann
225                                                     !< condition at the south boundary
226    LOGICAL ::  constant_top_csflux(99)   = .TRUE.   !< internal flag, set to .FALSE. if no
227                                                     !< top_csflux is prescribed
228    LOGICAL ::  constant_csflux(99)       = .TRUE.   !< internal flag, set to .FALSE. if no
229                                                     !< surface_csflux is prescribed
230    LOGICAL ::  call_chem_at_all_substeps = .FALSE.  !< namelist parameter: ....???
231    LOGICAL ::  chem_debug0               = .FALSE.  !< namelist parameter: flag for minimum print
232                                                     !< output
233    LOGICAL ::  chem_debug1               = .FALSE.  !< namelist parameter: flag for print output
234    LOGICAL ::  chem_debug2               = .FALSE.  !< namelist parameter: flag for further print
235                                                     !< output
236    LOGICAL ::  chem_gasphase_on          = .TRUE.   !< namelist parameter: flag to switch off
237                                                     !< chemical reactions
238    LOGICAL ::  cs_pr_namelist_found      = .FALSE.  !< ...???
239    LOGICAL ::  deposition_dry            = .FALSE.  !< namelist parameter: flag for activation of
240                                                     !< deposition calculation
241    LOGICAL ::  emissions_anthropogenic   = .FALSE.  !< namelist parameter: flag for turning on
242                                                     !< anthropogenic emissions
243    LOGICAL ::  emission_output_required  = .TRUE.   !< internal flag for requiring emission outputs
244    LOGICAL ::  emiss_read_legacy_mode    = .TRUE.   !< namelist parameter: flag to read emission
245                                                     !< data using legacy mode
246    LOGICAL ::  nesting_chem              = .TRUE.   !< apply self-nesting for the chemistry model
247    LOGICAL ::  nesting_offline_chem      = .TRUE.   !< apply offline nesting for the chemistry
248                                                     !< model
249
250    REAL(wp) ::  cs_surface_initial_change(99)     = 0.0_wp        !< namelist parameter: ...???
251    REAL(wp) ::  cs_vertical_gradient(99,10)       = 0.0_wp        !< namelist parameter: ...???
252    REAL(wp) ::  cs_vertical_gradient_level(99,10) = -999999.9_wp  !< namelist parameter: ...???
253    REAL(wp) ::  emiss_factor_main(99)             = -9999.0_wp    !< namelist parameter: ...???
254    REAL(wp) ::  emiss_factor_side(99)             = -9999.0_wp    !< namelist parameter: ...???
255    REAL(wp) ::  surface_csflux(99)                = 0.0_wp        !< namelist parameter: ...???
256    REAL(wp) ::  top_csflux(99)                    = 0.0_wp        !< namelist parameter: ...???
257    REAL(wp) ::  wall_csflux(99,0:5)               = 0.0_wp        !< namelist parameter: ...???
258
259    REAL(wp), DIMENSION(99)     ::  cs_surface = 0.0_wp        !< namelist parameter: chem species
260                                                               !< concentration at surface
261    REAL(wp), DIMENSION(99,100) ::  cs_heights = 9999999.9_wp  !< namelist parameter: height levels
262                                                               !< for initial chem species concentrations
263    REAL(wp), DIMENSION(99,100) ::  cs_profile = 9999999.9_wp  !< namelist parameter: chem species
264                                                               !< concentration values at cs_heights levels
265
266    REAL(wp), DIMENSION(:), ALLOCATABLE ::  bc_cs_t_val  !< vertical gradient of chemical species
267                                                         !< near domain top
268    REAL(wp), DIMENSION(:), ALLOCATABLE ::  css          !< scaling parameter for chem species
269
270    REAL(wp), DIMENSION(:,:,:),   ALLOCATABLE, TARGET ::  sums_ws_l  !< subdomain sum of vertical chemistry flux w'ch'
271
272    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  emis_distribution  !< emissions final values (main module output) ???
273
274    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_1  !< pointer for swapping of
275                                                                !< timelevels for respective quantity
276    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_2  !< pointer for swapping of
277                                                                !< timelevels for respective quantity
278    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_3  !< pointer for swapping of
279                                                                !< timelevels for respective quantity
280
281    REAL(wp), DIMENSION(:,:,:), POINTER ::  cs     !< pointer: sgs chem spcs  ???
282    REAL(wp), DIMENSION(:,:,:), POINTER ::  cs_p   !< pointer: prognostic value of sgs chem spcs ???
283    REAL(wp), DIMENSION(:,:,:), POINTER ::  tcs_m  !< pointer: to tcs array (temp)
284
285!
286!-  Define chemical variables within chem_species
287    TYPE species_def
288
289       CHARACTER(LEN=15)                            ::  name         !< name of chemical species
290       CHARACTER(LEN=15)                            ::  unit         !< unit (ppm for gases, kg m^-3
291                                                                     !< for aerosol tracers)
292
293       REAL(kind=wp), ALLOCATABLE, DIMENSION(:)     ::  conc_pr_init !< initial profile of chemical
294                                                                     !< species
295
296       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  cssws_av     !< averaged fluxes of trace
297                                                                     !< gases at surface
298       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  flux_s_cs    !< 6th-order advective flux at
299                                                                     !< south face of grid box of chemical species (='cs')
300       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  diss_s_cs    !< artificial numerical dissipation
301                                                                     !< flux at south face of grid box of chemical species
302
303       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:) ::  conc_av      !< averaged concentrations
304       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:) ::  flux_l_cs    !< 6th-order advective flux at
305                                                                     !< left face of grid box of chemical species (='cs')
306       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:) ::  diss_l_cs    !< artificial numerical dissipation
307                                                                     !< flux at left face of grid box of chemical species
308
309       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  conc         !< concentrations of trace
310                                                                     !< gases
311       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  conc_p       !< conc at prognostic time
312                                                                     !< level
313       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  tconc_m      !< weighted tendency of conc
314                                                                     !< for previous sub-timestep (Runge-Kutta)
315
316    END TYPE species_def
317!
318!-- Define photolysis frequencies in phot_frequen
319    TYPE photols_def
320
321       CHARACTER(LEN=15)                            :: name          !< name of pgotolysis frequency
322       CHARACTER(LEN=15)                            :: unit          !< unit (1/s)
323
324       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     :: freq          !< photolysis frequency
325
326    END TYPE photols_def
327
328
329    TYPE(species_def), ALLOCATABLE, DIMENSION(:), TARGET ::  chem_species
330    TYPE(photols_def), ALLOCATABLE, DIMENSION(:), TARGET ::  phot_frequen
331
332    SAVE
333
334 END MODULE chem_modules
Note: See TracBrowser for help on using the repository browser.