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

Last change on this file since 3822 was 3820, checked in by forkel, 5 years ago

renaming of get_mechanismname, do_emiss and do_depo, sorting in chem_modules

  • Property svn:keywords set to Id
File size: 13.7 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-2018 Leibniz Universitaet Hannover
18! Copyright 2018-2018 Karlsruhe Institute of Technology
19! Copyright 2018-2018 Freie Universitaet Berlin
20!------------------------------------------------------------------------------!
21!
22! Current revisions:
23! -----------------
24!
25!
26! Former revisions:
27! -----------------
28! $Id: chem_modules.f90 3820 2019-03-27 11:53:41Z hellstea $
29! renamed do_emis to emissions_anthropogenic, removed USE statistics, variables sorted by type
30!
31!
32! 3780 2019-03-05 11:19:45Z forkel
33! added cs_mech
34!
35! 3652 2019-01-07 15:29:59Z forkel
36! parameter chem_mechanism added (basit)
37!
38! 3636 2018-12-19 13:48:34Z raasch
39! nopointer option removed
40!
41! 3611 2018-12-07 14:14:11Z banzhafs
42! Minor formatting
43!
44! 3458 2018-10-30 14:51:23Z kanani
45! from chemistry branch r3443:
46! ??
47!
48! 3298 2018-10-02 12:21:11Z kanani
49! - Minor formatting
50! - Introduced Variables for Chemistry emissions Module (Russo)
51! - Variables and parameters added for 2d and profile output (basit)
52! - Converted scalar  emission factors  to 1-D array of 99 elements each (basit)
53! - Removed "__chem" directive (basit)
54!
55! 3282 2018-09-27 10:49:12Z basit
56! Initial revision
57!
58! Authors:
59! --------
60! @author Farah Kanani-Suehring
61! @author Basit Khan
62! @author Sabine Banzhaf
63! @author Emmanuele Russo
64! @author Edward C. Chan
65!
66!------------------------------------------------------------------------------!
67! Description:
68! ------------
69!> Definition of global PALM-4U chemistry variables
70!------------------------------------------------------------------------------!
71!
72 MODULE chem_modules
73
74    USE chem_gasphase_mod,                                                     &   
75        ONLY: cs_mech, nspec, nvar, spc_names
76
77    USE control_parameters,                                                    &
78        ONLY: varnamelength
79
80    USE kinds
81
82    IMPLICIT NONE
83
84    PUBLIC cs_mech
85    PUBLIC nspec
86    PUBLIC nvar
87    PUBLIC spc_names
88
89    CHARACTER (LEN=20)                ::  bc_cs_b             = 'dirichlet'         !< namelist parameter
90    CHARACTER (LEN=20)                ::  bc_cs_t             = 'initial_gradient'  !< namelist parameter
91    CHARACTER (LEN=30)                ::  chem_mechanism      = 'phstatp'           !< KPP chmical mechanism
92    CHARACTER (LEN=11), DIMENSION(99) ::  cs_name             = 'novalue'           !< Namelist parameter: chem spcs names
93    CHARACTER (LEN=11), DIMENSION(99) ::  cs_profile_name     = 'novalue'           !< Namelist parameter: Names of the chem for profiles
94    CHARACTER (LEN=11), DIMENSION(99) ::  data_output_pr_cs   = 'novalue'           !< Namelist parameter: Names of the chem species for profile output
95                                                                                    !< by cs_name for each height lvls defined by cs_heights
96    CHARACTER (LEN=80)                ::  daytype_mdh         ='workday'            !< Type of day in the MDH case: workday, weekend, holiday
97    CHARACTER (LEN=80)                ::  mode_emis           ='PARAMETERIZED'      !< Mode of chemistry emissions: DEFAULT .OR. EXPERT .OR.
98                                                                                    !< PARAMETERIZED
99    CHARACTER (LEN=11), DIMENSION(99) ::  surface_csflux_name = 'novalue'           !< Namelist parameter: chem species names with surface fluxes specified
100                                                                                    !< active chem spcs, default is 'novalue')  ????
101    CHARACTER (LEN=80)                ::  time_fac_type       ='MDH'                !< Type of time treatment in the emis DEFAULT mode: HOUR .OR. MDH
102
103    INTEGER(iwp), DIMENSION(99)            ::  cs_pr_index                           = 0      !< index for chemical species profile (ecc)
104    INTEGER(iwp)                           ::  cs_pr_count                           = 0      !< namelist parameter : No. of species profiles (ecc)
105    INTEGER(iwp)                           ::  cs_vertical_gradient_level_ind(99,10) = -9999  !< grid index values of cs_vertical_gradient_level_ind(s)
106    INTEGER(iwp)                           ::  ibc_cs_b                                       !< integer flag for bc_cs_b
107    INTEGER(iwp)                           ::  ibc_cs_t                                       !< integer flag for bc_cs_t
108    INTEGER(iwp),ALLOCATABLE,DIMENSION(:)  ::  match_spec_input                               !< Index of Input chem species for matching routine
109    INTEGER(iwp),ALLOCATABLE,DIMENSION(:)  ::  match_spec_model                               !< Index of Model chem species for matching routine
110    INTEGER(iwp),DIMENSION(:)              ::  match_spec_nox(1:2)                            !< results of matching the input and model's NOx
111    INTEGER(iwp),DIMENSION(:)              ::  match_spec_pm(1:3)                             !< results of matching the input and model's PMs
112    INTEGER(iwp),DIMENSION(:)              ::  match_spec_sox(1:2)                            !< results of matching the input and model's SOx!
113    INTEGER(iwp),ALLOCATABLE,DIMENSION(:)  ::  match_spec_voc_input                           !< index of VOC input components matching the model's VOCs
114    INTEGER(iwp),ALLOCATABLE,DIMENSION(:)  ::  match_spec_voc_model                           !< index of VOC model species matching the input VOCs comp.
115    INTEGER(iwp)                           ::  main_street_id                        = 0      !< namelist parameter for chem_emissions : ID for main streets 
116    INTEGER(iwp)                           ::  max_pr_cs                             = 0      !< namelist parameter : Max no. of species profiles (ecc)
117    INTEGER(iwp)                           ::  max_street_id                         = 0      !< namelist parameter for chem_emissions : maximum street IDs     
118    INTEGER(iwp)                           ::  nspec_out                                      !< Output of routine chem_emis_matching with
119    INTEGER(iwp)                           ::  side_street_id                        = 0      !< namelist paramtger for chem_emissions : ID for side streets
120
121    LOGICAL      ::  constant_top_csflux(99)               = .TRUE.   !< chem spcs at the top  orig .TRUE.
122    LOGICAL      ::  constant_csflux(99)                   = .TRUE.   !< chem spcs at namelist parameter   orig TRUE
123    LOGICAL      ::  call_chem_at_all_substeps             = .FALSE.  !< namelist parameter
124    LOGICAL      ::  chem_debug0                           = .FALSE.  !< namelist parameter flag for minimum print output
125    LOGICAL      ::  chem_debug1                           = .FALSE.  !< namelist parameter flag for print output
126    LOGICAL      ::  chem_debug2                           = .FALSE.  !< namelist parameter flag for further print output
127    LOGICAL      ::  chem_gasphase_on                      = .TRUE.   !< namelist parameter
128    LOGICAL      ::  emission_output_required              = .TRUE.   !< Logical Variable for requiring Emission Outputs
129    LOGICAL      ::  cs_pr_namelist_found                  = .FALSE.  !< Namelist parameter: Names of t
130    LOGICAL      ::  deposition_dry                        = .FALSE.  !< namelist parameter for activation of deposition calculation
131    LOGICAL      ::  emissions_anthropogenic               = .FALSE.  !< Flag for turning on anthropogenic emissions
132!
133!-- Namelist parameters for creating initial chemistry profiles
134    REAL(wp)                                          ::  cs_surface_initial_change(99)     = 0.0_wp        !< namelist parameter : initial surface flux difference
135    REAL(wp)                                          ::  cs_vertical_gradient(99,10)       = 0.0_wp        !< namelist parameter : vertical gradient
136    REAL(wp)                                          ::  cs_vertical_gradient_level(99,10) = -999999.9_wp  !< namelist parameter : vertical gradient level
137    REAL(wp)                                          ::  surface_csflux(99)                = 0.0_wp        !< namelist parameter : fluxes where 'surface_csflux_name' is
138                                                                                                            !< in the namelist
139    REAL(wp)                                          ::  top_csflux(99)                    = 0.0_wp        !< namelist parameter : chemical species flux at ceiling
140    REAL(wp)                                          ::  wall_csflux(99,0:5)               = 0.0_wp        !< namelist parameter : chemical species flux lateral
141    REAL(wp), DIMENSION(:), ALLOCATABLE               ::  bc_cs_t_val                                       !< chemical specices time value at BC
142    REAL(wp), DIMENSION(:,:,:), POINTER               ::  cs                                                !< pointer: sgs chem spcs)
143    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_1                                              !< pointer for swapping of timelevels for respective quantity
144    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_2                                              !< pointer for swapping of timelevels for respective quantity
145    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_3                                              !< pointer for swapping of timelevels for respective quantity
146    REAL(wp), DIMENSION(:,:,:), POINTER               ::  cs_p                                              !< pointer: prognostic value of sgs chem spcs
147    REAL(wp), DIMENSION(:), ALLOCATABLE               ::  css                                               !< scaling parameter for chem spcs
148    REAL(wp), DIMENSION(99,100)                       ::  cs_profile                        = 9999999.9_wp  !< Namelist parameter: Chem conc for each spcs defined
149    REAL(wp), DIMENSION(99,100)                       ::  cs_heights                        = 9999999.9_wp  !< Namelist parameter: Height lvls(m) for cs_profiles
150    REAL(wp), DIMENSION(99)                           ::  cs_surface                        = 0.0_wp        !< Namelist parameter: Surface conc of chem spcs'
151    REAL(wp),ALLOCATABLE, DIMENSION(:,:,:,:)          ::  emis_distribution                                 !< Emissions Final Values (main module output)
152    REAL(wp)                                          ::  emiss_factor_main(99)             = -9999.0_wp    !< emission factor for main streets
153    REAL(wp)                                          ::  emiss_factor_side(99)             = -9999.0_wp    !< emission factor for side streets
154    REAL(wp), DIMENSION(:,:,:), POINTER               ::  tcs_m                                             !< pointer: to tcs array (temp)
155!
156!-- molecular weights
157    REAL, PARAMETER        ::  xm_air   =   28.964e-3             !< air      molecular weight (kg/mol)
158    REAL, PARAMETER        ::  xm_C     =   12.01115e-3           !< C        molecular weight (kg/mol)
159    REAL, PARAMETER        ::  xm_Ca    =   40.07800e-3           !< Ca       molecular weight (kg/mol)
160    REAL, PARAMETER        ::  xm_Cd    =  112.41000e-3           !< Cd       molecular weight (kg/mol)
161    REAL, PARAMETER        ::  xm_Cl    =   35.45300e-3           !< Cl       molecular weight (kg/mol)
162    REAL, PARAMETER        ::  xm_dummy = 1000.0e-3               !< dummy    molecular weight (kg/mol)
163    REAL, PARAMETER        ::  xm_F     =   18.99840e-3           !< F        molecular weight (kg/mol)
164    REAL, PARAMETER        ::  xm_H     =    1.00790e-3           !< H        molecular weight (kg/mol)
165    REAL, PARAMETER        ::  xm_K     =   39.09800e-3           !< K        molecular weight (kg/mol)
166    REAL, PARAMETER        ::  xm_Mg    =   24.30500e-3           !< Mg       molecular weight (kg/mol)
167    REAL, PARAMETER        ::  xm_N     =   14.00670e-3           !< N        molecular weight (kg/mol)
168    REAL, PARAMETER        ::  xm_Na    =   22.98977e-3           !< Na       molecular weight (kg/mol)
169    REAL, PARAMETER        ::  xm_O     =   15.99940e-3           !< O        molecular weight (kg/mol)
170    REAL, PARAMETER        ::  xm_Pb    =  207.20000e-3           !< Pb       molecular weight (kg/mol)
171    REAL, PARAMETER        ::  xm_Pb210 =  210.00000e-3           !< Pb (210) molecular weight (kg/mol)
172    REAL, PARAMETER        ::  xm_Rn222 =  222.00000e-3           !< Rn (222) molecular weight (kg/mol)
173    REAL, PARAMETER        ::  xm_S     =   32.06400e-3           !< S        molecular weight (kg/mol)
174    REAL, PARAMETER        ::  xm_CO2   = xm_C + xm_O * 2         !< CO2      molecular weight (kg/mol)
175    REAL, PARAMETER        ::  xm_h2o   = xm_H * 2 + xm_O         !< H2O      molecular weight (kg/mol)
176    REAL, PARAMETER        ::  xm_HNO3  = xm_H + xm_N + xm_O * 3  !< HNO3     molecular weight (kg/mol)
177    REAL, PARAMETER        ::  xm_o3    = xm_O * 3                !< O3       molecular weight (kg/mol)
178    REAL, PARAMETER        ::  xm_N2O5  = xm_N * 2 + xm_O * 5     !< N2O5     molecular weight (kg/mol)
179    REAL, PARAMETER        ::  xm_NH4   = xm_N + xm_H * 4         !< NH4      molecular weight (kg/mol)
180    REAL, PARAMETER        ::  xm_NO3   = xm_N + xm_O * 3         !< NO3      molecular weight (kg/mol)
181    REAL, PARAMETER        ::  xm_SO4   = xm_S + xm_O * 4         !< SO4      molecular weight (kg/mol)
182
183    SAVE
184
185 END MODULE chem_modules
Note: See TracBrowser for help on using the repository browser.