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

Last change on this file since 2716 was 2696, checked in by kanani, 6 years ago

Merge of branch palm4u into trunk

  • Property svn:keywords set to Id
File size: 7.3 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 1997-2017 Leibniz Universitaet Hannover
18! Copyright 2017-2017 Karlsruhe Institute of Technology
19! Copyright 2017-2017 Freie Universitaet Berlin
20!------------------------------------------------------------------------------!
21!
22! Current revisions:
23! -----------------
24!
25!
26! Former revisions:
27! -----------------
28! $Id: chem_modules.f90 2696 2017-12-14 17:12:51Z kanani $
29! Initial revision
30!
31!
32!
33!
34! Authors:
35! --------
36! @author Farah Kanani-Suehring
37! @author Basit Khan
38!
39!------------------------------------------------------------------------------!
40! Description:
41! ------------
42!> Definition of global palm-4u chemistry variables
43!> (Module written to define global palm-4u chemistry variables. basit 16Nov2017)
44!------------------------------------------------------------------------------!
45!
46 MODULE chem_modules
47#if defined( __chem ) 
48    USE kinds 
49    USE chem_gasphase_mod,                                                     &   
50        ONLY: nspec, nvar, spc_names
51
52
53    IMPLICIT NONE
54
55    PUBLIC nspec
56    PUBLIC nvar
57    PUBLIC spc_names
58
59    LOGICAL ::  constant_top_csflux(99)            = .TRUE.                       !< chem spcs at the top  orig .TRUE.
60    LOGICAL ::  constant_csflux(99)                = .TRUE.                       !< chem spcs at namelist parameter   orig TRUE
61
62
63    INTEGER(iwp) :: cs_vertical_gradient_level_ind(99,10) = -9999                 !< grid index values of cs_vertical_gradient_level_ind(s)
64    REAL(wp),     DIMENSION(:),   ALLOCATABLE :: bc_cs_t_val
65    INTEGER(iwp)                              :: ibc_cs_b                         !< integer flag for bc_cs_b
66    INTEGER(iwp)                              :: ibc_cs_t                         !< integer flag for bc_cs_t
67
68    REAL(wp),      DIMENSION(:),  ALLOCATABLE ::  css                             !< scaling parameter for chem spcs
69
70!-- Namelist parameters for creating initial chemistry profiles
71    CHARACTER (LEN=20)               :: bc_cs_b    = 'dirichlet'                  !< namelist parameter
72    CHARACTER (LEN=20)               :: bc_cs_t    = 'initial_gradient'           !< namelist parameter
73    REAL(wp) :: wall_csflux (99,0:5)               = 0.0_wp                       !< namelist parameter
74    REAL(wp) :: cs_vertical_gradient (99,10)       = 0.0_wp                       !< namelist parameter
75    REAL(wp) :: cs_vertical_gradient_level (99,10) = -999999.9_wp                 !< namelist parameter
76    REAL(wp) :: top_csflux ( 99 )                  = 0.0_wp                       !< namelist parameter
77    REAL(wp) :: cs_surface_initial_change(99)      = 0.0_wp                       !< namelist parameter
78    REAL(wp) :: surface_csflux(99 )                = 0.0_wp                       !< namelist parameter: fluxes where 'surface_csflux_name' is in the namelist
79!   RFo: I do not know whether it makes sense to have 'constant_csflux=.TRUE. for only these species where
80!        no flux is given in the namelist. Let's choos surface_csflux=0.0 (and thus 'constant_csflux'=.TRUE.) as default
81!       To obtain  constant_csflux=.FALSE., set surface_csflux = 9999999.9 in the namelist
82!   @todo: need to think a bit more about constant_csflux for chemistry.
83
84    LOGICAL :: call_chem_at_all_substeps           = .FALSE.                      !< namelist parameter
85    LOGICAL :: chem_debug0                         = .FALSE.                      !< namelist parameter flag for minimum print output
86    LOGICAL :: chem_debug1                         = .FALSE.                      !< namelist parameter flag for print output
87    LOGICAL :: chem_debug2                         = .FALSE.                      !< namelist parameter flag for further print output
88    LOGICAL :: chem_gasphase_on                    = .TRUE.                       !< namelist parameter
89
90    CHARACTER (LEN=11), DIMENSION(99)         :: cs_name = 'novalue'              !< Namelist parameter: chem spcs names
91    CHARACTER (LEN=11), DIMENSION(99)         :: cs_profile_name = 'novalue'      !< Namelist parameter: Names of the
92    CHARACTER (LEN=11), DIMENSION(99)         :: surface_csflux_name = 'novalue'  !< Namelist parameter: chem species surface fluxes names
93                                                                                  !< active chem spcs, default is 'novalue')  ????
94    REAL(wp), DIMENSION(99)                   :: cs_surface = 0.0_wp              !< Namelist parameter: Surface conc of chem spcs'
95    REAL(wp), DIMENSION(99,100)               :: cs_heights = 9999999.9_wp        !< Namelist parameter: Height lvls(m) for cs_profiles
96    REAL(wp), DIMENSION(99,100)               :: cs_profile = 9999999.9_wp        !< Namelist parameter: Chem conc for each spcs defined
97
98#if defined( __nopointer )
99    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET   :: cs                       !< chem spcs
100    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET   :: cs_p                     !< prognostic value of chem spc
101    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET   :: tcs_m                    !< weighted tendency of s for previous sub-timestep (Runge-Kutta)
102
103#else                                                               
104! use pointers cs, cs_p and tcs_m to point arrays cs_1, cs_2, and cs_3
105    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET :: cs_1                     !< pointer for swapping of timelevels for respective quantity
106    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET :: cs_2                     !< pointer for swapping of timelevels for respective quantity
107    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET :: cs_3                     !< pointer for swapping of timelevels for respective quantity
108
109    REAL(wp), DIMENSION(:,:,:), POINTER               :: cs                       !< pointer: sgs chem spcs)
110    REAL(wp), DIMENSION(:,:,:), POINTER               :: cs_p                     !< pointer: prognostic value of sgs chem spcs
111    REAL(wp), DIMENSION(:,:,:), POINTER               :: tcs_m                    !< pointer:
112
113#endif                                                                           
114                                                                                  !< by cs_name for each height lvls defined by cs_heights
115!
116!-- Namelist parameters for chem_emissions
117    INTEGER(iwp) ::  main_street_id = 0
118    INTEGER(iwp) ::  max_street_id = 0
119    INTEGER(iwp) ::  side_street_id = 0
120!
121!-- Constant emission factors
122    REAL(wp) ::  emiss_factor_main = 0.0_wp
123    REAL(wp) ::  emiss_factor_side = 0.0_wp
124   
125!-- Emission factors with daily cycle
126!     REAL(wp), DIMENSION(1:24) ::  emiss_factor_main = 0.0_wp
127!     REAL(wp), DIMENSION(1:24) ::  emiss_factor_side = 0.0_wp
128
129    SAVE
130#endif
131 END MODULE chem_modules
132
Note: See TracBrowser for help on using the repository browser.