Ignore:
Timestamp:
Dec 14, 2017 5:12:51 PM (7 years ago)
Author:
kanani
Message:

Merge of branch palm4u into trunk

Location:
palm/trunk
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk

  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/modules.f90

    r2669 r2696  
    11!> @file modules.f90
    22!------------------------------------------------------------------------------!
    3 ! This file is part of PALM.
     3! This file is part of the PALM model system.
    44!
    55! PALM is free software: you can redistribute it and/or modify it under the
     
    2525! -----------------
    2626! $Id$
     27! Implementation of uv exposure model (FK)
     28! + turbulence closure variables (control_parameters)
     29! + arrays for prognostic equation of disspiation (arrays_3d)
     30! + km_av, kh_av (TG)
     31! Implementation of chemistry module (FK)
     32! -lod
     33! +topo_distinct (MS)
     34!
     35! 2669 2017-12-06 16:03:27Z raasch
    2736! CONTIGUOUS-attribut added to 3d pointer arrays,
    2837! coupling_char extended to LEN=8
     
    601610    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  c_v                   !< phase speed of v-velocity component
    602611    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  c_w                   !< phase speed of w-velocity component
     612    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_diss           !< artificial numerical dissipation flux at south face of grid box - TKE dissipation
    603613    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_e              !< artificial numerical dissipation flux at south face of grid box - subgrid-scale TKE
    604614    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_nc             !< artificial numerical dissipation flux at south face of grid box - clouddrop-number concentration   
     
    615625    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  dzu_mg                !< vertical grid size (u-grid) for multigrid pressure solver
    616626    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  dzw_mg                !< vertical grid size (w-grid) for multigrid pressure solver
     627    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_diss           !< 6th-order advective flux at south face of grid box - TKE dissipation
    617628    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_e              !< 6th-order advective flux at south face of grid box - subgrid-scale TKE
    618629    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_nc             !< 6th-order advective flux at south face of grid box - clouddrop-number concentration
     
    638649    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  total_2d_o            !< horizontal array to store the total domain data, used for atmosphere-ocean coupling (ocean data)
    639650   
    640     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  d          !< divergence
    641     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  de_dx      !< gradient of sgs tke in x-direction (lpm)
    642     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  de_dy      !< gradient of sgs tke in y-direction (lpm)
    643     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  de_dz      !< gradient of sgs tke in z-direction (lpm)
    644     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss       !< TKE dissipation rate
    645     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_e   !< artificial numerical dissipation flux at left face of grid box - subgrid-scale TKE
    646     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_nc  !< artificial numerical dissipation flux at left face of grid box - clouddrop-number concentration
    647     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_nr  !< artificial numerical dissipation flux at left face of grid box - raindrop-number concentration
    648     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_pt  !< artificial numerical dissipation flux at left face of grid box - potential temperature
    649     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_q   !< artificial numerical dissipation flux at left face of grid box - mixing ratio
    650     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_qc  !< artificial numerical dissipation flux at left face of grid box - cloudwater
    651     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_qr  !< artificial numerical dissipation flux at left face of grid box - rainwater
    652     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_s   !< artificial numerical dissipation flux at left face of grid box - passive scalar
    653     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_sa  !< artificial numerical dissipation flux at left face of grid box - salinity
    654     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_u   !< artificial numerical dissipation flux at left face of grid box - u-component
    655     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_v   !< artificial numerical dissipation flux at left face of grid box - v-component
    656     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_w   !< artificial numerical dissipation flux at left face of grid box - w-component
    657     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_e   !< 6th-order advective flux at south face of grid box - subgrid-scale TKE
    658     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_nc  !< 6th-order advective flux at south face of grid box - clouddrop-number concentration
    659     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_nr  !< 6th-order advective flux at south face of grid box - raindrop-number concentration
    660     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_pt  !< 6th-order advective flux at south face of grid box - potential temperature
    661     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_q   !< 6th-order advective flux at south face of grid box - mixing ratio
    662     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_qc  !< 6th-order advective flux at south face of grid box - cloudwater
    663     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_qr  !< 6th-order advective flux at south face of grid box - rainwater
    664     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_s   !< 6th-order advective flux at south face of grid box - passive scalar
    665     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_sa  !< 6th-order advective flux at south face of grid box - salinity
    666     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_u   !< 6th-order advective flux at south face of grid box - u-component
    667     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_v   !< 6th-order advective flux at south face of grid box - v-component
    668     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_w   !< 6th-order advective flux at south face of grid box - w-component
    669     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  kh         !< eddy diffusivity for heat
    670     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  km         !< eddy diffusivity for momentum
    671     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  l_wall     !< near-wall mixing length
    672     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  prr        !< rain rate
    673     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  p_loc      !< local array in multigrid/sor solver containing the pressure which is iteratively advanced in each iteration step
    674     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tend       !< tendency field (time integration)
    675     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tric       !< coefficients of the tridiagonal matrix for solution of the Poisson equation in Fourier space
    676     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_l      !< velocity data (u at left boundary) from time level t-dt required for radiation boundary condition
    677     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_n      !< velocity data (u at north boundary) from time level t-dt required for radiation boundary condition
    678     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_r      !< velocity data (u at right boundary) from time level t-dt required for radiation boundary condition
    679     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_s      !< velocity data (u at south boundary) from time level t-dt required for radiation boundary condition
    680     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_l      !< velocity data (v at left boundary) from time level t-dt required for radiation boundary condition
    681     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_n      !< velocity data (v at north boundary) from time level t-dt required for radiation boundary condition
    682     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_r      !< velocity data (v at right boundary) from time level t-dt required for radiation boundary condition
    683     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_s      !< velocity data (v at south boundary) from time level t-dt required for radiation boundary condition
    684     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_l      !< velocity data (w at left boundary) from time level t-dt required for radiation boundary condition
    685     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_n      !< velocity data (w at north boundary) from time level t-dt required for radiation boundary condition
    686     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_r      !< velocity data (w at right boundary) from time level t-dt required for radiation boundary condition
    687     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_s      !< velocity data (w at south boundary) from time level t-dt required for radiation boundary condition
     651    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  d           !< divergence
     652    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  de_dx       !< gradient of sgs tke in x-direction (lpm)
     653    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  de_dy       !< gradient of sgs tke in y-direction (lpm)
     654    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  de_dz       !< gradient of sgs tke in z-direction (lpm)
     655    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_diss !< artificial numerical dissipation flux at left face of grid box - TKE dissipation
     656    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_e    !< artificial numerical dissipation flux at left face of grid box - subgrid-scale TKE
     657    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_nc   !< artificial numerical dissipation flux at left face of grid box - clouddrop-number concentration
     658    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_nr   !< artificial numerical dissipation flux at left face of grid box - raindrop-number concentration
     659    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_pt   !< artificial numerical dissipation flux at left face of grid box - potential temperature
     660    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_q    !< artificial numerical dissipation flux at left face of grid box - mixing ratio
     661    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_qc   !< artificial numerical dissipation flux at left face of grid box - cloudwater
     662    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_qr   !< artificial numerical dissipation flux at left face of grid box - rainwater
     663    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_s    !< artificial numerical dissipation flux at left face of grid box - passive scalar
     664    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_sa   !< artificial numerical dissipation flux at left face of grid box - salinity
     665    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_u    !< artificial numerical dissipation flux at left face of grid box - u-component
     666    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_v    !< artificial numerical dissipation flux at left face of grid box - v-component
     667    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  diss_l_w    !< artificial numerical dissipation flux at left face of grid box - w-component
     668    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_diss !< 6th-order advective flux at south face of grid box - TKE dissipation
     669    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_e    !< 6th-order advective flux at south face of grid box - subgrid-scale TKE
     670    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_nc   !< 6th-order advective flux at south face of grid box - clouddrop-number concentration
     671    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_nr   !< 6th-order advective flux at south face of grid box - raindrop-number concentration
     672    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_pt   !< 6th-order advective flux at south face of grid box - potential temperature
     673    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_q    !< 6th-order advective flux at south face of grid box - mixing ratio
     674    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_qc   !< 6th-order advective flux at south face of grid box - cloudwater
     675    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_qr   !< 6th-order advective flux at south face of grid box - rainwater
     676    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_s    !< 6th-order advective flux at south face of grid box - passive scalar
     677    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_sa   !< 6th-order advective flux at south face of grid box - salinity
     678    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_u    !< 6th-order advective flux at south face of grid box - u-component
     679    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_v    !< 6th-order advective flux at south face of grid box - v-component
     680    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_w    !< 6th-order advective flux at south face of grid box - w-component
     681    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  kh          !< eddy diffusivity for heat
     682    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  km          !< eddy diffusivity for momentum
     683    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  l_wall      !< near-wall mixing length
     684    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  prr         !< rain rate
     685    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  p_loc       !< local array in multigrid/sor solver containing the pressure which is iteratively advanced in each iteration step
     686    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tend        !< tendency field (time integration)
     687    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tric        !< coefficients of the tridiagonal matrix for solution of the Poisson equation in Fourier space
     688    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_l       !< velocity data (u at left boundary) from time level t-dt required for radiation boundary condition
     689    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_n       !< velocity data (u at north boundary) from time level t-dt required for radiation boundary condition
     690    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_r       !< velocity data (u at right boundary) from time level t-dt required for radiation boundary condition
     691    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_s       !< velocity data (u at south boundary) from time level t-dt required for radiation boundary condition
     692    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_l       !< velocity data (v at left boundary) from time level t-dt required for radiation boundary condition
     693    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_n       !< velocity data (v at north boundary) from time level t-dt required for radiation boundary condition
     694    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_r       !< velocity data (v at right boundary) from time level t-dt required for radiation boundary condition
     695    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_s       !< velocity data (v at south boundary) from time level t-dt required for radiation boundary condition
     696    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_l       !< velocity data (w at left boundary) from time level t-dt required for radiation boundary condition
     697    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_n       !< velocity data (w at north boundary) from time level t-dt required for radiation boundary condition
     698    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_r       !< velocity data (w at right boundary) from time level t-dt required for radiation boundary condition
     699    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_s       !< velocity data (w at south boundary) from time level t-dt required for radiation boundary condition
    688700
    689701#if defined( __nopointer )
     702    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  diss       !< TKE dissipation
     703    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  diss_p     !< prognostic value TKE dissipation
    690704    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  e          !< subgrid-scale turbulence kinetic energy (sgs tke)
    691705    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  e_p        !< prognostic value of sgs tke
     
    715729    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  sa         !< ocean salinity
    716730    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  sa_p       !< prognostic value of ocean salinity
     731    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  tdiss_m    !< weighted tendency of diss for previous sub-timestep (Runge-Kutta)
    717732    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  te_m       !< weighted tendency of e for previous sub-timestep (Runge-Kutta)
    718733    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  tnc_m      !< weighted tendency of nc for previous sub-timestep (Runge-Kutta)
     
    735750    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  w_p        !< prognostic value of w
    736751#else
     752    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  diss_1  !< pointer for swapping of timelevels for respective quantity
     753    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  diss_2  !< pointer for swapping of timelevels for respective quantity
     754    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  diss_3  !< pointer for swapping of timelevels for respective quantity
    737755    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  e_1     !< pointer for swapping of timelevels for respective quantity
    738756    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  e_2     !< pointer for swapping of timelevels for respective quantity
     
    780798    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  w_3     !< pointer for swapping of timelevels for respective quantity
    781799
     800    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  diss       !< pointer: TKE dissipation
     801    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  diss_p     !< pointer: prognostic value of TKE dissipation
    782802    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  e          !< pointer: subgrid-scale turbulence kinetic energy (sgs tke)
    783803    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  e_p        !< pointer: prognostic value of sgs tke
     
    803823    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  sa         !< pointer: ocean salinity
    804824    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  sa_p       !< pointer: prognostic value of ocean salinity
     825    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tdiss_m    !< pointer: weighted tendency of diss for previous sub-timestep (Runge-Kutta)
    805826    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  te_m       !< pointer: weighted tendency of e for previous sub-timestep (Runge-Kutta)
    806827    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tnc_m      !< pointer: weighted tendency of nc for previous sub-timestep (Runge-Kutta)
     
    867888    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  z0q_av                 !< avg. roughness length for moisture
    868889
     890    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  diss_av       !< avg. tke dissipation rate
    869891    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  e_av          !< avg. subgrid-scale tke
     892    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  kh_av         !< avg. eddy diffusivity for heat
     893    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  km_av         !< avg. eddy diffusivity for momentum
    870894    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  lpt_av        !< avg. liquid water potential temperature
    871895    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nc_av         !< avg. cloud drop number density
     
    10181042    CHARACTER (LEN=20)   ::  reference_state = 'initial_profile'          !< namelist parameter 
    10191043    CHARACTER (LEN=20)   ::  timestep_scheme = 'runge-kutta-3'            !< namelist parameter       
     1044    CHARACTER (LEN=20)   ::  turbulence_closure = 'Moeng_Wyngaard'        !< namelist parameter
    10201045    CHARACTER (LEN=40)   ::  topography = 'flat'                          !< namelist parameter
    10211046    CHARACTER (LEN=64)   ::  host = '????'                                !< hostname on which PALM is running, ENVPAR namelist parameter provided by mrun
     
    10861111    INTEGER(iwp) ::  io_blocks = 1                     !< number of blocks for which I/O is done in sequence (total number of PEs / maximum_parallel_io_streams)
    10871112    INTEGER(iwp) ::  iran = -1234567                   !< integer random number used for flow disturbances
    1088     INTEGER(iwp) ::  lod = 1                           !< level of detail, topography input parameter
    10891113    INTEGER(iwp) ::  masks = 0                         !< counter for number of masked output quantities
    10901114    INTEGER(iwp) ::  maximum_grid_level                !< number of grid levels that the multigrid solver is using
     
    11571181    LOGICAL ::  aerosol_c3h4o4 =.FALSE.                      !< malonic acid aerosol for bulk scheme
    11581182    LOGICAL ::  aerosol_nh4no3 =.FALSE.                      !< malonic acid aerosol for bulk scheme
     1183    LOGICAL ::  air_chemistry = .FALSE.                      !< chemistry model switch
    11591184    LOGICAL ::  bc_lr_cyc =.TRUE.                            !< left-right boundary condition cyclic?
    11601185    LOGICAL ::  bc_lr_dirrad = .FALSE.                       !< left-right boundary condition dirichlet/radiation?
     
    11931218    LOGICAL ::  first_call_lpm = .TRUE.                      !< call lpm only once per timestep?
    11941219    LOGICAL ::  force_print_header = .FALSE.                 !< namelist parameter
     1220    LOGICAL ::  force_bound_l = .FALSE.                      !< flag indicating domain boundary on left side to set forcing boundary conditions
     1221    LOGICAL ::  force_bound_n = .FALSE.                      !< flag indicating domain boundary on north side to set forcing boundary conditions
     1222    LOGICAL ::  force_bound_r = .FALSE.                      !< flag indicating domain boundary on right side to set forcing boundary conditions
     1223    LOGICAL ::  force_bound_s = .FALSE.                      !< flag indicating domain boundary on south side to set forcing boundary conditions
     1224    LOGICAL ::  forcing = .FALSE.                            !< flag controlling forcing from large-scale model     
    11951225    LOGICAL ::  galilei_transformation = .FALSE.             !< namelist parameter
    11961226    LOGICAL ::  humidity = .FALSE.                           !< namelist parameter
     
    12031233    LOGICAL ::  large_scale_subsidence = .FALSE.             !< namelist parameter
    12041234    LOGICAL ::  land_surface = .FALSE.                       !< use land surface model?
     1235    LOGICAL ::  les_mw = .FALSE.                             !< use Moeng-Wyngaard turbulence closure for LES mode
    12051236    LOGICAL ::  lsf_exception = .FALSE.                      !< use of lsf with buildings (temporary)?
    12061237    LOGICAL ::  lsf_surf = .TRUE.                            !< use surface forcing (large scale forcing)?
     
    12121243    LOGICAL ::  microphysics_seifert = .FALSE.               !< use 2-moment Seifert and Beheng scheme
    12131244    LOGICAL ::  mg_switch_to_pe0 = .FALSE.                   !< internal multigrid switch for steering the ghost point exchange in case that data has been collected on PE0
    1214     LOGICAL ::  nest_bound_l = .FALSE.                       !< nested boundary on left side?
    1215     LOGICAL ::  nest_bound_n = .FALSE.                       !< nested boundary on north side?
    1216     LOGICAL ::  nest_bound_r = .FALSE.                       !< nested boundary on right side?
    1217     LOGICAL ::  nest_bound_s = .FALSE.                       !< nested boundary on south side?
     1245    LOGICAL ::  nest_bound_l = .FALSE.                       !< flag indicating nested domain boundary on left side
     1246    LOGICAL ::  nest_bound_n = .FALSE.                       !< flag indicating nested domain boundary on north side
     1247    LOGICAL ::  nest_bound_r = .FALSE.                       !< flag indicating nested domain boundary on right side
     1248    LOGICAL ::  nest_bound_s = .FALSE.                       !< flag indicating nested domain boundary on south side
    12181249    LOGICAL ::  nest_domain  = .FALSE.                       !< domain is nested into a parent domain?
    12191250    LOGICAL ::  neutral = .FALSE.                            !< namelist parameter
     
    12271258    LOGICAL ::  precipitation = .FALSE.                      !< namelist parameter
    12281259    LOGICAL ::  random_heatflux = .FALSE.                    !< namelist parameter
     1260    LOGICAL ::  rans_mode = .FALSE.                          !< switch between RANS and LES mode
     1261    LOGICAL ::  rans_tke_e = .FALSE.                         !< use TKE-e turbulence closure for RANS mode
     1262    LOGICAL ::  rans_tke_l = .FALSE.                         !< use TKE-l turbulence closure for RANS mode
    12291263    LOGICAL ::  recycling_yshift = .FALSE.                   !< namelist parameter
    12301264    LOGICAL ::  run_control_header = .FALSE.                 !< onetime output of RUN_CONTROL header
     
    12371271    LOGICAL ::  synthetic_turbulence_generator = .FALSE.     !< flag for synthetic turbulence generator module
    12381272    LOGICAL ::  terminate_run = .FALSE.                      !< terminate run (cpu-time limit, restarts)?
     1273    LOGICAL ::  topo_no_distinct = .FALSE.                   !< flag controlling classification of topography surfaces
    12391274    LOGICAL ::  transpose_compute_overlap = .FALSE.          !< namelist parameter
    12401275    LOGICAL ::  turbulent_inflow = .FALSE.                   !< namelist parameter
     
    12511286    LOGICAL ::  use_ug_for_galilei_tr = .TRUE.               !< namelist parameter
    12521287    LOGICAL ::  use_upstream_for_tke = .FALSE.               !< namelist parameter
     1288    LOGICAL ::  uv_exposure = .FALSE.                        !< switch for uv exposure model
    12531289    LOGICAL ::  virtual_flight = .FALSE.                     !< use virtual flight model?
    12541290    LOGICAL ::  wall_adjustment = .TRUE.                     !< namelist parameter
     
    18651901    INTEGER(iwp), DIMENSION(MPI_STATUS_SIZE,100) ::  wait_stat  !< MPI status variable used in various MPI calls
    18661902   
    1867     INTEGER(iwp) ::  ngp_yz_int   !< number of ghost points in yz-plane
    1868     INTEGER(iwp) ::  type_xz_int  !< derived MPI datatype for 3-D integer ghost-point exchange - north / south
    1869     INTEGER(iwp) ::  type_yz_int  !< derived MPI datatype for 3-D integer ghost-point exchange - left / right
    1870 
    18711903    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_xz      !< number of ghost points in xz-plane on different multigrid level
     1904    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_xz_int  !< number of ghost points in xz-plane on different multigrid level
    18721905    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_yz      !< number of ghost points in yz-plane on different multigrid level
     1906    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_yz_int  !< number of ghost points in yz-plane on different multigrid level
    18731907    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_x_int  !< derived MPI datatype for 2-D integer ghost-point exchange - north / south
    18741908    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_xz     !< derived MPI datatype for 3-D integer ghost-point exchange - north / south
     1909    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_xz_int !< derived MPI datatype for 3-D integer ghost-point exchange - north / south
    18751910    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_y_int  !< derived MPI datatype for 2-D integer ghost-point exchange - left / right
    18761911    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_yz     !< derived MPI datatype for 3-D integer ghost-point exchange - left / right
     1912    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_yz_int !< derived MPI datatype for 3-D integer ghost-point exchange - left / right
    18771913
    18781914    LOGICAL ::  left_border_pe  = .FALSE.  !< = .TRUE. if PE is on left border of computational domain
Note: See TracChangeset for help on using the changeset viewer.