Ignore:
Timestamp:
Jun 11, 2020 8:51:48 AM (4 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/chem_modules.f90

    r4544 r4559  
    11!> @file chem_modules.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    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/>.
     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/>.
    1615!
    1716! Copyright 2018-2020 Leibniz Universitaet Hannover
    1817! Copyright 2018-2020 Karlsruhe Institute of Technology
    1918! Copyright 2018-2020 Freie Universitaet Berlin
    20 !------------------------------------------------------------------------------!
     19!--------------------------------------------------------------------------------------------------!
    2120!
    2221! Current revisions:
     
    2726! -----------------
    2827! $Id$
     28! file re-formatted to follow the PALM coding standard
     29!
     30! 4544 2020-05-21 14:43:05Z raasch
    2931! conc_av changed from pointer to allocatable array
    30 ! 
     32!
    3133! 4511 2020-04-30 12:20:40Z raasch
    3234! new variables for explicit settings of lateral boundary conditions introduced
    3335!
    3436! 4481 2020-03-31 18:55:54Z maronga
    35 ! added namelist flag 'emiss_read_legacy_mode' to allow concurrent
    36 ! functioning of new emission read mode under development (ECC)
    37 !
    38 ! 4273 2019-10-24 13:40:54Z monakurppa
    39 ! Add logical switches nesting_chem and nesting_offline_chem (both .TRUE.
    40 ! by default)
     37! added namelist flag 'emiss_read_legacy_mode' to allow concurrent functioning of new emission read
     38! mode under development (ECC)
     39!
     40! 4273 2019-10-24 13:40:54Z monakurppa
     41! Add logical switches nesting_chem and nesting_offline_chem (both .TRUE. by default)
    4142!
    4243! 4182 2019-08-22 15:20:23Z scharf
    4344! Corrected "Former revisions" section
    44 ! 
     45!
    4546! 4110 2019-07-22 17:05:21Z suehring
    4647! +cs_advc_flags_s
    47 ! 
     48!
    4849! 4109 2019-07-22 17:00:34Z suehring
    4950! - introduced namelist item chem_modules@emiss_lod as future
    50 ! - replacement to chem_modules@mode_emis.  Currently keeping both
    51 !   for backward compatibility.  chem_modules@mode_emis will be
    52 !   depreciated upon migration of all dependent modules (e.g., salsa)
     51! - replacement to chem_modules@mode_emis.  Currently keeping both for backward compatibility.
     52!   chem_modules@mode_emis will be depreciated upon migration of all dependent modules (e.g., salsa)
    5353!   to chem_modules@emiss_lod
    5454!
    5555! (ecc) 20190513 replaced nspec_out with n_matched_vars
    56 ! 
     56!
    5757! 3877 2019-04-08 19:09:16Z knoop
    5858! Formatting, clean-up, clarified/corrected comments
    59 ! 
     59!
    6060! 3833 2019-03-28 15:04:04Z forkel
    6161! removed USE chem_gasphase_mod
    62 ! 
     62!
    6363! 3827 2019-03-27 17:20:32Z forkel
    64 ! some formatting  and reordering (ecc) 
    65 ! 
     64! some formatting  and reordering (ecc)
     65!
    6666! 3820 2019-03-27 11:53:41Z forkel
    67 ! renamed do_emis to emissions_anthropogenic, removed USE statistics, variables sorted by type
    68 !
    69 !
     67! renamed do_emis to emissions_anthropogenic, removed USE statistics, variables sorted by type
     68!
    7069! 3780 2019-03-05 11:19:45Z forkel
    7170! added cs_mech
    72 ! 
     71!
    7372! 3652 2019-01-07 15:29:59Z forkel
    7473! parameter chem_mechanism added (basit)
    75 ! 
     74!
    7675! 3282 2018-09-27 10:49:12Z basit
    7776! Initial revision
     
    8584! @author Edward C. Chan
    8685!
    87 !------------------------------------------------------------------------------!
     86!--------------------------------------------------------------------------------------------------!
    8887! Description:
    8988! ------------
    9089!> Definition of global PALM-4U chemistry variables
    91 !------------------------------------------------------------------------------!
     90!--------------------------------------------------------------------------------------------------!
    9291!
    9392 MODULE chem_modules
     
    9796    IMPLICIT NONE
    9897
    99     CHARACTER (LEN=20) ::  bc_cs_b        = 'dirichlet'         !< namelist parameter: surface boundary condition for concentration
     98    CHARACTER (LEN=20) ::  bc_cs_b        = 'dirichlet'         !< namelist parameter: surface
     99                                                                !< boundary condition for concentration
    100100    CHARACTER (LEN=20) ::  bc_cs_l        = 'undefined'         !< left boundary condition
    101101    CHARACTER (LEN=20) ::  bc_cs_n        = 'undefined'         !< north boundary condition
    102102    CHARACTER (LEN=20) ::  bc_cs_r        = 'undefined'         !< right boundary condition
    103103    CHARACTER (LEN=20) ::  bc_cs_s        = 'undefined'         !< south boundary condition
    104     CHARACTER (LEN=20) ::  bc_cs_t        = 'initial_gradient'  !< namelist parameter: top boudary condition for concentration
    105     CHARACTER (LEN=30) ::  chem_mechanism = 'phstatp'           !< namelist parameter: chemistry mechanism
    106     CHARACTER (LEN=80) ::  daytype_mdh    = 'workday'           !< namelist parameter: type of day - workday, weekend, holiday
    107     CHARACTER (LEN=80) ::  mode_emis      = 'PARAMETERIZED'     !< namelist parameter: mode of chemistry emissions - DEFAULT, EXPERT, PARAMETERIZED
    108     CHARACTER (LEN=80) ::  time_fac_type  = 'MDH'               !< namelist parameter: type of time treatment in the mode_emis DEFAULT - HOUR, MDH
     104    CHARACTER (LEN=20) ::  bc_cs_t        = 'initial_gradient'  !< namelist parameter: top boudary
     105                                                                !< condition for concentration
     106    CHARACTER (LEN=30) ::  chem_mechanism = 'phstatp'           !< namelist parameter: chemistry
     107                                                                !< mechanism
     108    CHARACTER (LEN=80) ::  daytype_mdh    = 'workday'           !< namelist parameter: type of day
     109                                                                !< - workday, weekend, holiday
     110    CHARACTER (LEN=80) ::  mode_emis      = 'PARAMETERIZED'     !< namelist parameter: mode of
     111                                                                !< chemistry emissions -
     112                                                                !< DEFAULT, EXPERT, PARAMETERIZED
    109113    CHARACTER (LEN=10) ::  photolysis_scheme                    !< 'constant',
    110                                                                 !< 'simple' (Simple parameterisation from MCM, Saunders et al., 2003, Atmos. Chem. Phys., 3, 161-180
    111                                                                 !< 'fastj'  (Wild et al., 2000, J. Atmos. Chem., 37, 245-282) STILL NOT IMPLEMENTED
    112 
    113     CHARACTER (LEN=11), DIMENSION(99) ::  cs_name             = 'novalue'  !< namelist parameter: names of species with given fluxes (see csflux)
    114     CHARACTER (LEN=11), DIMENSION(99) ::  cs_profile_name     = 'novalue'  !< namelist parameter: tbc...???
    115     CHARACTER (LEN=11), DIMENSION(99) ::  data_output_pr_cs   = 'novalue'  !< namelist parameter: tbc...???
    116     CHARACTER (LEN=11), DIMENSION(99) ::  surface_csflux_name = 'novalue'  !< namelist parameter: tbc...???
     114                                                                !< 'simple' (Simple parameterisation from MCM,
     115                                                                !< Saunders et al., 2003, Atmos. Chem. Phys., 3, 161-180
     116                                                                !< 'fastj'  (Wild et al., 2000, J. Atmos. Chem., 37, 245-282)
     117                                                                !< STILL NOT IMPLEMENTED
     118    CHARACTER (LEN=80) ::  time_fac_type  = 'MDH'               !< namelist parameter: type of time treatment in the mode_emis
     119                                                                !< DEFAULT - HOUR, MDH
     120
     121    CHARACTER (LEN=11), DIMENSION(99) ::  cs_name             = 'novalue'  !< namelist parameter:
     122                                                                           !<names of species with given fluxes
     123                                                                           !< (see csflux)
     124    CHARACTER (LEN=11), DIMENSION(99) ::  cs_profile_name     = 'novalue'  !< namelist parameter:
     125                                                                           !< tbc...???
     126    CHARACTER (LEN=11), DIMENSION(99) ::  data_output_pr_cs   = 'novalue'  !< namelist parameter:
     127                                                                           !< tbc...???
     128    CHARACTER (LEN=11), DIMENSION(99) ::  surface_csflux_name = 'novalue'  !< namelist parameter:
     129                                                                           !< tbc...???
    117130
    118131    INTEGER(iwp) ::  communicator_chem      !< stores the number of the MPI communicator to be used
     
    121134                                            !< 4: non-cyclic
    122135
    123     INTEGER(iwp) ::  cs_pr_count                           = 0      !< counter for chemical species profiles
    124     INTEGER(iwp) ::  cs_vertical_gradient_level_ind(99,10) = -9999  !< grid index values of cs_vertical_gradient_level
     136    INTEGER(iwp) ::  cs_pr_count                           = 0      !< counter for chemical species
     137                                                                    !< profiles
     138    INTEGER(iwp) ::  cs_vertical_gradient_level_ind(99,10) = -9999  !< grid index values of
     139                                                                    !< cs_vertical_gradient_level
    125140    INTEGER(iwp) ::  emiss_lod                             = -1     !< namelist parameter: chem emission LOD (same as mode_emis)
    126                                                                     !< -1 = unassigned, 0 = parameterized, 1 = default, 2 = pre-processed
     141                                                                    !< -1 = unassigned, 0 = parameterized, 1 = default,
     142                                                                    !< 2 = pre-processed
    127143    INTEGER(iwp) ::  ibc_cs_b                                       !< integer flag for bc_cs_b
    128144    INTEGER(iwp) ::  ibc_cs_t                                       !< integer flag for bc_cs_t
    129     INTEGER(iwp) ::  main_street_id                        = 0      !< namelist parameter: lower bound of main street IDs (OpenStreetMaps) for PARAMETERIZED mode
    130     INTEGER(iwp) ::  max_pr_cs                             = 0      !<
    131     INTEGER(iwp) ::  max_street_id                         = 0      !< namelist parameter: upper bound of main street IDs (OpenStreetMaps) for PARAMETERIZED mode     
    132     INTEGER(iwp) ::  n_matched_vars                                 !< number of matched emissions variables
    133     INTEGER(iwp) ::  side_street_id                        = 0      !< namelist parameter: lower bound of side street IDs (OpenStreetMaps) for PARAMETERIZED mode
     145    INTEGER(iwp) ::  main_street_id                        = 0      !< namelist parameter: lower bound of main street IDs
     146                                                                    !< (OpenStreetMaps) for PARAMETERIZED mode
     147    INTEGER(iwp) ::  max_pr_cs                             = 0      !<
     148    INTEGER(iwp) ::  max_street_id                         = 0      !< namelist parameter: upper bound of main street IDs
     149                                                                    !< (OpenStreetMaps) for PARAMETERIZED mode
     150    INTEGER(iwp) ::  n_matched_vars                                 !< number of matched emissions
     151                                                                    !< variables
     152    INTEGER(iwp) ::  side_street_id                        = 0      !< namelist parameter: lower bound of side street IDs
     153                                                                    !< (OpenStreetMaps) for PARAMETERIZED mode
    134154
    135155    INTEGER(iwp), DIMENSION(99) ::  cs_pr_index  = 0      !< index for chemical species profiles
    136     INTEGER(iwp), DIMENSION(:)  ::  match_spec_nox(1:2)   !< results of matching the input and model's NOx
    137     INTEGER(iwp), DIMENSION(:)  ::  match_spec_pm(1:3)    !< results of matching the input and model's PMs
    138     INTEGER(iwp), DIMENSION(:)  ::  match_spec_sox(1:2)   !< results of matching the input and model's SOx!
    139 
    140     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_spec_input      !< index of input chem species for matching routine
    141     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_spec_model      !< index of model chem species for matching routine
    142     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_spec_voc_input  !< index of VOC input components matching the model's VOCs
    143     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_spec_voc_model  !< index of VOC model species matching the input VOCs comp.
    144    
    145     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE  ::  cs_advc_flags_s !< flags used to degrade order of advection scheme for
     156    INTEGER(iwp), DIMENSION(:)  ::  match_spec_nox(1:2)   !< results of matching the input and
     157                                                          !< model's NOx
     158    INTEGER(iwp), DIMENSION(:)  ::  match_spec_pm(1:3)    !< results of matching the input and
     159                                                          !< model's PMs
     160    INTEGER(iwp), DIMENSION(:)  ::  match_spec_sox(1:2)   !< results of matching the input and
     161                                                          !< model's SOx!
     162
     163    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_spec_input      !< index of input chem species
     164                                                                      !< for matching routine
     165    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_spec_model      !< index of model chem species#
     166                                                                      !< for matching routine
     167    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_spec_voc_input  !< index of VOC input
     168                                                                      !< components matching the model's VOCs
     169    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  match_spec_voc_model  !< index of VOC model species
     170                                                                      !< matching the input VOCs comp.
     171
     172    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE  ::  cs_advc_flags_s !< flags used to degrade order of advection scheme for
    146173                                                                     !< chemical species near walls and lateral boundaries
    147174
     
    162189    LOGICAL ::  bc_radiation_cs_s         = .FALSE.  !< flag for indicating a radiation/neumann
    163190                                                     !< condition at the south boundary
    164     LOGICAL ::  constant_top_csflux(99)   = .TRUE.   !< internal flag, set to .FALSE. if no top_csflux is prescribed
    165     LOGICAL ::  constant_csflux(99)       = .TRUE.   !< internal flag, set to .FALSE. if no surface_csflux is prescribed
    166     LOGICAL ::  call_chem_at_all_substeps = .FALSE.  !< namelist parameter: ....???
    167     LOGICAL ::  chem_debug0               = .FALSE.  !< namelist parameter: flag for minimum print output
     191    LOGICAL ::  constant_top_csflux(99)   = .TRUE.   !< internal flag, set to .FALSE. if no
     192                                                     !< top_csflux is prescribed
     193    LOGICAL ::  constant_csflux(99)       = .TRUE.   !< internal flag, set to .FALSE. if no
     194                                                     !< surface_csflux is prescribed
     195    LOGICAL ::  call_chem_at_all_substeps = .FALSE.  !< namelist parameter: ....???
     196    LOGICAL ::  chem_debug0               = .FALSE.  !< namelist parameter: flag for minimum print
     197                                                     !< output
    168198    LOGICAL ::  chem_debug1               = .FALSE.  !< namelist parameter: flag for print output
    169     LOGICAL ::  chem_debug2               = .FALSE.  !< namelist parameter: flag for further print output
    170     LOGICAL ::  chem_gasphase_on          = .TRUE.   !< namelist parameter: flag to switch off chemical reactions
     199    LOGICAL ::  chem_debug2               = .FALSE.  !< namelist parameter: flag for further print
     200                                                     !< output
     201    LOGICAL ::  chem_gasphase_on          = .TRUE.   !< namelist parameter: flag to switch off
     202                                                     !< chemical reactions
    171203    LOGICAL ::  cs_pr_namelist_found      = .FALSE.  !< ...???
    172     LOGICAL ::  deposition_dry            = .FALSE.  !< namelist parameter: flag for activation of deposition calculation
    173     LOGICAL ::  emissions_anthropogenic   = .FALSE.  !< namelist parameter: flag for turning on anthropogenic emissions
     204    LOGICAL ::  deposition_dry            = .FALSE.  !< namelist parameter: flag for activation of
     205                                                     !< deposition calculation
     206    LOGICAL ::  emissions_anthropogenic   = .FALSE.  !< namelist parameter: flag for turning on
     207                                                     !< anthropogenic emissions
    174208    LOGICAL ::  emission_output_required  = .TRUE.   !< internal flag for requiring emission outputs
    175     LOGICAL ::  emiss_read_legacy_mode    = .TRUE.   !< namelist parameter: flag to read emission data using legacy mode
     209    LOGICAL ::  emiss_read_legacy_mode    = .TRUE.   !< namelist parameter: flag to read emission
     210                                                     !< data using legacy mode
    176211    LOGICAL ::  nesting_chem              = .TRUE.   !< apply self-nesting for the chemistry model
    177     LOGICAL ::  nesting_offline_chem      = .TRUE.   !< apply offline nesting for the chemistry model
     212    LOGICAL ::  nesting_offline_chem      = .TRUE.   !< apply offline nesting for the chemistry
     213                                                     !< model
    178214
    179215    REAL(wp) ::  cs_surface_initial_change(99)     = 0.0_wp        !< namelist parameter: ...???
     
    186222    REAL(wp) ::  wall_csflux(99,0:5)               = 0.0_wp        !< namelist parameter: ...???
    187223
    188     REAL(wp), DIMENSION(99)     ::  cs_surface = 0.0_wp        !< namelist parameter: chem species concentration at surface
    189     REAL(wp), DIMENSION(99,100) ::  cs_heights = 9999999.9_wp  !< namelist parameter: height levels for initial chem species concentrations
    190     REAL(wp), DIMENSION(99,100) ::  cs_profile = 9999999.9_wp  !< namelist parameter: chem species concentration values at cs_heights levels
    191 
    192     REAL(wp), DIMENSION(:), ALLOCATABLE ::  bc_cs_t_val  !< vertical gradient of chemical species near domain top
     224    REAL(wp), DIMENSION(99)     ::  cs_surface = 0.0_wp        !< namelist parameter: chem species
     225                                                               !< concentration at surface
     226    REAL(wp), DIMENSION(99,100) ::  cs_heights = 9999999.9_wp  !< namelist parameter: height levels
     227                                                               !< for initial chem species concentrations
     228    REAL(wp), DIMENSION(99,100) ::  cs_profile = 9999999.9_wp  !< namelist parameter: chem species
     229                                                               !< concentration values at cs_heights levels
     230
     231    REAL(wp), DIMENSION(:), ALLOCATABLE ::  bc_cs_t_val  !< vertical gradient of chemical species
     232                                                         !< near domain top
    193233    REAL(wp), DIMENSION(:), ALLOCATABLE ::  css          !< scaling parameter for chem species
    194234
    195     REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  emis_distribution  !< emissions final values (main module output) ???
    196                                  
    197     REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_1  !< pointer for swapping of timelevels for respective quantity
    198     REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_2  !< pointer for swapping of timelevels for respective quantity
    199     REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_3  !< pointer for swapping of timelevels for respective quantity
     235    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  emis_distribution  !< emissions final values
     236                                                                     !< (main module output) ???
     237
     238    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_1  !< pointer for swapping of
     239                                                                !< timelevels for respective quantity
     240    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_2  !< pointer for swapping of
     241                                                                !< timelevels for respective quantity
     242    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, TARGET ::  cs_3  !< pointer for swapping of
     243                                                                !< timelevels for respective quantity
    200244
    201245    REAL(wp), DIMENSION(:,:,:), POINTER ::  cs     !< pointer: sgs chem spcs  ???
     
    231275!-  Define chemical variables within chem_species
    232276    TYPE species_def
     277
    233278       CHARACTER(LEN=15)                            ::  name         !< name of chemical species
    234        CHARACTER(LEN=15)                            ::  unit         !< unit (ppm for gases, kg m^-3 for aerosol tracers)
    235        REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  conc         !< concentrations of trace gases
     279       CHARACTER(LEN=15)                            ::  unit         !< unit (ppm for gases, kg m^-3
     280                                                                     !< for aerosol tracers)
     281
     282       REAL(kind=wp), ALLOCATABLE, DIMENSION(:)     ::  conc_pr_init !< initial profile of chemical
     283                                                                     !< species
     284
     285       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  cssws_av     !< averaged fluxes of trace
     286                                                                     !< gases at surface
     287       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  flux_s_cs    !< 6th-order advective flux at
     288                                                                     !< south face of grid box of chemical species (='cs')
     289       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  diss_s_cs    !< artificial numerical dissipation
     290                                                                     !< flux at south face of grid box of chemical species
     291
    236292       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:) ::  conc_av      !< averaged concentrations
    237        REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  conc_p       !< conc at prognostic time level
    238        REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  tconc_m      !< weighted tendency of conc for previous sub-timestep (Runge-Kutta)
    239        REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  cssws_av     !< averaged fluxes of trace gases at surface
    240        REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  flux_s_cs    !< 6th-order advective flux at south face of grid box of chemical species (='cs')
    241        REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:)   ::  diss_s_cs    !< artificial numerical dissipation flux at south face of grid box of chemical species
    242        REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:) ::  flux_l_cs    !< 6th-order advective flux at left face of grid box of chemical species (='cs')
    243        REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:) ::  diss_l_cs    !< artificial numerical dissipation flux at left face of grid box of chemical species
    244        REAL(kind=wp), ALLOCATABLE, DIMENSION(:)     ::  conc_pr_init !< initial profile of chemical species
     293       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:) ::  flux_l_cs    !< 6th-order advective flux at
     294                                                                     !< left face of grid box of chemical species (='cs')
     295       REAL(kind=wp), ALLOCATABLE, DIMENSION(:,:,:) ::  diss_l_cs    !< artificial numerical dissipation
     296                                                                     !< flux at left face of grid box of chemical species
     297
     298       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  conc         !< concentrations of trace
     299                                                                     !< gases
     300       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  conc_p       !< conc at prognostic time
     301                                                                     !< level
     302       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     ::  tconc_m      !< weighted tendency of conc
     303                                                                     !< for previous sub-timestep (Runge-Kutta)
     304
    245305    END TYPE species_def
    246306!
    247307!-- Define photolysis frequencies in phot_frequen
    248308    TYPE photols_def
     309
    249310       CHARACTER(LEN=15)                            :: name          !< name of pgotolysis frequency
    250311       CHARACTER(LEN=15)                            :: unit          !< unit (1/s)
     312
    251313       REAL(kind=wp), POINTER, DIMENSION(:,:,:)     :: freq          !< photolysis frequency
     314
    252315    END TYPE photols_def
    253316
Note: See TracChangeset for help on using the changeset viewer.