Ignore:
Timestamp:
Oct 21, 2020 2:55:41 PM (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/modules.f90

    r4742 r4753  
    11!> @file 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 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
     
    2524! -----------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4742 2020-10-14 15:11:02Z schwenkel
    2729! Implement snow and graupel (bulk microphysics)
    2830!
     
    6971!
    7072! 4472 2020-03-24 12:21:00Z Giersch
    71 ! Additional switch added to activate calculations in flow_statistics for the
    72 ! kolmogorov length scale
     73! Additional switch added to activate calculations in flow_statistics for the kolmogorov length
     74! scale
    7375!
    7476! 4461 2020-03-12 16:51:59Z raasch
     
    7678!
    7779! 4414 2020-02-19 20:16:04Z suehring
    78 ! - nzb_diff_s_inner, nzb_diff_s_outer, nzb_inner,nzb_outer, nzb_s_inner,
    79 !   nzb_s_outer, nzb_u_inner, nzb_u_outer, nzb_v_inner, nzb_v_outer,
    80 !   nzb_w_inner, nzb_w_outer
     80! - nzb_diff_s_inner, nzb_diff_s_outer, nzb_inner,nzb_outer, nzb_s_inner, nzb_s_outer, nzb_u_inner,
     81!   nzb_u_outer, nzb_v_inner, nzb_v_outer, nzb_w_inner, nzb_w_outer
    8182!
    8283!
    8384! 4360 2020-01-07 11:25:50Z suehring
    84 ! Introduction of wall_flags_total_0, which currently sets bits based on static
    85 ! topography information used in wall_flags_static_0
     85! Introduction of wall_flags_total_0, which currently sets bits based on static topography
     86! information used in wall_flags_static_0
    8687!
    8788! 4340 2019-12-16 08:17:03Z Giersch
     
    107108!
    108109! 4184 2019-08-23 08:07:40Z oliver.maas
    109 ! changed allocated length of recycling_method_for_thermodynamic_quantities
    110 ! from 20 to 80 characters
     110! changed allocated length of recycling_method_for_thermodynamic_quantities from 20 to 80 characters
    111111!
    112112! 4183 2019-08-23 07:33:16Z oliver.maas
     
    127127!
    128128! 4131 2019-08-02 11:06:18Z monakurppa
    129 ! Add max_pr_salsa to control_parameters. Used in creating profile output for
    130 ! salsa.
     129! Add max_pr_salsa to control_parameters. Used in creating profile output for salsa.
    131130!
    132131! 4110 2019-07-22 17:05:21Z suehring
     
    141140!
    142141! 4069 2019-07-01 14:05:51Z Giersch
    143 ! Masked output running index mid has been introduced as a local variable to
    144 ! avoid runtime error (Loop variable has been modified) in time_integration
     142! Masked output running index mid has been introduced as a local variable to avoid runtime error
     143! (Loop variable has been modified) in time_integration
    145144!
    146145! 4017 2019-06-06 12:16:46Z schwenkel
     
    151150!
    152151! 3885 2019-04-11 11:29:34Z kanani
    153 ! Changes related to global restructuring of location messages and introduction
    154 ! of additional debug messages
     152! Changes related to global restructuring of location messages and introduction of additional debug
     153! messages
    155154!
    156155! 3871 2019-04-08 14:38:39Z knoop
     
    163162! -surface_data_output +surface_output
    164163!
    165 !------------------------------------------------------------------------------!
     164!--------------------------------------------------------------------------------------------------!
    166165! Description:
    167166! ------------
    168167!> Definition of global variables
    169 !------------------------------------------------------------------------------!
    170 
    171 
    172 !------------------------------------------------------------------------------!
     168!--------------------------------------------------------------------------------------------------!
     169
     170
     171!--------------------------------------------------------------------------------------------------!
    173172! Description:
    174173! ------------
    175174!> Definition of variables for special advection schemes.
    176 !------------------------------------------------------------------------------!
     175!--------------------------------------------------------------------------------------------------!
    177176 MODULE advection
    178177
     
    190189
    191190
    192 !------------------------------------------------------------------------------!
     191!--------------------------------------------------------------------------------------------------!
    193192! Description:
    194193! ------------
    195 !> The variable in this module is used by multi_agent_system_mod AND
    196 !> netcdf_interface_mod. It must be here to avoid circular dependency.
     194!> The variable in this module is used by multi_agent_system_mod AND netcdf_interface_mod. It must
     195!> be here to avoid circular dependency.
    197196!> This is a workaround.
    198 !------------------------------------------------------------------------------!
     197!--------------------------------------------------------------------------------------------------!
    199198 MODULE mas_global_attributes
    200199
     
    208207
    209208
    210 !------------------------------------------------------------------------------!
     209!--------------------------------------------------------------------------------------------------!
    211210! Description:
    212211! ------------
    213212!> Definition of all arrays defined on the computational grid.
    214 !------------------------------------------------------------------------------!
     213!--------------------------------------------------------------------------------------------------!
    215214 MODULE arrays_3d
    216215
    217216    USE kinds
    218217
    219     REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_u_m                  !< mean phase velocity at outflow for u-component used in radiation boundary condition
    220     REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_u_m_l                !< mean phase velocity at outflow for u-component used in radiation boundary condition (local subdomain value)
    221     REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_v_m                  !< mean phase velocity at outflow for v-component used in radiation boundary condition
    222     REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_v_m_l                !< mean phase velocity at outflow for v-component used in radiation boundary condition (local subdomain value)
    223     REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_w_m                  !< mean phase velocity at outflow for w-component used in radiation boundary condition
    224     REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_w_m_l                !< mean phase velocity at outflow for w-component used in radiation boundary condition (local subdomain value)
    225     REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddzu                   !< 1/dzu
    226     REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddzu_pres              !< modified ddzu for pressure solver
    227     REAL(wp), DIMENSION(:), ALLOCATABLE ::  dd2zu                  !< 1/(dzu(k)+dzu(k+1))
    228     REAL(wp), DIMENSION(:), ALLOCATABLE ::  dzu                    !< vertical grid size (u-grid)
    229     REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddzw                   !< 1/dzw
    230     REAL(wp), DIMENSION(:), ALLOCATABLE ::  dzw                    !< vertical grid size (w-grid)
    231     REAL(wp), DIMENSION(:), ALLOCATABLE ::  hyp                    !< hydrostatic pressure
    232     REAL(wp), DIMENSION(:), ALLOCATABLE ::  inflow_damping_factor  !< used for turbulent inflow (non-cyclic boundary conditions)
    233     REAL(wp), DIMENSION(:), ALLOCATABLE ::  ptdf_x                 !< damping factor for potential temperature in x-direction
    234     REAL(wp), DIMENSION(:), ALLOCATABLE ::  ptdf_y                 !< damping factor for potential temperature in y-direction
    235     REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt_init                !< initial profile of potential temperature
    236     REAL(wp), DIMENSION(:), ALLOCATABLE ::  q_init                 !< initial profile of total water mixing ratio
    237                                                                    !< (or total water content with active cloud physics)
    238     REAL(wp), DIMENSION(:), ALLOCATABLE ::  rdf                    !< rayleigh damping factor for velocity components
    239     REAL(wp), DIMENSION(:), ALLOCATABLE ::  rdf_sc                 !< rayleigh damping factor for scalar quantities
    240     REAL(wp), DIMENSION(:), ALLOCATABLE ::  ref_state              !< reference state of potential temperature
    241                                                                    !< (and density in case of ocean simulation)
    242     REAL(wp), DIMENSION(:), ALLOCATABLE ::  s_init                 !< initial profile of passive scalar concentration
    243     REAL(wp), DIMENSION(:), ALLOCATABLE ::  sa_init                !< initial profile of salinity (ocean)
    244     REAL(wp), DIMENSION(:), ALLOCATABLE ::  ug                     !< geostrophic wind component in x-direction
    245     REAL(wp), DIMENSION(:), ALLOCATABLE ::  u_init                 !< initial profile of horizontal velocity component u
    246     REAL(wp), DIMENSION(:), ALLOCATABLE ::  u_stokes_zu            !< u-component of Stokes drift velocity at zu levels
    247     REAL(wp), DIMENSION(:), ALLOCATABLE ::  u_stokes_zw            !< u-component of Stokes drift velocity at zw levels
    248     REAL(wp), DIMENSION(:), ALLOCATABLE ::  vg                     !< geostrophic wind component in y-direction
    249     REAL(wp), DIMENSION(:), ALLOCATABLE ::  v_init                 !< initial profile of horizontal velocity component v
    250     REAL(wp), DIMENSION(:), ALLOCATABLE ::  v_stokes_zu            !< v-component of Stokes drift velocity at zu levels
    251     REAL(wp), DIMENSION(:), ALLOCATABLE ::  v_stokes_zw            !< v-component of Stokes drift velocity at zw levels
    252     REAL(wp), DIMENSION(:), ALLOCATABLE ::  w_subs                 !< subsidence/ascent velocity
    253     REAL(wp), DIMENSION(:), ALLOCATABLE ::  x                      !< horizontal grid coordinate of v-grid (in m)
    254     REAL(wp), DIMENSION(:), ALLOCATABLE ::  xu                     !< horizontal grid coordinate of u-grid (in m)
    255     REAL(wp), DIMENSION(:), ALLOCATABLE ::  y                      !< horizontal grid coordinate of u-grid (in m)
    256     REAL(wp), DIMENSION(:), ALLOCATABLE ::  yv                     !< horizontal grid coordinate of v-grid (in m)
    257     REAL(wp), DIMENSION(:), ALLOCATABLE ::  zu                     !< vertical grid coordinate of u-grid (in m)
    258     REAL(wp), DIMENSION(:), ALLOCATABLE ::  zw                     !< vertical grid coordinate of w-grid (in m)
     218    REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_u_m                           !< mean phase velocity at outflow for u-component used
     219                                                                            !< in radiation boundary condition
     220    REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_u_m_l                         !< mean phase velocity at outflow for u-component used
     221                                                                            !< in radiation boundary condition (local subdomain value)
     222    REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_v_m                           !< mean phase velocity at outflow for v-component used
     223                                                                            !< in radiation boundary condition
     224    REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_v_m_l                         !< mean phase velocity at outflow for v-component used
     225                                                                            !< in radiation boundary condition (local subdomain value)
     226    REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_w_m                           !< mean phase velocity at outflow for w-component used
     227                                                                            !< in radiation boundary condition
     228    REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_w_m_l                         !< mean phase velocity at outflow for w-component used
     229                                                                            !< in radiation boundary condition (local subdomain value)
     230    REAL(wp), DIMENSION(:), ALLOCATABLE ::  d_exner                         !< ratio of potential and actual temperature
     231    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddzu                            !< 1/dzu
     232    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddzu_pres                       !< modified ddzu for pressure solver
     233    REAL(wp), DIMENSION(:), ALLOCATABLE ::  dd2zu                           !< 1/(dzu(k)+dzu(k+1))
     234    REAL(wp), DIMENSION(:), ALLOCATABLE ::  drho_air                        !< inverse air density profile on the uv grid
     235    REAL(wp), DIMENSION(:), ALLOCATABLE ::  drho_air_zw                     !< inverse air density profile on the w grid
     236    REAL(wp), DIMENSION(:), ALLOCATABLE ::  dzu                             !< vertical grid size (u-grid)
     237    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddzw                            !< 1/dzw
     238    REAL(wp), DIMENSION(:), ALLOCATABLE ::  dzw                             !< vertical grid size (w-grid)
     239    REAL(wp), DIMENSION(:), ALLOCATABLE ::  exner                           !< ratio of actual and potential temperature
     240    REAL(wp), DIMENSION(:), ALLOCATABLE ::  heatflux_input_conversion       !< conversion factor array for heatflux input
     241    REAL(wp), DIMENSION(:), ALLOCATABLE ::  heatflux_output_conversion      !< conversion factor array for heatflux output
     242    REAL(wp), DIMENSION(:), ALLOCATABLE ::  hyp                             !< hydrostatic pressure
     243    REAL(wp), DIMENSION(:), ALLOCATABLE ::  hyrho                           !< density of air calculated with hydrostatic pressure
     244    REAL(wp), DIMENSION(:), ALLOCATABLE ::  inflow_damping_factor           !< used for turbulent inflow
     245                                                                            !< (non-cyclic boundary conditions)
     246    REAL(wp), DIMENSION(:), ALLOCATABLE ::  momentumflux_input_conversion   !< conversion factor array for momentumflux input
     247    REAL(wp), DIMENSION(:), ALLOCATABLE ::  momentumflux_output_conversion  !< conversion factor array for momentumflux output
     248    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ptdf_x                          !< damping factor for potential temperature in
     249                                                                            !< x-direction
     250    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ptdf_y                          !< damping factor for potential temperature in
     251                                                                            !< y-direction
     252    REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt_init                         !< initial profile of potential temperature
     253    REAL(wp), DIMENSION(:), ALLOCATABLE ::  q_init                          !< initial profile of total water mixing ratio
     254                                                                            !< (or total water content with active cloud physics)
     255    REAL(wp), DIMENSION(:), ALLOCATABLE ::  rdf                             !< rayleigh damping factor for velocity components
     256    REAL(wp), DIMENSION(:), ALLOCATABLE ::  rdf_sc                          !< rayleigh damping factor for scalar quantities
     257    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ref_state                       !< reference state of potential temperature
     258                                                                            !< (and density in case of ocean simulation)
     259    REAL(wp), DIMENSION(:), ALLOCATABLE ::  rho_air                         !< air density profile on the uv grid
     260    REAL(wp), DIMENSION(:), ALLOCATABLE ::  rho_air_zw                      !< air density profile on the w grid
     261    REAL(wp), DIMENSION(:), ALLOCATABLE ::  s_init                          !< initial profile of passive scalar concentration
     262    REAL(wp), DIMENSION(:), ALLOCATABLE ::  sa_init                         !< initial profile of salinity (ocean)
     263    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ug                              !< geostrophic wind component in x-direction
     264    REAL(wp), DIMENSION(:), ALLOCATABLE ::  u_init                          !< initial profile of horizontal velocity component u
     265    REAL(wp), DIMENSION(:), ALLOCATABLE ::  u_stokes_zu                     !< u-component of Stokes drift velocity at zu levels
     266    REAL(wp), DIMENSION(:), ALLOCATABLE ::  u_stokes_zw                     !< u-component of Stokes drift velocity at zw levels
     267    REAL(wp), DIMENSION(:), ALLOCATABLE ::  vg                              !< geostrophic wind component in y-direction
     268    REAL(wp), DIMENSION(:), ALLOCATABLE ::  v_init                          !< initial profile of horizontal velocity component v
     269    REAL(wp), DIMENSION(:), ALLOCATABLE ::  v_stokes_zu                     !< v-component of Stokes drift velocity at zu levels
     270    REAL(wp), DIMENSION(:), ALLOCATABLE ::  v_stokes_zw                     !< v-component of Stokes drift velocity at zw levels
     271    REAL(wp), DIMENSION(:), ALLOCATABLE ::  waterflux_input_conversion      !< conversion factor array for waterflux input
     272    REAL(wp), DIMENSION(:), ALLOCATABLE ::  waterflux_output_conversion     !< conversion factor array for waterflux output
     273    REAL(wp), DIMENSION(:), ALLOCATABLE ::  w_subs                          !< subsidence/ascent velocity
     274    REAL(wp), DIMENSION(:), ALLOCATABLE ::  x                               !< horizontal grid coordinate of v-grid (in m)
     275    REAL(wp), DIMENSION(:), ALLOCATABLE ::  xu                              !< horizontal grid coordinate of u-grid (in m)
     276    REAL(wp), DIMENSION(:), ALLOCATABLE ::  y                               !< horizontal grid coordinate of u-grid (in m)
     277    REAL(wp), DIMENSION(:), ALLOCATABLE ::  yv                              !< horizontal grid coordinate of v-grid (in m)
     278    REAL(wp), DIMENSION(:), ALLOCATABLE ::  zu                              !< vertical grid coordinate of u-grid (in m)
     279    REAL(wp), DIMENSION(:), ALLOCATABLE ::  zw                              !< vertical grid coordinate of w-grid (in m)
     280
    259281
    260282    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  c_u                   !< phase speed of u-velocity component
    261283    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  c_v                   !< phase speed of v-velocity component
    262284    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  c_w                   !< phase speed of w-velocity component
    263     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_diss           !< artificial numerical dissipation flux at south face of grid box - TKE dissipation
    264     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_e              !< artificial numerical dissipation flux at south face of grid box - subgrid-scale TKE
    265     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_nc             !< artificial numerical dissipation flux at south face of grid box - clouddrop-number concentration
    266     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_ng             !< artificial numerical dissipation flux at south face of grid box - graupel number concentration
    267     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_ni             !< artificial numerical dissipation flux at south face of grid box - ice crystal-number concentration
    268     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_nr             !< artificial numerical dissipation flux at south face of grid box - raindrop-number concentration
    269     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_ns             !< artificial numerical dissipation flux at south face of grid box - snow-number concentration
    270     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_pt             !< artificial numerical dissipation flux at south face of grid box - potential temperature
    271     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_q              !< artificial numerical dissipation flux at south face of grid box - total water mixing ratio
    272     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_qc             !< artificial numerical dissipation flux at south face of grid box - cloudwater mixing ratio
    273     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_qg             !< artificial numerical dissipation flux at south face of grid box - graupel mixing ratio
    274     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_qi             !< artificial numerical dissipation flux at south face of grid box - ice crystal mixing ratio
    275     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_qr             !< artificial numerical dissipation flux at south face of grid box - rainwater mixing ratio
    276     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_qs             !< artificial numerical dissipation flux at south face of grid box - snow mixing ratio
    277     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_s              !< artificial numerical dissipation flux at south face of grid box - passive scalar
    278     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_sa             !< artificial numerical dissipation flux at south face of grid box - salinity
    279     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_u              !< artificial numerical dissipation flux at south face of grid box - u-component
    280     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_v              !< artificial numerical dissipation flux at south face of grid box - v-component
    281     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_w              !< artificial numerical dissipation flux at south face of grid box - w-component
     285    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_diss           !< artificial numerical dissipation flux at south face of grid
     286                                                                    !< box - TKE dissipation
     287    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_e              !< artificial numerical dissipation flux at south face of grid
     288                                                                    !< box - subgrid-scale TKE
     289    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_nc             !< artificial numerical dissipation flux at south face of grid
     290                                                                    !< box - clouddrop-number concentration
     291    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_ng             !< artificial numerical dissipation flux at south face of grid
     292                                                                    !< box - graupel number concentration
     293    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_ni             !< artificial numerical dissipation flux at south face of grid
     294                                                                    !< box - ice crystal-number concentration
     295    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_nr             !< artificial numerical dissipation flux at south face of grid
     296                                                                    !< box - raindrop-number concentration
     297    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_ns             !< artificial numerical dissipation flux at south face of grid
     298                                                                    !< box - snow-number concentration
     299    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_pt             !< artificial numerical dissipation flux at south face of grid
     300                                                                    !< box - potential temperature
     301    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_q              !< artificial numerical dissipation flux at south face of grid
     302                                                                    !< box - total water mixing ratio
     303    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_qc             !< artificial numerical dissipation flux at south face of grid
     304                                                                    !< box - cloudwater mixing ratio
     305    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_qg             !< artificial numerical dissipation flux at south face of grid
     306                                                                    !< box - graupel mixing ratio
     307    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_qi             !< artificial numerical dissipation flux at south face of grid
     308                                                                    !< box - ice crystal mixing ratio
     309    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_qr             !< artificial numerical dissipation flux at south face of grid
     310                                                                    !< box - rainwater mixing ratio
     311    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_qs             !< artificial numerical dissipation flux at south face of grid
     312                                                                    !< box - snow mixing ratio
     313    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_s              !< artificial numerical dissipation flux at south face of grid
     314                                                                    !< box - passive scalar
     315    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_sa             !< artificial numerical dissipation flux at south face of grid
     316                                                                    !< box - salinity
     317    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_u              !< artificial numerical dissipation flux at south face of grid
     318                                                                    !< box - u-component
     319    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_v              !< artificial numerical dissipation flux at south face of grid
     320                                                                    !< box - v-component
     321    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_w              !< artificial numerical dissipation flux at south face of grid
     322                                                                    !< box - w-component
    282323    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  dzu_mg                !< vertical grid size (u-grid) for multigrid pressure solver
    283324    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  dzw_mg                !< vertical grid size (w-grid) for multigrid pressure solver
    284     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_diss           !< 6th-order advective flux at south face of grid box - TKE dissipation
    285     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_e              !< 6th-order advective flux at south face of grid box - subgrid-scale TKE
    286     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_nc             !< 6th-order advective flux at south face of grid box - clouddrop-number concentration
    287     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_ng             !< 6th-order advective flux at south face of grid box - graupel-number concentration
    288     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_ni             !< 6th-order advective flux at south face of grid box - icecrystal-number concentration
    289     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_nr             !< 6th-order advective flux at south face of grid box - raindrop-number concentration
    290     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_ns             !< 6th-order advective flux at south face of grid box - graupel-number concentration
    291     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_pt             !< 6th-order advective flux at south face of grid box - potential temperature
    292     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_q              !< 6th-order advective flux at south face of grid box - total water mixing ratio
    293     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_qc             !< 6th-order advective flux at south face of grid box - cloudwater mixing ratio
    294     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_qg             !< 6th-order advective flux at south face of grid box - graupel mixing ratio
    295     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_qi             !< 6th-order advective flux at south face of grid box - ice crystal mixing ratio
    296     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_qr             !< 6th-order advective flux at south face of grid box - rainwater mixing ratio
    297     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_qs             !< 6th-order advective flux at south face of grid box - snow mixing ratio
    298     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_s              !< 6th-order advective flux at south face of grid box - passive scalar
    299     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_sa             !< 6th-order advective flux at south face of grid box - salinity
    300     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_u              !< 6th-order advective flux at south face of grid box - u-component
    301     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_v              !< 6th-order advective flux at south face of grid box - v-component
    302     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_w              !< 6th-order advective flux at south face of grid box - w-component
    303     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  f1_mg                 !< grid factor used in right hand side of Gauss-Seidel equation (multigrid)
    304     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  f2_mg                 !< grid factor used in right hand side of Gauss-Seidel equation (multigrid)
    305     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  f3_mg                 !< grid factor used in right hand side of Gauss-Seidel equation (multigrid)
     325    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_diss           !< 6th-order advective flux at south face of grid box -
     326                                                                    !< TKE dissipation
     327    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_e              !< 6th-order advective flux at south face of grid box -
     328                                                                    !< subgrid-scale TKE
     329    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_nc             !< 6th-order advective flux at south face of grid box -
     330                                                                    !< clouddrop-number concentration
     331    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_ng             !< 6th-order advective flux at south face of grid box -
     332                                                                    !< graupel-number concentration
     333    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_ni             !< 6th-order advective flux at south face of grid box -
     334                                                                    !< icecrystal-number concentration
     335    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_nr             !< 6th-order advective flux at south face of grid box -
     336                                                                    !< raindrop-number concentration
     337    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_ns             !< 6th-order advective flux at south face of grid box -
     338                                                                    !< graupel-number concentration
     339    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_pt             !< 6th-order advective flux at south face of grid box -
     340                                                                    !< potential temperature
     341    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_q              !< 6th-order advective flux at south face of grid box -
     342                                                                    !< total water mixing ratio
     343    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_qc             !< 6th-order advective flux at south face of grid box -
     344                                                                    !< cloudwater mixing ratio
     345    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_qg             !< 6th-order advective flux at south face of grid box -
     346                                                                    !< graupel mixing ratio
     347    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_qi             !< 6th-order advective flux at south face of grid box -
     348                                                                    !< ice crystal mixing ratio
     349    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_qr             !< 6th-order advective flux at south face of grid box -
     350                                                                    !< rainwater mixing ratio
     351    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_qs             !< 6th-order advective flux at south face of grid box -
     352                                                                    !< snow mixing ratio
     353    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_s              !< 6th-order advective flux at south face of grid box -
     354                                                                    !< passive scalar
     355    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_sa             !< 6th-order advective flux at south face of grid box -
     356                                                                    !< salinity
     357    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_u              !< 6th-order advective flux at south face of grid box -
     358                                                                    !< u-component
     359    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_v              !< 6th-order advective flux at south face of grid box -
     360                                                                    !< v-component
     361    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_w              !< 6th-order advective flux at south face of grid box -
     362                                                                    !< w-component
     363    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  f1_mg                 !< grid factor used in right hand side of Gauss-Seidel equation
     364                                                                    !< (multigrid)
     365    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  f2_mg                 !< grid factor used in right hand side of Gauss-Seidel equation
     366                                                                    !< (multigrid)
     367    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  f3_mg                 !< grid factor used in right hand side of Gauss-Seidel equation
     368                                                                    !< (multigrid)
    306369    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  mean_inflow_profiles  !< used for turbulent inflow (non-cyclic boundary conditions)
    307     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  precipitation_amount  !< precipitation amount due to gravitational settling (bulk microphysics)
     370    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  precipitation_amount  !< precipitation amount due to gravitational settling
     371                                                                    !< (bulk microphysics)
    308372    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pt_slope_ref          !< potential temperature in rotated coordinate system
    309373                                                                    !< (in case of sloped surface)
    310     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  total_2d_a            !< horizontal array to store the total domain data, used for atmosphere-ocean coupling (atmosphere data)
    311     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  total_2d_o            !< horizontal array to store the total domain data, used for atmosphere-ocean coupling (ocean data)
     374    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rho_air_mg            !< air density profiles on the uv grid for multigrid
     375    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rho_air_zw_mg         !< air density profiles on the w grid for multigrid
     376    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  total_2d_a            !< horizontal array to store the total domain data, used for
     377                                                                    !< atmosphere-ocean coupling (atmosphere data)
     378    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  total_2d_o            !< horizontal array to store the total domain data, used for
     379                                                                    !< atmosphere-ocean coupling (ocean data)
    312380
    313381    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  d           !< divergence
     
    315383    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  de_dy       !< gradient of sgs tke in y-direction (lpm)
    316384    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  de_dz       !< gradient of sgs tke in z-direction (lpm)
    317     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_diss !< artificial numerical dissipation flux at left face of grid box - TKE dissipation
    318     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_e    !< artificial numerical dissipation flux at left face of grid box - subgrid-scale TKE
    319     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_nc   !< artificial numerical dissipation flux at left face of grid box - clouddrop-number concentration
    320     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_ng   !< artificial numerical dissipation flux at left face of grid box - graupel-number concentration
    321     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_ni   !< artificial numerical dissipation flux at left face of grid box - ice crystal-number concentration
    322     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_nr   !< artificial numerical dissipation flux at left face of grid box - raindrop-number concentration
    323     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_ns   !< artificial numerical dissipation flux at left face of grid box - snow-number concentration
    324     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_pt   !< artificial numerical dissipation flux at left face of grid box - potential temperature
    325     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_q    !< artificial numerical dissipation flux at left face of grid box - total water mixing ratio
    326     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_qc   !< artificial numerical dissipation flux at left face of grid box - cloudwater
    327     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_qg   !< artificial numerical dissipation flux at left face of grid box - graupel
    328     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_qi   !< artificial numerical dissipation flux at left face of grid box - ice crystal
    329     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_qr   !< artificial numerical dissipation flux at left face of grid box - rainwater
    330     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_qs   !< artificial numerical dissipation flux at left face of grid box - snow
    331     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_s    !< artificial numerical dissipation flux at left face of grid box - passive scalar
    332     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_sa   !< artificial numerical dissipation flux at left face of grid box - salinity
    333     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_u    !< artificial numerical dissipation flux at left face of grid box - u-component
    334     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_v    !< artificial numerical dissipation flux at left face of grid box - v-component
    335     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_w    !< artificial numerical dissipation flux at left face of grid box - w-component
     385    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_diss !< artificial numerical dissipation flux at left face of grid box -
     386                                                            !< TKE dissipation
     387    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_e    !< artificial numerical dissipation flux at left face of grid box -
     388                                                            !< subgrid-scale TKE
     389    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_nc   !< artificial numerical dissipation flux at left face of grid box -
     390                                                            !< clouddrop-number concentration
     391    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_ng   !< artificial numerical dissipation flux at left face of grid box -
     392                                                            !< graupel-number concentration
     393    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_ni   !< artificial numerical dissipation flux at left face of grid box -
     394                                                            !< ice crystal-number concentration
     395    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_nr   !< artificial numerical dissipation flux at left face of grid box -
     396                                                            !< raindrop-number concentration
     397    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_ns   !< artificial numerical dissipation flux at left face of grid box -
     398                                                            !< snow-number concentration
     399    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_pt   !< artificial numerical dissipation flux at left face of grid box -
     400                                                            !< potential temperature
     401    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_q    !< artificial numerical dissipation flux at left face of grid box -
     402                                                            !< total water mixing ratio
     403    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_qc   !< artificial numerical dissipation flux at left face of grid box -
     404                                                            !< cloudwater
     405    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_qg   !< artificial numerical dissipation flux at left face of grid box -
     406                                                            !< graupel
     407    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_qi   !< artificial numerical dissipation flux at left face of grid box -
     408                                                            !< ice crystal
     409    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_qr   !< artificial numerical dissipation flux at left face of grid box -
     410                                                            !< rainwater
     411    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_qs   !< artificial numerical dissipation flux at left face of grid box -
     412                                                            !< snow
     413    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_s    !< artificial numerical dissipation flux at left face of grid box -
     414                                                            !< passive scalar
     415    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_sa   !< artificial numerical dissipation flux at left face of grid box -
     416                                                            !< salinity
     417    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_u    !< artificial numerical dissipation flux at left face of grid box -
     418                                                            !< u-component
     419    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_v    !< artificial numerical dissipation flux at left face of grid box -
     420                                                            !< v-component
     421    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_w    !< artificial numerical dissipation flux at left face of grid box -
     422                                                            !< w-component
    336423    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_diss !< 6th-order advective flux at south face of grid box - TKE dissipation
    337     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_e    !< 6th-order advective flux at south face of grid box - subgrid-scale TKE
    338     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_nc   !< 6th-order advective flux at south face of grid box - clouddrop-number concentration
    339     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_ng   !< 6th-order advective flux at south face of grid box - graupel-number concentration
    340     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_ni   !< 6th-order advective flux at south face of grid box - ice crystal-number concentration
    341     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_nr   !< 6th-order advective flux at south face of grid box - raindrop-number concentration
     424    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_e    !< 6th-order advective flux at south face of grid box - subgrid-scale
     425                                                            !< TKE
     426    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_nc   !< 6th-order advective flux at south face of grid box - clouddrop-number
     427                                                            !< concentration
     428    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_ng   !< 6th-order advective flux at south face of grid box -
     429                                                            !< graupel-number concentration
     430    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_ni   !< 6th-order advective flux at south face of grid box -
     431                                                            !< ice crystal-number concentration
     432    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_nr   !< 6th-order advective flux at south face of grid box - raindrop-number
     433                                                            !< concentration
    342434    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_ns   !< 6th-order advective flux at south face of grid box - snow-number concentration
    343     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_pt   !< 6th-order advective flux at south face of grid box - potential temperature
     435    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_pt   !< 6th-order advective flux at south face of grid box - potential
     436                                                            !< temperature
    344437    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_q    !< 6th-order advective flux at south face of grid box - mixing ratio
    345438    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_qc   !< 6th-order advective flux at south face of grid box - cloudwater
     
    356449    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  km  !< eddy diffusivity for momentum
    357450    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  prr         !< rain rate
    358     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  p_loc       !< local array in multigrid/sor solver containing the pressure which is iteratively advanced in each iteration step
     451    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  p_loc       !< local array in multigrid/sor solver containing the pressure which is
     452                                                            !< iteratively advanced in each iteration step
    359453    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tend        !< tendency field (time integration)
    360     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tric        !< coefficients of the tridiagonal matrix for solution of the Poisson equation in Fourier space
    361     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_l       !< velocity data (u at left boundary) from time level t-dt required for radiation boundary condition
    362     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_n       !< velocity data (u at north boundary) from time level t-dt required for radiation boundary condition
    363     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_r       !< velocity data (u at right boundary) from time level t-dt required for radiation boundary condition
    364     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_s       !< velocity data (u at south boundary) from time level t-dt required for radiation boundary condition
    365     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_l       !< velocity data (v at left boundary) from time level t-dt required for radiation boundary condition
    366     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_n       !< velocity data (v at north boundary) from time level t-dt required for radiation boundary condition
    367     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_r       !< velocity data (v at right boundary) from time level t-dt required for radiation boundary condition
    368     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_s       !< velocity data (v at south boundary) from time level t-dt required for radiation boundary condition
    369     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_l       !< velocity data (w at left boundary) from time level t-dt required for radiation boundary condition
    370     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_n       !< velocity data (w at north boundary) from time level t-dt required for radiation boundary condition
    371     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_r       !< velocity data (w at right boundary) from time level t-dt required for radiation boundary condition
    372     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_s       !< velocity data (w at south boundary) from time level t-dt required for radiation boundary condition
     454    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tric        !< coefficients of the tridiagonal matrix for solution of the Poisson
     455                                                            !< equation in Fourier space
     456    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_l       !< velocity data (u at left boundary) from time level t-dt required for
     457                                                            !< radiation boundary condition
     458    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_n       !< velocity data (u at north boundary) from time level t-dt required for
     459                                                            !< radiation boundary condition
     460    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_r       !< velocity data (u at right boundary) from time level t-dt required for
     461                                                            !< radiation boundary condition
     462    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_s       !< velocity data (u at south boundary) from time level t-dt required for
     463                                                            !< radiation boundary condition
     464    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_l       !< velocity data (v at left boundary) from time level t-dt required for
     465                                                            !< radiation boundary condition
     466    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_n       !< velocity data (v at north boundary) from time level t-dt required for
     467                                                            !< radiation boundary condition
     468    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_r       !< velocity data (v at right boundary) from time level t-dt required for
     469                                                            !< radiation boundary condition
     470    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_s       !< velocity data (v at south boundary) from time level t-dt required for
     471                                                            !< radiation boundary condition
     472    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_l       !< velocity data (w at left boundary) from time level t-dt required for
     473                                                            !< radiation boundary condition
     474    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_n       !< velocity data (w at north boundary) from time level t-dt required for
     475                                                            !< radiation boundary condition
     476    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_r       !< velocity data (w at right boundary) from time level t-dt required for
     477                                                            !< radiation boundary condition
     478    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_s       !< velocity data (w at south boundary) from time level t-dt required for
     479                                                            !< radiation boundary condition
    373480
    374481    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  diss_1  !< pointer for swapping of timelevels for respective quantity
     
    404511    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qc_2    !< pointer for swapping of timelevels for respective quantity
    405512    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qc_3    !< pointer for swapping of timelevels for respective quantity
     513    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qf_1    !< pointer for swapping of timelevels for respective quantity
    406514    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qg_1    !< pointer for swapping of timelevels for respective quantity
    407515    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qg_2    !< pointer for swapping of timelevels for respective quantity
     
    412520    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_v    !< pointer: volume of liquid water
    413521    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_vp   !< pointer: liquid water weighting factor
    414     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qf_1    !< pointer for swapping of timelevels for respective quantity
    415522    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_1    !< pointer for swapping of timelevels for respective quantity
    416523    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_2    !< pointer for swapping of timelevels for respective quantity
     
    460567    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qc         !< pointer: cloud water content
    461568    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qc_p       !< pointer: prognostic value cloud water content
     569    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qf         !< pointer: frozen water content
    462570    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qg         !< pointer: graupel water content
    463571    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qg_p       !< pointer: prognostic value graupel water content
    464572    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qi         !< pointer: ice crystal content
    465573    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qi_p       !< pointer: prognostic value ice crystal content
    466     REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qf         !< pointer: frozen water content
    467574    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  ql         !< pointer: liquid water content
    468575    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  ql_c       !< pointer: change in liquid water content due to
     
    477584    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  sa         !< pointer: ocean salinity
    478585    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  sa_p       !< pointer: prognostic value of ocean salinity
    479     REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tdiss_m    !< pointer: weighted tendency of diss for previous sub-timestep (Runge-Kutta)
    480     REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  te_m       !< pointer: weighted tendency of e for previous sub-timestep (Runge-Kutta)
    481     REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tnc_m      !< pointer: weighted tendency of nc for previous sub-timestep (Runge-Kutta)
     586    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tdiss_m    !< pointer: weighted tendency of diss for previous sub-timestep
     587                                                                   !< (Runge-Kutta)
     588    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  te_m       !< pointer: weighted tendency of e for previous sub-timestep
     589                                                                   !< (Runge-Kutta)
     590    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tnc_m      !< pointer: weighted tendency of nc for previous sub-timestep
     591                                                                   !< (Runge-Kutta)
    482592    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tng_m      !< pointer: weighted tendency of ng for previous sub-timestep (Runge-Kutta)
    483     REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tni_m      !< pointer: weighted tendency of ni for previous sub-timestep (Runge-Kutta)
    484     REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tnr_m      !< pointer: weighted tendency of nr for previous sub-timestep (Runge-Kutta)
     593    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tni_m      !< pointer: weighted tendency of ni for previous sub-timestep
     594                                                                   !< (Runge-Kutta)
     595    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tnr_m      !< pointer: weighted tendency of nr for previous sub-timestep
     596                                                                   !< (Runge-Kutta)
    485597    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tns_m      !< pointer: weighted tendency of ns for previous sub-timestep (Runge-Kutta)
    486     REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tpt_m      !< pointer: weighted tendency of pt for previous sub-timestep (Runge-Kutta)
    487     REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tq_m       !< pointer: weighted tendency of q for previous sub-timestep (Runge-Kutta)
    488     REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tqc_m      !< pointer: weighted tendency of qc for previous sub-timestep (Runge-Kutta)
     598    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tpt_m      !< pointer: weighted tendency of pt for previous sub-timestep
     599                                                                   !< (Runge-Kutta)
     600    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tq_m       !< pointer: weighted tendency of q for previous sub-timestep
     601                                                                   !< (Runge-Kutta)
     602    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tqc_m      !< pointer: weighted tendency of qc for previous sub-timestep
     603                                                                   !< (Runge-Kutta)
    489604    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tqg_m      !< pointer: weighted tendency of qg for previous sub-timestep (Runge-Kutta)
    490     REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tqi_m      !< pointer: weighted tendency of qi for previous sub-timestep (Runge-Kutta)
    491     REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tqr_m      !< pointer: weighted tendency of qr for previous sub-timestep (Runge-Kutta)
     605    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tqi_m      !< pointer: weighted tendency of qi for previous sub-timestep
     606                                                                   !< (Runge-Kutta)
     607    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tqr_m      !< pointer: weighted tendency of qr for previous sub-timestep
     608                                                                   !< (Runge-Kutta)
    492609    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tqs_m      !< pointer: weighted tendency of qs for previous sub-timestep (Runge-Kutta)
    493     REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  ts_m       !< pointer: weighted tendency of s for previous sub-timestep (Runge-Kutta)
    494     REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tsa_m      !< pointer: weighted tendency of sa for previous sub-timestep (Runge-Kutta)
    495     REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tu_m       !< pointer: weighted tendency of u for previous sub-timestep (Runge-Kutta)
    496     REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tv_m       !< pointer: weighted tendency of v for previous sub-timestep (Runge-Kutta)
    497     REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tw_m       !< pointer: weighted tendency of w for previous sub-timestep (Runge-Kutta)
     610    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  ts_m       !< pointer: weighted tendency of s for previous sub-timestep
     611                                                                   !< (Runge-Kutta)
     612    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tsa_m      !< pointer: weighted tendency of sa for previous sub-timestep
     613                                                                   !< (Runge-Kutta)
     614    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tu_m       !< pointer: weighted tendency of u for previous sub-timestep
     615                                                                   !< (Runge-Kutta)
     616    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tv_m       !< pointer: weighted tendency of v for previous sub-timestep
     617                                                                   !< (Runge-Kutta)
     618    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tw_m       !< pointer: weighted tendency of w for previous sub-timestep
     619                                                                   !< (Runge-Kutta)
    498620    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  u          !< pointer: horizontal velocity component u (x-direction)
    499621    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  u_p        !< pointer: prognostic value of u
     
    504626    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  w_p        !< pointer: prognostic value of w
    505627
    506     REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  tri    !<  array to hold the tridiagonal matrix for solution of the Poisson equation in Fourier space (4th dimension for threads)
    507 
    508     REAL(wp), DIMENSION(:), ALLOCATABLE ::  rho_air      !< air density profile on the uv grid
    509     REAL(wp), DIMENSION(:), ALLOCATABLE ::  rho_air_zw   !< air density profile on the w grid
    510     REAL(wp), DIMENSION(:), ALLOCATABLE ::  drho_air     !< inverse air density profile on the uv grid
    511     REAL(wp), DIMENSION(:), ALLOCATABLE ::  drho_air_zw  !< inverse air density profile on the w grid
    512 
    513     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rho_air_mg     !< air density profiles on the uv grid for multigrid
    514     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rho_air_zw_mg  !< air density profiles on the w grid for multigrid
    515 
    516     REAL(wp), DIMENSION(:), ALLOCATABLE ::  heatflux_input_conversion       !< conversion factor array for heatflux input
    517     REAL(wp), DIMENSION(:), ALLOCATABLE ::  waterflux_input_conversion      !< conversion factor array for waterflux input
    518     REAL(wp), DIMENSION(:), ALLOCATABLE ::  momentumflux_input_conversion   !< conversion factor array for momentumflux input
    519     REAL(wp), DIMENSION(:), ALLOCATABLE ::  heatflux_output_conversion      !< conversion factor array for heatflux output
    520     REAL(wp), DIMENSION(:), ALLOCATABLE ::  waterflux_output_conversion     !< conversion factor array for waterflux output
    521     REAL(wp), DIMENSION(:), ALLOCATABLE ::  momentumflux_output_conversion  !< conversion factor array for momentumflux output
    522 
    523     REAL(wp), DIMENSION(:), ALLOCATABLE ::  hyrho   !< density of air calculated with hydrostatic pressure
    524     REAL(wp), DIMENSION(:), ALLOCATABLE ::  exner   !< ratio of actual and potential temperature
    525     REAL(wp), DIMENSION(:), ALLOCATABLE ::  d_exner !< ratio of potential and actual temperature
     628    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  tri    !< array to hold the tridiagonal matrix for solution of the Poisson
     629                                                         !< equation in Fourier space (4th dimension for threads)
    526630
    527631    SAVE
     
    530634
    531635
    532 !------------------------------------------------------------------------------!
     636!--------------------------------------------------------------------------------------------------!
    533637! Description:
    534638! ------------
    535639!> Definition of variables needed for time-averaging of 2d/3d data.
    536 !------------------------------------------------------------------------------!
     640!--------------------------------------------------------------------------------------------------!
    537641 MODULE averaging
    538642
     
    594698
    595699
    596 !------------------------------------------------------------------------------!
     700!--------------------------------------------------------------------------------------------------!
    597701! Description:
    598702! ------------
    599703!> Definition of parameters for program control
    600 !------------------------------------------------------------------------------!
     704!--------------------------------------------------------------------------------------------------!
    601705 MODULE control_parameters
    602706
     
    608712    END TYPE file_status
    609713
    610     INTEGER, PARAMETER      ::  mask_xyz_dimension = 100  !< limit of mask dimensions (100 points in each direction)
    611     INTEGER, PARAMETER      ::  max_masks = 50            !< maximum number of masks
     714    INTEGER(iwp), PARAMETER ::  fl_max = 500              !< maximum number of virtual-flight measurements
     715    INTEGER,      PARAMETER ::  mask_xyz_dimension = 100  !< limit of mask dimensions (100 points in each direction)
     716    INTEGER,      PARAMETER ::  max_masks = 50            !< maximum number of masks
     717    INTEGER(iwp), PARAMETER ::  var_fl_max = 20           !< maximum number of different sampling variables in virtual flight
     718                                                          !< measurements
    612719    INTEGER(iwp), PARAMETER ::  varnamelength = 30        !< length of output variable names
    613720
     
    616723
    617724    CHARACTER (LEN=1)    ::  cycle_mg = 'w'                               !< namelist parameter (see documentation)
    618     CHARACTER (LEN=1)    ::  timestep_reason = ' '                        !< 'A'dvection or 'D'iffusion criterion, written to RUN_CONTROL file
    619     CHARACTER (LEN=8)    ::  coupling_char = ''                           !< appended to filenames in coupled or nested runs ('_O': ocean PE,
    620                                                                           !< '_NV': vertically nested atmosphere PE, '_N##': PE of nested domain ##
    621     CHARACTER (LEN=23)   ::  origin_date_time = '2019-06-21 12:00:00 +00' !< date and time to be simulated
     725    CHARACTER (LEN=1)    ::  timestep_reason = ' '                        !< 'A'dvection or 'D'iffusion criterion, written to
     726                                                                          !< RUN_CONTROL file
     727    CHARACTER (LEN=5)    ::  run_zone = ' '                               !< time zone of simulation run
     728    CHARACTER (LEN=8)    ::  coupling_char = ''                           !< appended to filenames in coupled or nested runs
     729                                                                          !< ('_O': ocean PE,
     730                                                                          !< '_NV': vertically nested atmosphere PE, '_N##': PE of
     731                                                                          !< nested domain ##
     732    CHARACTER (LEN=8)    ::  run_time = ' '                               !< time of simulation run
     733    CHARACTER (LEN=9)    ::  simulated_time_chr                           !< simulated time, printed to RUN_CONTROL file
    622734    CHARACTER (LEN=10)   ::  run_date = ' '                               !< date of simulation run
    623     CHARACTER (LEN=8)    ::  run_time = ' '                               !< time of simulation run
    624     CHARACTER (LEN=5)    ::  run_zone = ' '                               !< time zone of simulation run
    625     CHARACTER (LEN=9)    ::  simulated_time_chr                           !< simulated time, printed to RUN_CONTROL file
    626735    CHARACTER (LEN=11)   ::  topography_grid_convention = ' '             !< namelist parameter
     736    CHARACTER (LEN=12)   ::  revision = ' '                               !< PALM revision number
    627737    CHARACTER (LEN=12)   ::  version = ' '                                !< PALM version number
    628     CHARACTER (LEN=12)   ::  revision = ' '                               !< PALM revision number
    629     CHARACTER (LEN=12)   ::  user_interface_current_revision = ' '        !< revision number of the currently used user-interface (must match user_interface_required_revision)
     738    CHARACTER (LEN=12)   ::  user_interface_current_revision = ' '        !< revision number of the currently used user-interface
     739                                                                          !< (must match user_interface_required_revision)
    630740    CHARACTER (LEN=12)   ::  user_interface_required_revision = ' '       !< required user-interface revision number
    631741    CHARACTER (LEN=16)   ::  conserve_volume_flow_mode = 'default'        !< namelist parameter
     
    635745    CHARACTER (LEN=16)   ::  scalar_advec = 'ws-scheme'                   !< namelist parameter
    636746    CHARACTER (LEN=20)   ::  approximation = 'boussinesq'                 !< namelist parameter
    637     CHARACTER (LEN=40)   ::  flux_input_mode = 'approximation-specific'   !< type of flux input: dynamic or kinematic
    638     CHARACTER (LEN=40)   ::  flux_output_mode = 'approximation-specific'  !< type of flux output: dynamic or kinematic
    639747    CHARACTER (LEN=20)   ::  bc_e_b = 'neumann'                           !< namelist parameter
    640748    CHARACTER (LEN=20)   ::  bc_lr = 'cyclic'                             !< namelist parameter
     
    651759    CHARACTER (LEN=20)   ::  bc_uv_t = 'dirichlet'                        !< namelist parameter
    652760    CHARACTER (LEN=20)   ::  coupling_mode = 'uncoupled'                  !< coupling mode for atmosphere-ocean coupling
    653     CHARACTER (LEN=20)   ::  coupling_mode_remote = 'uncoupled'           !< coupling mode of the remote process in case of coupled atmosphere-ocean runs
     761    CHARACTER (LEN=20)   ::  coupling_mode_remote = 'uncoupled'           !< coupling mode of the remote process in case of coupled
     762                                                                          !< atmosphere-ocean runs
    654763    CHARACTER (LEN=20)   ::  dissipation_1d = 'detering'                  !< namelist parameter
    655764    CHARACTER (LEN=20)   ::  fft_method = 'temperton-algorithm'           !< namelist parameter
    656765    CHARACTER (LEN=20)   ::  mixing_length_1d = 'blackadar'               !< namelist parameter
    657766    CHARACTER (LEN=20)   ::  random_generator = 'random-parallel'         !< namelist parameter
    658     CHARACTER (LEN=80)   ::  recycling_method_for_thermodynamic_quantities = 'turbulent_fluctuation'        !< namelist parameter
    659767    CHARACTER (LEN=20)   ::  reference_state = 'initial_profile'          !< namelist parameter
    660768    CHARACTER (LEN=20)   ::  restart_data_format = 'fortran_binary'       !< namelist parameter
     
    663771    CHARACTER (LEN=20)   ::  timestep_scheme = 'runge-kutta-3'            !< namelist parameter
    664772    CHARACTER (LEN=20)   ::  turbulence_closure = '1.5-order'             !< namelist parameter
     773    CHARACTER (LEN=23)   ::  origin_date_time = '2019-06-21 12:00:00 +00' !< date and time to be simulated
     774    CHARACTER (LEN=40)   ::  flux_input_mode = 'approximation-specific'   !< type of flux input: dynamic or kinematic
     775    CHARACTER (LEN=40)   ::  flux_output_mode = 'approximation-specific'  !< type of flux output: dynamic or kinematic
    665776    CHARACTER (LEN=40)   ::  topography = 'flat'                          !< namelist parameter
    666     CHARACTER (LEN=64)   ::  host = '????'                                !< configuration identifier as given by palmrun option -c, ENVPAR namelist parameter provided by palmrun
     777    CHARACTER (LEN=64)   ::  host = '????'                                !< configuration identifier as given by palmrun option -c,
     778                                                                          !< ENVPAR namelist parameter provided by palmrun
    667779    CHARACTER (LEN=80)   ::  log_message                                  !< user-defined message for debugging (sse data_log.f90)
    668     CHARACTER (LEN=80)   ::  run_identifier                               !< run identifier as given by palmrun option -r, ENVPAR namelist parameter provided by palmrun
     780    CHARACTER (LEN=80)   ::  recycling_method_for_thermodynamic_quantities = 'turbulent_fluctuation'        !< namelist parameter
     781    CHARACTER (LEN=80)   ::  run_identifier                               !< run identifier as given by palmrun option -r, ENVPAR
     782                                                                          !< namelist parameter provided by palmrun
    669783    CHARACTER (LEN=100)  ::  initializing_actions = ' '                   !< namelist parameter
    670     CHARACTER (LEN=100)  ::  restart_string = ' '                         !< for storing strings in case of writing/reading restart data
    671     CHARACTER (LEN=210)  ::  run_description_header                       !< string containing diverse run informations as run identifier, coupling mode, host, ensemble number, run date and time
     784    CHARACTER (LEN=100)  ::  restart_string = ' '                         !< for storing strings in case of writing/reading restart
     785                                                                          !< data
     786    CHARACTER (LEN=210)  ::  run_description_header                       !< string containing diverse run informations as run
     787                                                                          !< identifier, coupling mode, host, ensemble number, run
     788                                                                          !< date and time
    672789    CHARACTER (LEN=1000) ::  debug_string = ' '                           !<.....
    673790    CHARACTER (LEN=1000) ::  message_string = ' '                         !< dynamic string for error message output
    674791
    675     CHARACTER (LEN=varnamelength), DIMENSION(500) ::  data_output = ' '       !< namelist parameter
    676     CHARACTER (LEN=varnamelength), DIMENSION(500) ::  data_output_user = ' '  !< namelist parameter
    677     CHARACTER (LEN=varnamelength), DIMENSION(500) ::  doav = ' '              !< label array for multi-dimensional,
    678                                                                               !< averaged output quantities
     792    CHARACTER (LEN=varnamelength), DIMENSION(200) ::  data_output_pr_user = ' '  !< namelist parameter
     793    CHARACTER (LEN=varnamelength), DIMENSION(300) ::  data_output_pr = ' '       !< namelist parameter
     794    CHARACTER (LEN=varnamelength), DIMENSION(500) ::  data_output = ' '          !< namelist parameter
     795    CHARACTER (LEN=varnamelength), DIMENSION(500) ::  data_output_user = ' '     !< namelist parameter
     796    CHARACTER (LEN=varnamelength), DIMENSION(500) ::  doav = ' '                 !< label array for multi-dimensional,
     797                                                                                 !< averaged output quantities
    679798
    680799    CHARACTER (LEN=varnamelength), DIMENSION(max_masks,100) ::  data_output_masks = ' '       !< namelist parameter
    681800    CHARACTER (LEN=varnamelength), DIMENSION(max_masks,100) ::  data_output_masks_user = ' '  !< namelist parameter
    682 
    683     CHARACTER (LEN=varnamelength), DIMENSION(300) ::  data_output_pr = ' '  !< namelist parameter
    684 
    685     CHARACTER (LEN=varnamelength), DIMENSION(200) ::  data_output_pr_user = ' '  !< namelist parameter
     801    CHARACTER (LEN=varnamelength), DIMENSION(0:1,500)       ::  do2d = ' '                    !< label array for 2d output
     802                                                                                              !< quantities
     803    CHARACTER (LEN=varnamelength), DIMENSION(0:1,500)       ::  do3d = ' '                    !< label array for 3d output
     804                                                                                              !< quantities
    686805
    687806    CHARACTER (LEN=varnamelength), DIMENSION(max_masks,0:1,100) ::  domask = ' ' !< label array for multi-dimensional,
    688807                                                                                 !< masked output quantities
    689 
    690     CHARACTER (LEN=varnamelength), DIMENSION(0:1,500) ::  do2d = ' '  !< label array for 2d output quantities
    691     CHARACTER (LEN=varnamelength), DIMENSION(0:1,500) ::  do3d = ' '  !< label array for 3d output quantities
    692 
    693     INTEGER(iwp), PARAMETER ::  fl_max = 500     !< maximum number of virtual-flight measurements
    694     INTEGER(iwp), PARAMETER ::  var_fl_max = 20  !< maximum number of different sampling variables in virtual flight measurements
    695808
    696809    INTEGER(iwp) ::  abort_mode = 1                    !< abort condition (nested runs)
     
    699812    INTEGER(iwp) ::  average_count_3d = 0              !< number of samples in 3d output
    700813    INTEGER(iwp) ::  current_timestep_number = 0       !< current timestep number, printed to RUN_CONTROL file
    701     INTEGER(iwp) ::  coupling_topology = 0             !< switch for atmosphere-ocean-coupling: 0: same number of grid points and PEs along x and y in atmosphere and ocean, otherwise 1
    702     INTEGER(iwp) ::  dist_range = 0                    !< switch for steering the horizontal disturbance range, 1: inflow disturbances in case of non-cyclic horizontal BC, 0: otherwise
     814    INTEGER(iwp) ::  coupling_topology = 0             !< switch for atmosphere-ocean-coupling: 0: same number of grid points and
     815                                                       !< PEs along x and y in atmosphere and ocean, otherwise 1
     816    INTEGER(iwp) ::  dist_range = 0                    !< switch for steering the horizontal disturbance range, 1: inflow
     817                                                       !< disturbances in case of non-cyclic horizontal BC, 0: otherwise
    703818    INTEGER(iwp) ::  disturbance_level_ind_b           !< lowest grid index where flow disturbance is applied
    704819    INTEGER(iwp) ::  disturbance_level_ind_t           !< highest grid index where flow disturbance is applied
     
    711826    INTEGER(iwp) ::  ensemble_member_nr = 0            !< namelist parameter
    712827    INTEGER(iwp) ::  gamma_mg                          !< switch for steering the multigrid cycle: 1: v-cycle, 2: w-cycle
    713     INTEGER(iwp) ::  gathered_size                     !< number of total domain grid points of the grid level which is gathered on PE0 (multigrid solver)
     828    INTEGER(iwp) ::  gathered_size                     !< number of total domain grid points of the grid level which is gathered on
     829                                                       !< PE0 (multigrid solver)
    714830    INTEGER(iwp) ::  grid_level                        !< current grid level handled in the multigrid solver
    715831    INTEGER(iwp) ::  ibc_e_b                           !< integer flag for bc_e_b
     
    729845    INTEGER(iwp) ::  intermediate_timestep_count_max   !< maximum number of Runge-Kutta substeps
    730846    INTEGER(iwp) ::  io_group = 0                      !< I/O group to which the PE belongs (= #PE / io_blocks)
    731     INTEGER(iwp) ::  io_blocks = 1                     !< number of blocks for which I/O is done in sequence (total number of PEs / maximum_parallel_io_streams)
     847    INTEGER(iwp) ::  io_blocks = 1                     !< number of blocks for which I/O is done in sequence (total number of PEs /
     848                                                       !< maximum_parallel_io_streams)
    732849    INTEGER(iwp) ::  iran = -1234567                   !< integer random number used for flow disturbances
    733     INTEGER(iwp) ::  length = 0                        !< integer that specifies the length of a string in case of writing/reading restart data
     850    INTEGER(iwp) ::  length = 0                        !< integer that specifies the length of a string in case of writing/reading
     851                                                       !< restart data
    734852    INTEGER(iwp) ::  masks = 0                         !< counter for number of masked output quantities
    735853    INTEGER(iwp) ::  maximum_grid_level                !< number of grid levels that the multigrid solver is using
    736     INTEGER(iwp) ::  maximum_parallel_io_streams = -1  !< maximum number of parallel io streams that the underlying parallel file system allows, set with palmrun option -w, ENVPAR namelist parameter, provided by palmrun
     854    INTEGER(iwp) ::  maximum_parallel_io_streams = -1  !< maximum number of parallel io streams that the underlying parallel file
     855                                                       !< system allows, set with palmrun option -w, ENVPAR namelist parameter, provided by palmrun
    737856    INTEGER(iwp) ::  max_pr_salsa = 0                  !< number of salsa profiles (must not change within a job chain)
    738857    INTEGER(iwp) ::  max_pr_user = 0                   !< number of user-defined profiles (must not change within a job chain)
    739     INTEGER(iwp) ::  max_pr_user_tmp = 0               !< number of user-defined profiles that is temporary stored to check it against max_pr_user in case of restarts
    740     INTEGER(iwp) ::  mgcycles = 0                      !< number of multigrid cycles that the multigrid solver has actually carried out
     858    INTEGER(iwp) ::  max_pr_user_tmp = 0               !< number of user-defined profiles that is temporary stored to check it
     859                                                       !< against max_pr_user in case of restarts
     860    INTEGER(iwp) ::  mgcycles = 0                      !< number of multigrid cycles that the multigrid solver has actually carried
     861                                                       !< out
    741862    INTEGER(iwp) ::  mg_cycles = 4                     !< namelist parameter
    742863    INTEGER(iwp) ::  mg_switch_to_pe0_level = -1       !< namelist parameter
     
    750871    INTEGER(iwp) ::  num_leg=0                         !< number of different legs in virtual flight measurements
    751872    INTEGER(iwp) ::  num_var_fl                        !< number of sampling/output variables in virtual flight measurements
    752     INTEGER(iwp) ::  num_var_fl_user=0                 !< number of user-defined sampling/output variables in virtual flight measurements
     873    INTEGER(iwp) ::  num_var_fl_user=0                 !< number of user-defined sampling/output variables in virtual flight
     874                                                       !< measurements
    753875    INTEGER(iwp) ::  number_stretch_level_start        !< number of user-specified start levels for stretching
    754876    INTEGER(iwp) ::  number_stretch_level_end          !< number of user-specified end levels for stretching
    755877    INTEGER(iwp) ::  nz_do3d = -9999                   !< namelist parameter
    756878    INTEGER(iwp) ::  prt_time_count = 0                !< number of output intervals for particle data output
    757     INTEGER(iwp) ::  recycling_plane                   !< position of recycling plane along x (in grid points) in case of turbulence recycling
     879    INTEGER(iwp) ::  recycling_plane                   !< position of recycling plane along x (in grid points) in case of turbulence
     880                                                       !< recycling
    758881    INTEGER(iwp) ::  runnr = 0                         !< number of run in job chain
    759882    INTEGER(iwp) ::  subdomain_size                    !< number of grid points in (3d) subdomain including ghost points
    760883    INTEGER(iwp) ::  symmetry_flag = 0                 !< flag for sterring the symmetric behavior of the bottom and top boundary
    761884    INTEGER(iwp) ::  terminate_coupled = 0             !< switch for steering termination in case of coupled runs
    762     INTEGER(iwp) ::  terminate_coupled_remote = 0      !< switch for steering termination in case of coupled runs (condition of the remote model)
     885    INTEGER(iwp) ::  terminate_coupled_remote = 0      !< switch for steering termination in case of coupled runs (condition of the
     886                                                       !< remote model)
    763887    INTEGER(iwp) ::  timestep_count = 0                !< number of timesteps carried out since the beginning of the initial run
    764888    INTEGER(iwp) ::  y_shift = 0                       !< namelist parameter
     
    776900    INTEGER(iwp) ::  domask_no(max_masks,0:1) = 0                !< number of masked output quantities
    777901    INTEGER(iwp) ::  domask_time_count(max_masks,0:1)            !< number of output intervals for masked data
    778     INTEGER(iwp) ::  dz_stretch_level_end_index(9)               !< vertical grid level index until which the vertical grid spacing is stretched
    779     INTEGER(iwp) ::  dz_stretch_level_start_index(9)             !< vertical grid level index above which the vertical grid spacing is stretched
     902    INTEGER(iwp) ::  dz_stretch_level_end_index(9)               !< vertical grid level index until which the vertical grid spacing
     903                                                                 !< is stretched
     904    INTEGER(iwp) ::  dz_stretch_level_start_index(9)             !< vertical grid level index above which the vertical grid spacing
     905                                                                 !< is stretched
    780906    INTEGER(iwp) ::  mask_size(max_masks,3) = -1                 !< size of mask array per mask and dimension (for netcdf output)
    781     INTEGER(iwp) ::  mask_size_l(max_masks,3) = -1               !< subdomain size of mask array per mask and dimension (for netcdf output)
     907    INTEGER(iwp) ::  mask_size_l(max_masks,3) = -1               !< subdomain size of mask array per mask and dimension
     908                                                                 !< (for netcdf output)
    782909    INTEGER(iwp) ::  mask_start_l(max_masks,3) = -1              !< subdomain start index of mask array (for netcdf output)
    783910    INTEGER(iwp) ::  pt_vertical_gradient_level_ind(10) = -9999  !< grid index values of pt_vertical_gradient_level(s)
     
    796923    INTEGER(iwp), DIMENSION(0:1) ::  ntdim_3d     !< number of output intervals for 3d data
    797924
     925    INTEGER(iwp), DIMENSION(max_masks,mask_xyz_dimension) ::  mask_k_over_surface = -1  !< namelist parameter, k index of height
     926                                                                                        !<over surface
     927
    798928    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  grid_level_count  !< internal switch for steering the multigrid v- and w-cycles
    799929
     
    805935    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  mask_k_global  !< global grid index of masked output point on z-dimension
    806936
    807     INTEGER(iwp), DIMENSION(max_masks,mask_xyz_dimension) ::  mask_k_over_surface = -1  !< namelist parameter, k index of height over surface
    808937
    809938    LOGICAL ::  agent_time_unlimited = .FALSE.                   !< namelist parameter
    810939    LOGICAL ::  air_chemistry = .FALSE.                          !< chemistry model switch
    811     LOGICAL ::  bc_dirichlet_l = .FALSE.                         !< flag indicating dirichlet boundary condition on left model boundary
    812     LOGICAL ::  bc_dirichlet_n = .FALSE.                         !< flag indicating dirichlet boundary condition on north model boundary
    813     LOGICAL ::  bc_dirichlet_r = .FALSE.                         !< flag indicating dirichlet boundary condition on right model boundary
    814     LOGICAL ::  bc_dirichlet_s = .FALSE.                         !< flag indicating dirichlet boundary condition on south model boundary
     940    LOGICAL ::  bc_dirichlet_l = .FALSE.                         !< flag indicating dirichlet boundary condition on left model
     941                                                                 !< boundary
     942    LOGICAL ::  bc_dirichlet_n = .FALSE.                         !< flag indicating dirichlet boundary condition on north model
     943                                                                 !< boundary
     944    LOGICAL ::  bc_dirichlet_r = .FALSE.                         !< flag indicating dirichlet boundary condition on right model
     945                                                                 !< boundary
     946    LOGICAL ::  bc_dirichlet_s = .FALSE.                         !< flag indicating dirichlet boundary condition on south model
     947                                                                 !< boundary
    815948    LOGICAL ::  bc_lr_cyc =.TRUE.                                !< left-right boundary condition cyclic?
    816949    LOGICAL ::  bc_lr_dirrad = .FALSE.                           !< left-right boundary condition dirichlet/radiation?
     
    820953    LOGICAL ::  bc_ns_raddir = .FALSE.                           !< north-south boundary condition radiation/dirichlet?
    821954    LOGICAL ::  bc_radiation_l = .FALSE.                         !< radiation boundary condition for outflow at left domain boundary
    822     LOGICAL ::  bc_radiation_n = .FALSE.                         !< radiation boundary condition for outflow at north domain boundary
    823     LOGICAL ::  bc_radiation_r = .FALSE.                         !< radiation boundary condition for outflow at right domain boundary
    824     LOGICAL ::  bc_radiation_s = .FALSE.                         !< radiation boundary condition for outflow at south domain boundary
     955    LOGICAL ::  bc_radiation_n = .FALSE.                         !< radiation boundary condition for outflow at north domain
     956                                                                 !< boundary
     957    LOGICAL ::  bc_radiation_r = .FALSE.                         !< radiation boundary condition for outflow at right domain
     958                                                                 !< boundary
     959    LOGICAL ::  bc_radiation_s = .FALSE.                         !< radiation boundary condition for outflow at south domain
     960                                                                 !< boundary
    825961    LOGICAL ::  biometeorology = .FALSE.                         !< biometeorology module switch
    826962    LOGICAL ::  calc_soil_moisture_during_spinup = .FALSE.       !< namelist parameter
     
    859995    LOGICAL ::  galilei_transformation = .FALSE.                 !< namelist parameter
    860996    LOGICAL ::  humidity = .FALSE.                               !< namelist parameter
    861     LOGICAL ::  humidity_remote = .FALSE.                        !< switch for receiving near-surface humidity flux (atmosphere-ocean coupling)
     997    LOGICAL ::  humidity_remote = .FALSE.                        !< switch for receiving near-surface humidity flux
     998                                                                 !< (atmosphere-ocean coupling)
    862999    LOGICAL ::  include_total_domain_boundaries = .FALSE.        !< store outer boundaries in restart file (MPI-IO)
    8631000    LOGICAL ::  indoor_model = .FALSE.                           !< switch for indoor-climate and energy-demand model
    864     LOGICAL ::  kolmogorov_length_scale = .FALSE.                !< switch to activate calculations in flow_statistics for the kolmogorov length scale
     1001    LOGICAL ::  kolmogorov_length_scale = .FALSE.                !< switch to activate calculations in flow_statistics for the
     1002                                                                 !< kolmogorov length scale
    8651003    LOGICAL ::  large_scale_forcing = .FALSE.                    !< namelist parameter
    8661004    LOGICAL ::  large_scale_subsidence = .FALSE.                 !< namelist parameter
    8671005    LOGICAL ::  land_surface = .FALSE.                           !< use land surface model?
    868     LOGICAL ::  les_dai = .FALSE.                                !< use Dai et al. turbulence closure (modified 1.5-order closure) for LES mode. Shall replace the default 1.5-order closure
     1006    LOGICAL ::  les_dai = .FALSE.                                !< use Dai et al. turbulence closure (modified 1.5-order closure)
     1007                                                                 !< for LES mode. Shall replace the default 1.5-order closure
    8691008    LOGICAL ::  les_dynamic = .FALSE.                            !< use dynamic subgrid model as turbulence closure for LES mode
    8701009    LOGICAL ::  les_default = .FALSE.                            !< use 1.5-order default turbulence closure for LES mode
     
    8731012    LOGICAL ::  lsf_vert = .TRUE.                                !< use atmospheric forcing (large scale forcing)?
    8741013    LOGICAL ::  masking_method = .FALSE.                         !< namelist parameter
    875     LOGICAL ::  mg_switch_to_pe0 = .FALSE.                       !< internal multigrid switch for steering the ghost point exchange in case that data has been collected on PE0
     1014    LOGICAL ::  mg_switch_to_pe0 = .FALSE.                       !< internal multigrid switch for steering the ghost point exchange
     1015                                                                 !< in case that data has been collected on PE0
    8761016    LOGICAL ::  monotonic_limiter_z = .FALSE.                    !< use monotonic flux limiter for vertical scalar advection
    8771017    LOGICAL ::  nesting_offline = .FALSE.                        !< flag controlling offline nesting in COSMO model
     
    8851025    LOGICAL ::  rans_tke_e = .FALSE.                             !< use TKE-e turbulence closure for RANS mode
    8861026    LOGICAL ::  rans_tke_l = .FALSE.                             !< use TKE-l turbulence closure for RANS mode
    887     LOGICAL ::  read_svf = .FALSE.                               !< ENVPAR namelist parameter to steer input of svf (ENVPAR is provided by palmrun)
     1027    LOGICAL ::  read_svf = .FALSE.                               !< ENVPAR namelist parameter to steer input of svf
     1028                                                                 !< (ENVPAR is provided by palmrun)
    8881029    LOGICAL ::  run_control_header = .FALSE.                     !< onetime output of RUN_CONTROL header
    889     LOGICAL ::  run_coupled = .TRUE.                             !< internal switch telling PALM to run in coupled mode (i.e. to exchange surface data) in case of atmosphere-ocean coupling
     1030    LOGICAL ::  run_coupled = .TRUE.                             !< internal switch telling PALM to run in coupled mode
     1031                                                                 !< (i.e. to exchange surface data) in case of atmosphere-ocean coupling
    8901032    LOGICAL ::  salsa = .FALSE.                                  !< switch for the sectional aerosol module salsa
    8911033    LOGICAL ::  scalar_rayleigh_damping = .TRUE.                 !< namelist parameter
     
    9051047    LOGICAL ::  use_fixed_date = .FALSE.                         !< date of simulation does not change (namelist parameter)
    9061048    LOGICAL ::  use_fixed_time = .FALSE.                         !< time of simulation does not change (namelist parameter)
    907     LOGICAL ::  use_free_convection_scaling = .FALSE.            !< namelist parameter to switch on free convection velocity scale in calculation of horizontal wind speed (surface_layer_fluxes)
     1049    LOGICAL ::  use_free_convection_scaling = .FALSE.            !< namelist parameter to switch on free convection velocity scale
     1050                                                                 !< in calculation of horizontal wind speed (surface_layer_fluxes)
    9081051    LOGICAL ::  use_initial_profile_as_reference = .FALSE.       !< use of initial profiles as reference state?
    9091052    LOGICAL ::  use_prescribed_profile_data = .FALSE.            !< use of prescribed wind profiles?
     
    9201063    LOGICAL ::  wall_adjustment = .TRUE.                         !< namelist parameter
    9211064    LOGICAL ::  wind_turbine = .FALSE.                           !< flag for use of wind turbine model
    922     LOGICAL ::  write_binary = .FALSE.                           !< ENVPAR namelist parameter to steer restart I/O (ENVPAR is provided by palmrun)
    923     LOGICAL ::  write_svf = .FALSE.                              !< ENVPAR namelist parameter to steer output of svf (ENVPAR is provided by palmrun)
     1065    LOGICAL ::  write_binary = .FALSE.                           !< ENVPAR namelist parameter to steer restart I/O
     1066                                                                 !< (ENVPAR is provided by palmrun)
     1067    LOGICAL ::  write_svf = .FALSE.                              !< ENVPAR namelist parameter to steer output of svf
     1068                                                                 !< (ENVPAR is provided by palmrun)
    9241069    LOGICAL ::  ws_scheme_sca = .FALSE.                          !< use Wicker-Skamarock scheme (scalar advection)?
    9251070    LOGICAL ::  ws_scheme_mom = .FALSE.                          !< use Wicker-Skamarock scheme (momentum advection)?
     
    10671212    REAL(wp) ::  time_restart = 9999999.9_wp                   !< time at which run shall be terminated and restarted
    10681213    REAL(wp) ::  time_run_control = 0.0_wp                     !< time since last RUN_CONTROL output
    1069     REAL(wp) ::  time_since_reference_point = 0.0_wp           !< time after atmosphere-ocean coupling has been activated, or time after spinup phase of LSM has been finished
     1214    REAL(wp) ::  time_since_reference_point = 0.0_wp           !< time after atmosphere-ocean coupling has been activated, or time
     1215                                                               !< after spinup phase of LSM has been finished
    10701216    REAL(wp) ::  top_heatflux = 9999999.9_wp                   !< namelist parameter
    10711217    REAL(wp) ::  top_momentumflux_u = 9999999.9_wp             !< namelist parameter
     
    11001246    REAL(wp) ::  mask_scale(3)                                     !< collective array for mask_scale_x/y/z
    11011247    REAL(wp) ::  pt_vertical_gradient(10) = 0.0_wp                 !< namelist parameter
    1102     REAL(wp) ::  pt_vertical_gradient_level(10) = -999999.9_wp   !< namelist parameter
     1248    REAL(wp) ::  pt_vertical_gradient_level(10) = -999999.9_wp     !< namelist parameter
    11031249    REAL(wp) ::  q_vertical_gradient(10) = 0.0_wp                  !< namelist parameter
    1104     REAL(wp) ::  q_vertical_gradient_level(10) = -999999.9_wp    !< namelist parameter
     1250    REAL(wp) ::  q_vertical_gradient_level(10) = -999999.9_wp      !< namelist parameter
    11051251    REAL(wp) ::  s_vertical_gradient(10) = 0.0_wp                  !< namelist parameter
    1106     REAL(wp) ::  s_vertical_gradient_level(10) = -999999.9_wp    !< namelist parameter
     1252    REAL(wp) ::  s_vertical_gradient_level(10) = -999999.9_wp      !< namelist parameter
    11071253    REAL(wp) ::  skip_time_domask(max_masks) = 9999999.9_wp        !< namelist parameter
    11081254    REAL(wp) ::  threshold(20) = 0.0_wp                            !< namelist parameter
     
    11171263    REAL(wp) ::  vg_vertical_gradient(10) = 0.0_wp                 !< namelist parameter
    11181264    REAL(wp) ::  vg_vertical_gradient_level(10) = -9999999.9_wp    !< namelist parameter
    1119     REAL(wp) ::  volume_flow(1:3) = 0.0_wp                         !< volume flow through 1:yz-plane, 2: xz-plane, 3: xy-plane (nest childs only)
     1265    REAL(wp) ::  volume_flow(1:3) = 0.0_wp                         !< volume flow through 1:yz-plane, 2: xz-plane, 3: xy-plane
     1266                                                                   !< (nest childs only)
    11201267    REAL(wp) ::  volume_flow_area(1:3) = 0.0_wp                    !< area of the respective volume flow planes
    1121     REAL(wp) ::  volume_flow_initial(1:3) = 0.0_wp                 !< initial volume flow (t=0) through the respective volume flow planes
     1268    REAL(wp) ::  volume_flow_initial(1:3) = 0.0_wp                 !< initial volume flow (t=0) through the respective volume flow
     1269                                                                   !< planes
    11221270    REAL(wp) ::  wall_heatflux(0:5) = 0.0_wp                       !< namelist parameter
    11231271    REAL(wp) ::  wall_humidityflux(0:5) = 0.0_wp                   !< namelist parameter
     
    11381286
    11391287!
    1140 !--    internal mask arrays ("mask,dimension,selection")
     1288!--    Internal mask arrays ("mask,dimension,selection")
    11411289       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  mask       !< collective array for mask_x/y/z
    11421290       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  mask_loop  !< collective array for mask_x/y/z_loop
     
    11471295
    11481296
    1149 !------------------------------------------------------------------------------!
     1297!--------------------------------------------------------------------------------------------------!
    11501298! Description:
    11511299! ------------
    11521300!> Definition of grid spacings.
    1153 !------------------------------------------------------------------------------!
     1301!--------------------------------------------------------------------------------------------------!
    11541302 MODULE grid_variables
    11551303
     
    11761324
    11771325
    1178 !------------------------------------------------------------------------------!
     1326!--------------------------------------------------------------------------------------------------!
    11791327! Description:
    11801328! ------------
    11811329!> Definition of array bounds, number of gridpoints, and wall flag arrays.
    1182 !------------------------------------------------------------------------------!
     1330!--------------------------------------------------------------------------------------------------!
    11831331 MODULE indices
    11841332
     
    11861334
    11871335    INTEGER(iwp) ::  nbgp = 3       !< number of boundary ghost points
    1188     INTEGER(iwp) ::  ngp_sums       !< number of vertical profile grid points time number of output profiles - used for allreduce statements in MPI calls
    1189     INTEGER(iwp) ::  ngp_sums_ls    !< number of vertical profile grid points time number of large-scale forcing profiles - used for allreduce statements in MPI calls
     1336    INTEGER(iwp) ::  ngp_sums       !< number of vertical profile grid points time number of output profiles - used for allreduce
     1337                                    !< statements in MPI calls
     1338    INTEGER(iwp) ::  ngp_sums_ls    !< number of vertical profile grid points time number of large-scale forcing profiles - used for
     1339                                    !< allreduce statements in MPI calls
    11901340    INTEGER(iwp) ::  nnx            !< number of subdomain grid points in x-direction
    11911341    INTEGER(iwp) ::  nx = 0         !< nx+1 = total number of grid points in x-direction
     
    11941344    INTEGER(iwp) ::  nxl            !< left-most grid index of subdomain (excluding ghost points)
    11951345    INTEGER(iwp) ::  nxlg           !< left-most grid index of subdomain (including ghost points)
    1196     INTEGER(iwp) ::  nxlu           !< =nxl+1 (at left domain boundary with inflow from left), else =nxl (used for u-velocity component)
     1346    INTEGER(iwp) ::  nxlu           !< =nxl+1 (at left domain boundary with inflow from left), else =nxl
     1347                                    !< (used for u-velocity component)
    11971348    INTEGER(iwp) ::  nxr            !< right-most grid index of subdomain (excluding ghost points)
    11981349    INTEGER(iwp) ::  nxrg           !< right-most grid index of subdomain (including ghost points)
     
    12061357    INTEGER(iwp) ::  nys            !< south-most grid index of subdomain (excluding ghost points)
    12071358    INTEGER(iwp) ::  nysg           !< south-most grid index of subdomain (including ghost points)
    1208     INTEGER(iwp) ::  nysv           !< =nys+1 (at south domain boundary with inflow from south), else =nys (used for v-velocity component)
     1359    INTEGER(iwp) ::  nysv           !< =nys+1 (at south domain boundary with inflow from south), else =nys
     1360                                    !< (used for v-velocity component)
    12091361    INTEGER(iwp) ::  ny_on_file     !< ny of previous run in job chain
    12101362    INTEGER(iwp) ::  nnz            !< number of subdomain grid points in z-direction
     
    12161368    INTEGER(iwp) ::  topo_min_level !< minimum topography-top index (usually equal to nzb)
    12171369
     1370    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_2dh       !< number of grid points of a horizontal cross section through the
     1371                                                              !< total domain
    12181372    INTEGER(idp), DIMENSION(:), ALLOCATABLE ::  ngp_3d        !< number of grid points of the total domain
    12191373    INTEGER(idp), DIMENSION(:), ALLOCATABLE ::  ngp_3d_inner  !< ! need to have 64 bit for grids > 2E9
    1220 
    1221     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_2dh  !< number of grid points of a horizontal cross section through the total domain
    1222     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nxl_mg   !< left-most grid index of subdomain on different multigrid level
    1223     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nxr_mg   !< right-most grid index of subdomain on different multigrid level
    1224     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nyn_mg   !< north-most grid index of subdomain on different multigrid level
    1225     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nys_mg   !< south-most grid index of subdomain on different multigrid level
    1226     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nzt_mg   !< top-most grid index of subdomain on different multigrid level
    1227 
    1228 
    1229     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  ngp_2dh_outer     !< number of horizontal grid points which are non-topography and non-surface-bounded
     1374    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nxl_mg        !< left-most grid index of subdomain on different multigrid level
     1375    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nxr_mg        !< right-most grid index of subdomain on different multigrid level
     1376    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nyn_mg        !< north-most grid index of subdomain on different multigrid level
     1377    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nys_mg        !< south-most grid index of subdomain on different multigrid level
     1378    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nzt_mg        !< top-most grid index of subdomain on different multigrid level
     1379
     1380
     1381    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  mg_loc_ind        !< internal array to store index bounds of all PEs of that
     1382                                                                    !< multigrid level where data is collected to PE0
     1383    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  ngp_2dh_outer     !< number of horizontal grid points which are non-topography and
     1384                                                                    !< non-surface-bounded
    12301385    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  ngp_2dh_s_inner   !< number of horizontal grid points which are non-topography
    1231     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  mg_loc_ind        !< internal array to store index bounds of all PEs of that multigrid level where data is collected to PE0
    1232 
    1233     INTEGER(iwp), DIMENSION(:,:,:), POINTER ::  flags  !< pointer to wall_flags_1-10
    12341386
    12351387    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_1   !< topograpyh masking flag on multigrid level 1
     
    12441396    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_10  !< topograpyh masking flag on multigrid level 10
    12451397
    1246     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  advc_flags_m            !< flags used to degrade order of advection scheme for momentum
    1247     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  advc_flags_s            !< flags used to degrade order of advection scheme for scalar quantities
     1398    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  advc_flags_m            !< flags used to degrade order of advection scheme for
     1399                                                                            !< momentum
     1400    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  advc_flags_s            !< flags used to degrade order of advection scheme for
     1401                                                                            !< scalar quantities
    12481402    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  topo_top_ind            !< precalculated topography top indices
    1249     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  wall_flags_static_0     !< flags to mask topography and surface-bounded grid points
    1250     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  wall_flags_total_0      !< merged array, which contains the static and dynamic flags
     1403    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  wall_flags_static_0     !< flags to mask topography and surface-bounded grid
     1404                                                                            !< points
     1405    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  wall_flags_total_0      !< merged array, which contains the static and dynamic
     1406                                                                            !< flags
     1407
     1408    INTEGER(iwp), DIMENSION(:,:,:), POINTER ::  flags  !< pointer to wall_flags_1-10
    12511409
    12521410    SAVE
     
    12551413
    12561414
    1257 !------------------------------------------------------------------------------!
     1415!--------------------------------------------------------------------------------------------------!
    12581416! Description:
    12591417! ------------
    12601418!> Interfaces for special subroutines which use optional parameters.
    1261 !------------------------------------------------------------------------------!
     1419!--------------------------------------------------------------------------------------------------!
    12621420 MODULE interfaces
    12631421
    12641422    INTERFACE
    12651423
    1266 !------------------------------------------------------------------------------!
     1424!--------------------------------------------------------------------------------------------------!
    12671425! Description:
    12681426! ------------
    12691427!> @todo Missing subroutine description.
    1270 !------------------------------------------------------------------------------!
    1271        SUBROUTINE global_min_max ( i1, i2, j1, j2, k1, k2, array, mode, offset, &
    1272                                    result, result_ijk, result1, result1_ijk )
     1428!--------------------------------------------------------------------------------------------------!
     1429       SUBROUTINE global_min_max ( i1, i2, j1, j2, k1, k2, array, mode, offset, result, result_ijk,&
     1430                                   result1, result1_ijk )
    12731431
    12741432          USE kinds
    12751433
    1276           CHARACTER (LEN=*), INTENT(IN) ::  mode                      !< mode of global min/max function: can be 'min', 'max', 'minmax', 'abs', or 'absoff'
     1434          CHARACTER (LEN=*), INTENT(IN) ::  mode                      !< mode of global min/max function: can be 'min', 'max',
     1435                                                                      !< 'minmax', 'abs', or 'absoff'
     1436
    12771437          INTEGER(iwp), INTENT(IN)      ::  i1                        !< internal index of min/max function
    12781438          INTEGER(iwp), INTENT(IN)      ::  i2                        !< internal index of min/max function
     
    12811441          INTEGER(iwp), INTENT(IN)      ::  k1                        !< internal index of min/max function
    12821442          INTEGER(iwp), INTENT(IN)      ::  k2                        !< internal index of min/max function
     1443
    12831444          INTEGER(iwp)                  ::  result_ijk(3)             !< grid index result of min/max function
    12841445          INTEGER(iwp), OPTIONAL        ::  result1_ijk(3)            !< optional grid index result of min/max function
    1285           REAL(wp)                      ::  offset                    !< min/max function calculates absolute value with respect to an offset
     1446
     1447          REAL(wp)                      ::  offset                    !< min/max function calculates absolute value with respect to
     1448                                                                      !< an offset
    12861449          REAL(wp)                      ::  result                    !< result of min/max function
    12871450          REAL(wp), OPTIONAL            ::  result1                   !< optional result of min/max function
     1451
    12881452          REAL(wp), INTENT(IN)          ::  array(i1:i2,j1:j2,k1:k2)  !< input array of min/max function
    12891453
     
    12971461
    12981462
    1299 !------------------------------------------------------------------------------!
     1463!--------------------------------------------------------------------------------------------------!
    13001464! Description:
    13011465! ------------
    1302 !> Interfaces for subroutines with pointer arguments called in
    1303 !> prognostic_equations.
    1304 !------------------------------------------------------------------------------!
     1466!> Interfaces for subroutines with pointer arguments called in prognostic_equations.
     1467!--------------------------------------------------------------------------------------------------!
    13051468 MODULE pointer_interfaces
    13061469
    13071470    INTERFACE
    13081471
    1309 !------------------------------------------------------------------------------!
     1472!--------------------------------------------------------------------------------------------------!
    13101473! Description:
    13111474! ------------
    13121475!> @todo Missing subroutine description.
    1313 !------------------------------------------------------------------------------!
     1476!--------------------------------------------------------------------------------------------------!
    13141477       SUBROUTINE advec_s_bc( sk, sk_char )
    13151478
     
    13291492
    13301493
    1331 !------------------------------------------------------------------------------!
     1494!--------------------------------------------------------------------------------------------------!
    13321495! Description:
    13331496! ------------
    1334 !> Definition of variables which define processor topology and the exchange of
    1335 !> ghost point layers. This module must be placed in all routines containing
    1336 !> MPI-calls.
    1337 !------------------------------------------------------------------------------!
     1497!> Definition of variables which define processor topology and the exchange of ghost point layers.
     1498!> This module must be placed in all routines containing MPI-calls.
     1499!--------------------------------------------------------------------------------------------------!
    13381500 MODULE pegrid
    13391501
     
    13491511    INTEGER(iwp) ::  comm1dx                     !< communicator for domain decomposition along x
    13501512    INTEGER(iwp) ::  comm1dy                     !< communicator for domain decomposition along y
    1351     INTEGER(iwp) ::  comm2d                      !< standard 2d (xy) communicator used in PALM for the process group the PE belongs to
     1513    INTEGER(iwp) ::  comm2d                      !< standard 2d (xy) communicator used in PALM for the process group the PE belongs
     1514                                                 !< to
    13521515    INTEGER(iwp) ::  comm_inter                  !< intercommunicator that connects atmosphere/ocean process groups
    13531516    INTEGER(iwp) ::  comm_palm                   !< internal communicator used during the MPI setup at the beginning of a run
     
    13611524    INTEGER(iwp) ::  myidy = 0                   !< id number of processor elements with same position along y-direction
    13621525    INTEGER(iwp) ::  ndim = 2                    !< dimension of the virtual PE grid
    1363     INTEGER(iwp) ::  ngp_a                       !< used in atmosphere/ocean coupling: total number of horizontal grid points (atmosphere)
    1364     INTEGER(iwp) ::  ngp_o                       !< used in atmosphere/ocean coupling: total number of horizontal grid points (ocean)
     1526    INTEGER(iwp) ::  ngp_a                       !< used in atmosphere/ocean coupling: total number of horizontal grid points
     1527                                                 !< (atmosphere)
     1528    INTEGER(iwp) ::  ngp_o                       !< used in atmosphere/ocean coupling: total number of horizontal grid points
     1529                                                 !< (ocean)
    13651530    INTEGER(iwp) ::  ngp_xy                      !< used in atmosphere/ocean coupling: number of grid points of the subdomain
    13661531    INTEGER(iwp) ::  ngp_y                       !< number of subdomain grid points along y including ghost points
     
    13741539    INTEGER(iwp) ::  psouth                      !< MPI id of north neigbour pe
    13751540    INTEGER(iwp) ::  req_count = 0               !< MPI return variable - checks if Send-Receive operation is already finished
    1376     INTEGER(iwp) ::  sendrecvcount_xy            !< number of subdomain gridpoints to be exchanged in direct transpositions (y --> x, or x --> y) or second (2d) transposition x --> y
    1377     INTEGER(iwp) ::  sendrecvcount_yz            !< number of subdomain gridpoints to be exchanged in third (2d) transposition y --> z
    1378     INTEGER(iwp) ::  sendrecvcount_zx            !< number of subdomain gridpoints to be exchanged in first (2d) transposition z --> x
     1541    INTEGER(iwp) ::  sendrecvcount_xy            !< number of subdomain gridpoints to be exchanged in direct transpositions
     1542                                                 !< (y --> x, or x --> y) or second (2d) transposition x --> y
     1543    INTEGER(iwp) ::  sendrecvcount_yz            !< number of subdomain gridpoints to be exchanged in third (2d) transposition
     1544                                                 !< y --> z
     1545    INTEGER(iwp) ::  sendrecvcount_zx            !< number of subdomain gridpoints to be exchanged in first (2d) transposition
     1546                                                 !< z --> x
    13791547    INTEGER(iwp) ::  sendrecvcount_zyd           !< number of subdomain gridpoints to be exchanged in direct transpositions z --> y (used for calculating spectra)
    1380     INTEGER(iwp) ::  target_id                   !< in atmosphere/ocean coupling: id of the ocean/atmosphere counterpart PE with whom the atmosphere/ocean PE exchanges data
     1548    INTEGER(iwp) ::  target_id                   !< in atmosphere/ocean coupling: id of the ocean/atmosphere counterpart PE with
     1549                                                 !< whom the atmosphere/ocean PE exchanges data
    13811550    INTEGER(iwp) ::  tasks_per_node = -9999      !< MPI tasks per compute node
    13821551    INTEGER(iwp) ::  threads_per_task = 1        !< number of OPENMP threads per MPI task
     
    14081577    INTEGER(iwp) ::  pcoord(2)                !< PE coordinates along x and y
    14091578    INTEGER(iwp) ::  status(MPI_STATUS_SIZE)  !< MPI status variable used in various MPI calls
     1579    INTEGER(iwp) ::  type_x_byte              !< derived MPI datatype for 2-D 8-bit integer ghost-point exchange - north / south
     1580    INTEGER(iwp) ::  type_y_byte              !< derived MPI datatype for 2-D integer ghost-point exchange - left / right
    14101581
    14111582    INTEGER(iwp), DIMENSION(MPI_STATUS_SIZE,100) ::  wait_stat  !< MPI status variable used in various MPI calls
    1412 
    1413     INTEGER(iwp) ::  type_x_byte !< derived MPI datatype for 2-D 8-bit integer ghost-point exchange - north / south
    1414     INTEGER(iwp) ::  type_y_byte !< derived MPI datatype for 2-D integer ghost-point exchange - left / right
    14151583
    14161584    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_xz      !< number of ghost points in xz-plane on different multigrid level
     
    14181586    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_yz      !< number of ghost points in yz-plane on different multigrid level
    14191587    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_yz_int  !< number of ghost points in yz-plane on different multigrid level
    1420     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_x_int  !< derived MPI datatype for 2-D integer ghost-point exchange - north / south
    1421     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_xz     !< derived MPI datatype for 3-D integer ghost-point exchange - north / south
    1422     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_xz_int !< derived MPI datatype for 3-D integer ghost-point exchange - north / south
    1423     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_y_int  !< derived MPI datatype for 2-D integer ghost-point exchange - left / right
    1424     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_yz     !< derived MPI datatype for 3-D integer ghost-point exchange - left / right
    1425     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_yz_int !< derived MPI datatype for 3-D integer ghost-point exchange - left / right
     1588    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_x_int  !< derived MPI datatype for 2-D integer ghost-point exchange - north /
     1589                                                            !< south
     1590    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_xz     !< derived MPI datatype for 3-D integer ghost-point exchange - north /
     1591                                                            !< south
     1592    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_xz_int !< derived MPI datatype for 3-D integer ghost-point exchange - north /
     1593                                                            !< south
     1594    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_y_int  !< derived MPI datatype for 2-D integer ghost-point exchange - left /
     1595                                                            !< right
     1596    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_yz     !< derived MPI datatype for 3-D integer ghost-point exchange - left /
     1597                                                            !< right
     1598    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_yz_int !< derived MPI datatype for 3-D integer ghost-point exchange - left /
     1599                                                            !< right
    14261600
    14271601    LOGICAL ::  left_border_pe  = .FALSE.  !< = .TRUE. if PE is on left border of computational domain
     
    14401614
    14411615
    1442 !------------------------------------------------------------------------------!
     1616!--------------------------------------------------------------------------------------------------!
    14431617! Description:
    14441618! ------------
    14451619!> Definition of variables which control PROFIL-output.
    1446 !------------------------------------------------------------------------------!
     1620!--------------------------------------------------------------------------------------------------!
    14471621 MODULE profil_parameter
    14481622
     
    14521626
    14531627    CHARACTER (LEN=27), DIMENSION(20) ::  cross_ts_profiles = &  !< time series to be plotted into one coordinate system, respectively
    1454                            (/ ' E E*                      ', &
    1455                               ' dt                        ', &
    1456                               ' u* w*                     ', &
    1457                               ' th*                       ', &
    1458                               ' umax vmax wmax            ', &
    1459                               ' div_old div_new           ', &
    1460                               ' zi_wtheta zi_theta        ', &
    1461                               ' w"theta"0 w"theta" wtheta ', &
    1462                               ' theta(0) theta(zp)        ', &
    1463                               ' splux spluy spluz         ', &
    1464                               ' L                         ', &
    1465                             ( '                           ', i9 = 1, 9 ) /)
     1628                                          (/ ' E E*                      ',                        &
     1629                                             ' dt                        ',                        &
     1630                                             ' u* w*                     ',                        &
     1631                                             ' th*                       ',                        &
     1632                                             ' umax vmax wmax            ',                        &
     1633                                             ' div_old div_new           ',                        &
     1634                                             ' zi_wtheta zi_theta        ',                        &
     1635                                             ' w"theta"0 w"theta" wtheta ',                        &
     1636                                             ' theta(0) theta(zp)        ',                        &
     1637                                             ' splux spluy spluz         ',                        &
     1638                                             ' L                         ',                        &
     1639                                           ( '                           ', i9 = 1, 9 ) /)
    14661640
    14671641    CHARACTER (LEN=100), DIMENSION(crmax) ::  cross_profiles = &  !< quantities to be plotted into one coordinate system, respectively
    1468                           (/ ' u v                                          ', &
    1469                              ' pt                                           ', &
    1470                              ' w"theta" w*theta* w*theta*BC wtheta wthetaBC ', &
    1471                              ' w"u" w*u* wu w"v" w*v* wv                    ', &
    1472                              ' km kh                                        ', &
    1473                              ' l                                            ', &
    1474              ( '                                              ', i9 = 1, 94 ) /)
     1642                                              (/ ' u v                                          ', &
     1643                                                 ' pt                                           ', &
     1644                                                 ' w"theta" w*theta* w*theta*BC wtheta wthetaBC ', &
     1645                                                 ' w"u" w*u* wu w"v" w*v* wv                    ', &
     1646                                                 ' km kh                                        ', &
     1647                                                 ' l                                            ', &
     1648                                 ( '                                              ', i9 = 1, 94 ) /)
    14751649
    14761650    INTEGER(iwp) ::  profile_columns = 2  !< number of coordinate systems on a profile plot per column
     
    14841658 END MODULE profil_parameter
    14851659
    1486 !------------------------------------------------------------------------------!
     1660!--------------------------------------------------------------------------------------------------!
    14871661! Description:
    14881662! ------------
    14891663!> Definition of statistical quantities, e.g. global sums.
    1490 !------------------------------------------------------------------------------!
     1664!--------------------------------------------------------------------------------------------------!
    14911665 MODULE statistics
    14921666
    14931667    USE kinds
    14941668
    1495     CHARACTER (LEN=40) ::  region(0:9) =  &  !< label for statistic region
    1496                            'total domain                            '
     1669    CHARACTER (LEN=40) ::  region(0:9) = 'total domain                            '  !< label for statistic region
    14971670
    14981671    INTEGER(iwp) ::  pr_palm = 200          !< maximum number of output profiles
     
    15121685    REAL(wp), DIMENSION(2) ::  z_i  !< inversion height
    15131686
    1514     REAL(wp), DIMENSION(:), ALLOCATABLE ::  mean_surface_level_height  !< mean surface level height for the different statistic regions
     1687    REAL(wp), DIMENSION(:), ALLOCATABLE ::  mean_surface_level_height  !< mean surface level height for the different statistic
     1688                                                                       !< regions
    15151689    REAL(wp), DIMENSION(:), ALLOCATABLE ::  sums_divnew_l              !< subdomain sum (_l) of divergence after pressure
    15161690                                                                       !< solver call (new)
    15171691    REAL(wp), DIMENSION(:), ALLOCATABLE ::  sums_divold_l              !< subdomain sum (_l) of divergence before pressure
    15181692                                                                       !< solver call (old)
     1693    REAL(wp), DIMENSION(:), ALLOCATABLE ::  weight_pres                !< substep weighting factor for pressure solver
    15191694    REAL(wp), DIMENSION(:), ALLOCATABLE ::  weight_substep             !< weighting factor for substeps in timestepping
    1520     REAL(wp), DIMENSION(:), ALLOCATABLE ::  weight_pres                !< substep weighting factor for pressure solver
    15211695
    15221696    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums             !< global sum array for the various output quantities
    1523     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_salsa_ws_l  !< subdomain sum of vertical salsa flux w's' (5th-order advection scheme only)
     1697    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_ls_l        !< subdomain sum of large scale forcing and nudging tendencies
     1698    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_salsa_ws_l  !< subdomain sum of vertical salsa flux w's'
     1699                                                               !< (5th-order advection scheme only)
     1700    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_us2_ws_l    !< subdomain sum of horizontal momentum flux u'u'
     1701                                                               !< (5th-order advection scheme only)
     1702    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_vs2_ws_l    !< subdomain sum of horizontal momentum flux v'v'
     1703                                                               !< (5th-order advection scheme only)
     1704    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_ws2_ws_l    !< subdomain sum of vertical momentum flux w'w'
     1705                                                               !< (5th-order advection scheme only)
     1706    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsncs_ws_l  !< subdomain sum of vertical clouddrop-number concentration flux
     1707                                                               !< w'nc' (5th-order advection scheme only)
     1708    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsngs_ws_l  !< subdomain sum of vertical graupel-number concentration flux w'nc' (5th-order advection scheme only)
     1709    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsnis_ws_l  !< subdomain sum of vertical ice crystal concentration flux w'ni'
     1710                                                               !< (5th-order advection scheme only)
     1711    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsnrs_ws_l  !< subdomain sum of vertical raindrop-number concentration flux w'nr'
     1712                                                               !< (5th-order advection scheme only)
     1713    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsnss_ws_l  !< subdomain sum of vertical snow-number concentration flux w'ns' (5th-order advection scheme only)
     1714    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wssas_ws_l  !< subdomain sum of vertical salinity flux w'sa'
     1715                                                               !< (5th-order advection scheme only)
     1716    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsss_ws_l   !< subdomain sum of vertical passive scalar flux w's'
     1717                                                               !< (5th-order advection scheme only)
     1718    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wspts_ws_l  !< subdomain sum of vertical sensible heat flux w'pt'
     1719                                                               !< (5th-order advection scheme only)
     1720    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsqcs_ws_l  !< subdomain sum of vertical cloudwater flux w'qc'
     1721                                                               !< (5th-order advection scheme only)
     1722    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsqgs_ws_l  !< subdomain sum of vertical graupel flux w'qg' (5th-order advection scheme only)
     1723    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsqis_ws_l  !< subdomain sum of vertical ice crystal flux w'qi'
     1724                                                               !< (5th-order advection scheme only)
     1725    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsqrs_ws_l  !< subdomain sum of vertical rainwater flux w'qr'
     1726                                                               !< (5th-order advection scheme only)
     1727    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsqss_ws_l  !< subdomain sum of vertical snow flux w'qs' (5th-order advection scheme only)
     1728    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsqs_ws_l   !< subdomain sum of vertical latent heat flux w'q'
     1729                                                               !< (5th-order advection scheme only)
    15241730    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsts_bc_l   !< subdomain sum of sensible heat flux in Bott-Chlond scheme
     1731    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsus_ws_l   !< subdomain sum of vertical momentum flux w'u'
     1732                                                               !< (5th-order advection scheme only)
     1733    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsvs_ws_l   !< subdomain sum of vertical momentum flux w'v'
     1734                                                               !< (5th-order advection scheme only)
    15251735    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ts_value         !< timeseries output array for the various output quantities
    1526     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsus_ws_l   !< subdomain sum of vertical momentum flux w'u' (5th-order advection scheme only)
    1527     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsvs_ws_l   !< subdomain sum of vertical momentum flux w'v' (5th-order advection scheme only)
    1528     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_us2_ws_l    !< subdomain sum of horizontal momentum flux u'u' (5th-order advection scheme only)
    1529     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_vs2_ws_l    !< subdomain sum of horizontal momentum flux v'v' (5th-order advection scheme only)
    1530     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_ws2_ws_l    !< subdomain sum of vertical momentum flux w'w' (5th-order advection scheme only)
    1531     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsncs_ws_l  !< subdomain sum of vertical clouddrop-number concentration flux w'nc' (5th-order advection scheme only)
    1532     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsngs_ws_l  !< subdomain sum of vertical graupel-number concentration flux w'nc' (5th-order advection scheme only)
    1533     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsnis_ws_l  !< subdomain sum of vertical ice crystal concentration flux w'ni' (5th-order advection scheme only)
    1534     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsnrs_ws_l  !< subdomain sum of vertical raindrop-number concentration flux w'nr' (5th-order advection scheme only)
    1535     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsnss_ws_l  !< subdomain sum of vertical snow-number concentration flux w'ns' (5th-order advection scheme only)
    1536     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wspts_ws_l  !< subdomain sum of vertical sensible heat flux w'pt' (5th-order advection scheme only)
    1537     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsqs_ws_l   !< subdomain sum of vertical latent heat flux w'q' (5th-order advection scheme only)
    1538     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsqcs_ws_l  !< subdomain sum of vertical cloudwater flux w'qc' (5th-order advection scheme only)
    1539     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsqgs_ws_l  !< subdomain sum of vertical graupel flux w'qg' (5th-order advection scheme only)
    1540     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsqis_ws_l  !< subdomain sum of vertical ice crystal flux w'qi' (5th-order advection scheme only)
    1541     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsqrs_ws_l  !< subdomain sum of vertical rainwater flux w'qr' (5th-order advection scheme only)
    1542     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsqss_ws_l  !< subdomain sum of vertical snow flux w'qs' (5th-order advection scheme only)
    1543     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wssas_ws_l  !< subdomain sum of vertical salinity flux w'sa' (5th-order advection scheme only)
    1544     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsss_ws_l   !< subdomain sum of vertical passive scalar flux w's' (5th-order advection scheme only)
    1545     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_ls_l        !< subdomain sum of large scale forcing and nudging tendencies
    15461736
    15471737    REAL(wp), DIMENSION(:,:), POINTER     ::  sums_wschs_ws_l  !< subdomain sum of vertical chemistry flux w'ch'
     
    15601750
    15611751
    1562 !------------------------------------------------------------------------------!
     1752!--------------------------------------------------------------------------------------------------!
    15631753! Description:
    15641754! ------------
    15651755!> Definition of indices for transposed arrays.
    1566 !------------------------------------------------------------------------------!
     1756!--------------------------------------------------------------------------------------------------!
    15671757 MODULE transpose_indices
    15681758
Note: See TracChangeset for help on using the changeset viewer.