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

Last change on this file since 3398 was 3298, checked in by kanani, 5 years ago

Merge chemistry branch at r3297 to trunk

  • Property svn:keywords set to Id
File size: 10.4 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 3298 2018-10-02 12:21:11Z knoop $
29! - Minor formatting
30! - Introduced Variables for Chemistry emissions Module (Russo)
31! - Variables and parameters added for 2d and profile output (basit)
32! - Converted scalar  emission factors  to 1-D array of 99 elements each (basit)
33! - Removed "__chem" directive (basit)
34!
35! 3282 2018-09-27 10:49:12Z basit
36! Initial revision
37!
38!
39!
40!
41! Authors:
42! --------
43! @author Farah Kanani-Suehring
44! @author Basit Khan
45!
46!------------------------------------------------------------------------------!
47! Description:
48! ------------
49!> Definition of global palm-4u chemistry variables
50!> (Module written to define global palm-4u chemistry variables. basit 16Nov2017)
51!------------------------------------------------------------------------------!
52!
53 MODULE chem_modules
54
55    USE chem_gasphase_mod,                                                     &   
56        ONLY: nspec, nvar, spc_names
57
58    USE control_parameters,                                                    &
59        ONLY: varnamelength
60
61    USE kinds
62
63    USE statistics,                                                            &
64        ONLY: pr_palm
65
66
67    IMPLICIT NONE
68
69    PUBLIC nspec
70    PUBLIC nvar
71    PUBLIC spc_names
72
73    INTEGER(iwp), DIMENSION(99)  :: cs_pr_index            = 0
74    INTEGER(iwp)  :: ibc_cs_b                                                      !< integer flag for bc_cs_b
75    INTEGER(iwp)  :: ibc_cs_t                                                      !< integer flag for bc_cs_t
76    INTEGER(iwp)  :: cs_pr_count                           = 0 
77    INTEGER(iwp)  :: max_pr_cs                             = 0
78    INTEGER(iwp)  :: cs_vertical_gradient_level_ind(99,10) = -9999                 !< grid index values of cs_vertical_gradient_level_ind(s)
79
80    LOGICAL       :: constant_top_csflux(99)               = .TRUE.                !< chem spcs at the top  orig .TRUE.
81    LOGICAL       :: constant_csflux(99)                   = .TRUE.                !< chem spcs at namelist parameter   orig TRUE
82    LOGICAL       :: call_chem_at_all_substeps             = .FALSE.               !< namelist parameter
83    LOGICAL       :: chem_debug0                           = .FALSE.               !< namelist parameter flag for minimum print output
84    LOGICAL       :: chem_debug1                           = .FALSE.               !< namelist parameter flag for print output
85    LOGICAL       :: chem_debug2                           = .FALSE.               !< namelist parameter flag for further print output
86    LOGICAL       :: chem_gasphase_on                      = .TRUE.                !< namelist parameter
87    LOGICAL       :: emission_output_required              = .TRUE.                !< Logical Variable for requiring Emission Outputs
88    LOGICAL       :: do_emis                               = .FALSE.               !< Flag for turning on chemistry emissions
89    LOGICAL       :: cs_pr_namelist_found                  = .FALSE.               !< Namelist parameter: Names of t
90
91
92
93!-- Namelist parameters for creating initial chemistry profiles
94    REAL(wp) :: wall_csflux (99,0:5)               = 0.0_wp                        !< namelist parameter
95    REAL(wp) :: cs_vertical_gradient (99,10)       = 0.0_wp                        !< namelist parameter
96    REAL(wp) :: cs_vertical_gradient_level (99,10) = -999999.9_wp                  !< namelist parameter
97    REAL(wp) :: top_csflux ( 99 )                  = 0.0_wp                        !< namelist parameter
98    REAL(wp) :: cs_surface_initial_change(99)      = 0.0_wp                        !< namelist parameter
99    REAL(wp) :: surface_csflux(99 )                = 0.0_wp                        !< namelist parameter: fluxes where 'surface_csflux_name' is in the namelist
100
101    REAL(wp), DIMENSION(:),  ALLOCATABLE              :: bc_cs_t_val
102    REAL(wp), DIMENSION(:),  ALLOCATABLE              ::  css                      !< scaling parameter for chem spcs
103    REAL(wp), DIMENSION(99)                           :: cs_surface = 0.0_wp       !< Namelist parameter: Surface conc of chem spcs'
104    REAL(wp), DIMENSION(99,100)                       :: cs_heights = 9999999.9_wp !< Namelist parameter: Height lvls(m) for cs_profiles
105    REAL(wp), DIMENSION(99,100)                       :: cs_profile = 9999999.9_wp !< Namelist parameter: Chem conc for each spcs defined
106
107
108#if defined( __nopointer )
109    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET   :: cs                        !< chem spcs
110    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET   :: cs_p                      !< prognostic value of chem spc
111    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET   :: tcs_m                     !< weighted tendency of cs for previous sub-timestep (Runge-Kutta)
112
113#else                                                               
114! use pointers cs, cs_p and tcs_m to point arrays cs_1, cs_2, and cs_3
115    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET :: cs_1                      !< pointer for swapping of timelevels for respective quantity
116    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET :: cs_2                      !< pointer for swapping of timelevels for respective quantity
117    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET :: cs_3                      !< pointer for swapping of timelevels for respective quantity
118    REAL(wp), DIMENSION(:,:,:), POINTER               :: cs                        !< pointer: sgs chem spcs)
119    REAL(wp), DIMENSION(:,:,:), POINTER               :: cs_p                      !< pointer: prognostic value of sgs chem spcs
120    REAL(wp), DIMENSION(:,:,:), POINTER               :: tcs_m                     !< pointer:
121
122#endif                                                                           
123 
124    CHARACTER (LEN=20)                 :: bc_cs_b             = 'dirichlet'        !< namelist parameter
125    CHARACTER (LEN=20)                 :: bc_cs_t             = 'initial_gradient' !< namelist parameter
126    CHARACTER (LEN=11), DIMENSION(99)  :: cs_name             = 'novalue'          !< Namelist parameter: chem spcs names
127    CHARACTER (LEN=11), DIMENSION(99)  :: cs_profile_name     = 'novalue'          !< Namelist parameter: Names of the chem for profiles
128    CHARACTER (LEN=11), DIMENSION(99)  :: surface_csflux_name = 'novalue'          !< Namelist parameter: chem species surface fluxes names
129                                                                                   !< active chem spcs, default is 'novalue')  ????
130    CHARACTER (LEN=80)                 :: mode_emis           ='PARAMETERIZED'     !< Mode of chemistry emissions: DEFAULT .OR. EXPERT .OR.
131                                                                                   !  PARAMETERIZED
132    CHARACTER (LEN=80)                 :: time_fac_type       ='MDH'               !< Type of time treatment in the emis DEFAULT mode: HOUR .OR. MDH
133    CHARACTER (LEN=80)                 :: daytype_mdh         ='workday'           !< Type of day in the MDH case: workday, weekend, holiday
134    CHARACTER (LEN=11), DIMENSION(99)  :: data_output_pr_cs   = 'novalue'          !< Namelist parameter: Names of the che    m for profile output
135                                                                                   !< by cs_name for each height lvls defined by cs_heights
136!
137!-- Namelist parameters for chem_emissions
138    INTEGER(iwp) ::  main_street_id = 0
139    INTEGER(iwp) ::  max_street_id  = 0
140    INTEGER(iwp) ::  side_street_id = 0
141!
142!-- Constant emission factors
143    REAL(wp) ::  emiss_factor_main ( 99 ) = -9999.0_wp
144    REAL(wp) ::  emiss_factor_side ( 99 ) = -9999.0_wp
145   
146!-- Other Emissions Variables
147    INTEGER(iwp) ::  nspec_out                                                     !< Output of routine chem_emis_matching with
148                                                                                   !< number of matched species
149    REAL(wp),ALLOCATABLE, DIMENSION(:,:,:,:)         :: emis_distribution          !> Emissions Final Values (main module output)
150
151    INTEGER(iwp),ALLOCATABLE,DIMENSION(:)            :: match_spec_input           !< Index of Input chem species for matching routine
152    INTEGER(iwp),ALLOCATABLE,DIMENSION(:)            :: match_spec_model           !< Index of Model chem species for matching routine
153    INTEGER(iwp),ALLOCATABLE,DIMENSION(:)            :: match_spec_voc_input       !< index of VOC input components matching the model's VOCs
154    INTEGER(iwp),ALLOCATABLE,DIMENSION(:)            :: match_spec_voc_model       !< index of VOC model species matching the input VOCs comp.
155    INTEGER(iwp),DIMENSION(:)                        :: match_spec_pm(1:3)         !< results of matching the input and model's PMs
156    INTEGER(iwp),DIMENSION(:)                        :: match_spec_nox(1:2)        !< results of matching the input and model's NOx
157    INTEGER(iwp),DIMENSION(:)                        :: match_spec_sox(1:2)        !< results of matching the input and model's SOx!
158                                                                                   ! TBD: evaluate whether to make them allocatable
159                                                                                   ! and allocate their dimension in the matching
160                                                                                   ! routine according to the number of components
161                                                                                   ! matching between the model and the input files
162
163    SAVE
164 END MODULE chem_modules
165
Note: See TracBrowser for help on using the repository browser.