Ignore:
Timestamp:
Mar 24, 2020 12:21:00 PM (4 years ago)
Author:
Giersch
Message:

Profile output of the Kolmogorov length scale added

File:
1 edited

Legend:

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

    r4461 r4472  
    2525! -----------------
    2626! $Id$
     27! Additional switch added to activate calculations in flow_statistics for the
     28! kolmogorov length scale
     29!
     30! 4461 2020-03-12 16:51:59Z raasch
    2731! +virtual_pe_grid, communicator_configurations
    28 ! 
     32!
    2933! 4414 2020-02-19 20:16:04Z suehring
    30 ! - nzb_diff_s_inner, nzb_diff_s_outer, nzb_inner,nzb_outer, nzb_s_inner, 
    31 !   nzb_s_outer, nzb_u_inner, nzb_u_outer, nzb_v_inner, nzb_v_outer, 
     34! - nzb_diff_s_inner, nzb_diff_s_outer, nzb_inner,nzb_outer, nzb_s_inner,
     35!   nzb_s_outer, nzb_u_inner, nzb_u_outer, nzb_v_inner, nzb_v_outer,
    3236!   nzb_w_inner, nzb_w_outer
    3337!
    34 ! 
     38!
    3539! 4360 2020-01-07 11:25:50Z suehring
    3640! Introduction of wall_flags_total_0, which currently sets bits based on static
    3741! topography information used in wall_flags_static_0
    38 ! 
     42!
    3943! 4340 2019-12-16 08:17:03Z Giersch
    4044! Flag for topography closed channel flow with symmetric boundaries introduced
    41 ! 
     45!
    4246! 4331 2019-12-10 18:25:02Z suehring
    4347! - do_output_at_2m, pt_2m_av
    44 ! 
     48!
    4549! 4329 2019-12-10 15:46:36Z motisi
    4650! Renamed wall_flags_0 to wall_flags_static_0
    47 ! 
     51!
    4852! 4301 2019-11-22 12:09:09Z oliver.maas
    4953! removed recycling_yshift
    50 ! 
     54!
    5155! 4297 2019-11-21 10:37:50Z oliver.maas
    5256! changed variable type of recycling_yshift from LOGICAL to INTEGER
    53 ! 
     57!
    5458! 4293 2019-11-12 14:44:01Z Giersch
    5559! Add origin_date_time
    56 ! 
     60!
    5761! 4146 2019-08-07 07:47:36Z gronemeier
    5862! Added rotation_angle
    59 ! 
     63!
    6064! 4184 2019-08-23 08:07:40Z oliver.maas
    61 ! changed allocated length of recycling_method_for_thermodynamic_quantities 
     65! changed allocated length of recycling_method_for_thermodynamic_quantities
    6266! from 20 to 80 characters
    63 ! 
     67!
    6468! 4183 2019-08-23 07:33:16Z oliver.maas
    6569! removed recycle_absolute_quantities and raq
    6670! added recycling_method_for_thermodynamic_quantities
    67 ! 
     71!
    6872! 4182 2019-08-22 15:20:23Z scharf
    6973! Corrected "Former revisions" section
    70 ! 
     74!
    7175! 4173 2019-08-20 12:04:06Z gronemeier
    7276! add vdi_internal_controls
    73 ! 
     77!
    7478! 4172 2019-08-20 11:55:33Z oliver.maas
    7579! added recycle_absolute_quantities and raq
    76 ! 
     80!
    7781! 4168 2019-08-16 13:50:17Z suehring
    7882! +topo_top_ind
    79 ! 
     83!
    8084! 4131 2019-08-02 11:06:18Z monakurppa
    8185! Add max_pr_salsa to control_parameters. Used in creating profile output for
    8286! salsa.
    83 ! 
     87!
    8488! 4110 2019-07-22 17:05:21Z suehring
    8589! -advc_flags_1, advc_flags_2
    8690! +advc_flags_m, advc_flags_s
    87 ! 
     91!
    8892! 4109 2019-07-22 17:00:34Z suehring
    8993! remove old_dt
    90 ! 
     94!
    9195! 4079 2019-07-09 18:04:41Z suehring
    9296! + monotonic_limiter_z
    93 ! 
     97!
    9498! 4069 2019-07-01 14:05:51Z Giersch
    95 ! Masked output running index mid has been introduced as a local variable to 
     99! Masked output running index mid has been introduced as a local variable to
    96100! avoid runtime error (Loop variable has been modified) in time_integration
    97 ! 
     101!
    98102! 4017 2019-06-06 12:16:46Z schwenkel
    99103! increase maximum number of virtual flights
    100 ! 
     104!
    101105! 3987 2019-05-22 09:52:13Z kanani
    102106! Introduce alternative switch for debug output during timestepping
    103 ! 
     107!
    104108! 3885 2019-04-11 11:29:34Z kanani
    105 ! Changes related to global restructuring of location messages and introduction 
     109! Changes related to global restructuring of location messages and introduction
    106110! of additional debug messages
    107 ! 
     111!
    108112! 3871 2019-04-08 14:38:39Z knoop
    109113! Initialized parameter region
    110 ! 
     114!
    111115! 3746 2019-02-16 12:41:27Z gronemeier
    112116! Removed most_method
    113 ! 
     117!
    114118! 3648 2019-01-02 16:35:46Z suehring
    115119! -surface_data_output +surface_output
     
    128132!------------------------------------------------------------------------------!
    129133 MODULE advection
    130  
     134
    131135    USE kinds
    132136
     
    135139    REAL(wp), DIMENSION(:), ALLOCATABLE ::  dex  !< exponential coefficient for the Bott-Chlond advection scheme
    136140    REAL(wp), DIMENSION(:), ALLOCATABLE ::  eex  !< exponential coefficient for the Bott-Chlond advection scheme
    137    
     141
    138142    SAVE
    139143
     
    150154!------------------------------------------------------------------------------!
    151155 MODULE mas_global_attributes
    152  
     156
    153157    USE kinds
    154158
     
    175179    REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_w_m                  !< mean phase velocity at outflow for w-component used in radiation boundary condition
    176180    REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_w_m_l                !< mean phase velocity at outflow for w-component used in radiation boundary condition (local subdomain value)
    177     REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddzu                   !< 1/dzu 
    178     REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddzu_pres              !< modified ddzu for pressure solver 
    179     REAL(wp), DIMENSION(:), ALLOCATABLE ::  dd2zu                  !< 1/(dzu(k)+dzu(k+1)) 
    180     REAL(wp), DIMENSION(:), ALLOCATABLE ::  dzu                    !< vertical grid size (u-grid) 
    181     REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddzw                   !< 1/dzw 
    182     REAL(wp), DIMENSION(:), ALLOCATABLE ::  dzw                    !< vertical grid size (w-grid) 
    183     REAL(wp), DIMENSION(:), ALLOCATABLE ::  hyp                    !< hydrostatic pressure 
    184     REAL(wp), DIMENSION(:), ALLOCATABLE ::  inflow_damping_factor  !< used for turbulent inflow (non-cyclic boundary conditions) 
    185     REAL(wp), DIMENSION(:), ALLOCATABLE ::  ptdf_x                 !< damping factor for potential temperature in x-direction 
    186     REAL(wp), DIMENSION(:), ALLOCATABLE ::  ptdf_y                 !< damping factor for potential temperature in y-direction 
    187     REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt_init                !< initial profile of potential temperature 
    188     REAL(wp), DIMENSION(:), ALLOCATABLE ::  q_init                 !< initial profile of total water mixing ratio 
    189                                                                    !< (or total water content with active cloud physics) 
    190     REAL(wp), DIMENSION(:), ALLOCATABLE ::  rdf                    !< rayleigh damping factor for velocity components 
    191     REAL(wp), DIMENSION(:), ALLOCATABLE ::  rdf_sc                 !< rayleigh damping factor for scalar quantities 
    192     REAL(wp), DIMENSION(:), ALLOCATABLE ::  ref_state              !< reference state of potential temperature 
     181    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddzu                   !< 1/dzu
     182    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddzu_pres              !< modified ddzu for pressure solver
     183    REAL(wp), DIMENSION(:), ALLOCATABLE ::  dd2zu                  !< 1/(dzu(k)+dzu(k+1))
     184    REAL(wp), DIMENSION(:), ALLOCATABLE ::  dzu                    !< vertical grid size (u-grid)
     185    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddzw                   !< 1/dzw
     186    REAL(wp), DIMENSION(:), ALLOCATABLE ::  dzw                    !< vertical grid size (w-grid)
     187    REAL(wp), DIMENSION(:), ALLOCATABLE ::  hyp                    !< hydrostatic pressure
     188    REAL(wp), DIMENSION(:), ALLOCATABLE ::  inflow_damping_factor  !< used for turbulent inflow (non-cyclic boundary conditions)
     189    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ptdf_x                 !< damping factor for potential temperature in x-direction
     190    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ptdf_y                 !< damping factor for potential temperature in y-direction
     191    REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt_init                !< initial profile of potential temperature
     192    REAL(wp), DIMENSION(:), ALLOCATABLE ::  q_init                 !< initial profile of total water mixing ratio
     193                                                                   !< (or total water content with active cloud physics)
     194    REAL(wp), DIMENSION(:), ALLOCATABLE ::  rdf                    !< rayleigh damping factor for velocity components
     195    REAL(wp), DIMENSION(:), ALLOCATABLE ::  rdf_sc                 !< rayleigh damping factor for scalar quantities
     196    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ref_state              !< reference state of potential temperature
    193197                                                                   !< (and density in case of ocean simulation)
    194198    REAL(wp), DIMENSION(:), ALLOCATABLE ::  s_init                 !< initial profile of passive scalar concentration
     
    215219    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_diss           !< artificial numerical dissipation flux at south face of grid box - TKE dissipation
    216220    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_e              !< artificial numerical dissipation flux at south face of grid box - subgrid-scale TKE
    217     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_nc             !< artificial numerical dissipation flux at south face of grid box - clouddrop-number concentration   
    218     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_nr             !< artificial numerical dissipation flux at south face of grid box - raindrop-number concentration   
    219     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_pt             !< artificial numerical dissipation flux at south face of grid box - potential temperature 
    220     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_q              !< artificial numerical dissipation flux at south face of grid box - mixing ratio 
    221     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_qc             !< artificial numerical dissipation flux at south face of grid box - cloudwater 
    222     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_qr             !< artificial numerical dissipation flux at south face of grid box - rainwater 
     221    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_nc             !< artificial numerical dissipation flux at south face of grid box - clouddrop-number concentration
     222    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_nr             !< artificial numerical dissipation flux at south face of grid box - raindrop-number concentration
     223    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_pt             !< artificial numerical dissipation flux at south face of grid box - potential temperature
     224    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_q              !< artificial numerical dissipation flux at south face of grid box - mixing ratio
     225    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_qc             !< artificial numerical dissipation flux at south face of grid box - cloudwater
     226    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_qr             !< artificial numerical dissipation flux at south face of grid box - rainwater
    223227    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_s              !< artificial numerical dissipation flux at south face of grid box - passive scalar
    224228    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  diss_s_sa             !< artificial numerical dissipation flux at south face of grid box - salinity
     
    230234    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_diss           !< 6th-order advective flux at south face of grid box - TKE dissipation
    231235    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_e              !< 6th-order advective flux at south face of grid box - subgrid-scale TKE
    232     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_nc             !< 6th-order advective flux at south face of grid box - clouddrop-number concentration 
    233     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_nr             !< 6th-order advective flux at south face of grid box - raindrop-number concentration 
    234     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_pt             !< 6th-order advective flux at south face of grid box - potential temperature 
    235     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_q              !< 6th-order advective flux at south face of grid box - mixing ratio 
     236    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_nc             !< 6th-order advective flux at south face of grid box - clouddrop-number concentration
     237    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_nr             !< 6th-order advective flux at south face of grid box - raindrop-number concentration
     238    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_pt             !< 6th-order advective flux at south face of grid box - potential temperature
     239    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_q              !< 6th-order advective flux at south face of grid box - mixing ratio
    236240    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_qc             !< 6th-order advective flux at south face of grid box - cloudwater
    237241    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  flux_s_qr             !< 6th-order advective flux at south face of grid box - rainwater
     
    246250    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  mean_inflow_profiles  !< used for turbulent inflow (non-cyclic boundary conditions)
    247251    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  precipitation_amount  !< precipitation amount due to gravitational settling (bulk microphysics)
    248     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pt_slope_ref          !< potential temperature in rotated coordinate system 
    249                                                                     !< (in case of sloped surface) 
     252    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  pt_slope_ref          !< potential temperature in rotated coordinate system
     253                                                                    !< (in case of sloped surface)
    250254    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  total_2d_a            !< horizontal array to store the total domain data, used for atmosphere-ocean coupling (atmosphere data)
    251255    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  total_2d_o            !< horizontal array to store the total domain data, used for atmosphere-ocean coupling (ocean data)
    252    
     256
    253257    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  d           !< divergence
    254258    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  de_dx       !< gradient of sgs tke in x-direction (lpm)
     
    281285    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_v    !< 6th-order advective flux at south face of grid box - v-component
    282286    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  flux_l_w    !< 6th-order advective flux at south face of grid box - w-component
    283     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  kh  !< eddy diffusivity for heat 
     287    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  kh  !< eddy diffusivity for heat
    284288    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  km  !< eddy diffusivity for momentum
    285289    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  prr         !< rain rate
     
    309313    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  prho_1  !< pointer for swapping of timelevels for respective quantity
    310314    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nc_1    !< pointer for swapping of timelevels for respective quantity
    311     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nc_2    !< pointer for swapping of timelevels for respective quantity 
     315    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nc_2    !< pointer for swapping of timelevels for respective quantity
    312316    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nc_3    !< pointer for swapping of timelevels for respective quantity
    313317    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nr_1    !< pointer for swapping of timelevels for respective quantity
    314     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nr_2    !< pointer for swapping of timelevels for respective quantity 
     318    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nr_2    !< pointer for swapping of timelevels for respective quantity
    315319    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  nr_3    !< pointer for swapping of timelevels for respective quantity
    316320    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  pt_1    !< pointer for swapping of timelevels for respective quantity
     
    426430!------------------------------------------------------------------------------!
    427431 MODULE averaging
    428  
     432
    429433    USE kinds
    430434
     
    458462                                                                      !< (or total water content with active cloud physics)
    459463    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  qc_av         !< avg. cloud water content
    460     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_av         !< avg. liquid water content 
    461     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_c_av       !< avg. change in liquid water content due to 
     464    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_av         !< avg. liquid water content
     465    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_c_av       !< avg. change in liquid water content due to
    462466                                                                      !< condensation/evaporation during last time step
    463467    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  ql_v_av       !< avg. volume of liquid water
     
    468472    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  s_av          !< avg. passive scalar
    469473    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  sa_av         !< avg. salinity
    470     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  u_av          !< avg. horizontal velocity component u 
     474    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  u_av          !< avg. horizontal velocity component u
    471475    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  v_av          !< avg. horizontal velocity component v
    472476    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  vpt_av        !< avg. virtual potential temperature
    473477    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  w_av          !< avg. vertical velocity component
    474  
     478
    475479 END MODULE averaging
    476480
    477  
     481
    478482!------------------------------------------------------------------------------!
    479483! Description:
     
    489493       LOGICAL ::  opened_before  !< file is currently closed, but has been openend before
    490494    END TYPE file_status
    491    
     495
    492496    INTEGER, PARAMETER      ::  mask_xyz_dimension = 100  !< limit of mask dimensions (100 points in each direction)
    493497    INTEGER, PARAMETER      ::  max_masks = 50            !< maximum number of masks
     
    532536    CHARACTER (LEN=20)   ::  bc_uv_b = 'dirichlet'                        !< namelist parameter
    533537    CHARACTER (LEN=20)   ::  bc_uv_t = 'dirichlet'                        !< namelist parameter
    534     CHARACTER (LEN=20)   ::  coupling_mode = 'uncoupled'                  !< coupling mode for atmosphere-ocean coupling 
     538    CHARACTER (LEN=20)   ::  coupling_mode = 'uncoupled'                  !< coupling mode for atmosphere-ocean coupling
    535539    CHARACTER (LEN=20)   ::  coupling_mode_remote = 'uncoupled'           !< coupling mode of the remote process in case of coupled atmosphere-ocean runs
    536540    CHARACTER (LEN=20)   ::  dissipation_1d = 'detering'                  !< namelist parameter
     
    539543    CHARACTER (LEN=20)   ::  random_generator = 'random-parallel'         !< namelist parameter
    540544    CHARACTER (LEN=80)   ::  recycling_method_for_thermodynamic_quantities = 'turbulent_fluctuation'        !< namelist parameter
    541     CHARACTER (LEN=20)   ::  reference_state = 'initial_profile'          !< namelist parameter 
    542     CHARACTER (LEN=20)   ::  timestep_scheme = 'runge-kutta-3'            !< namelist parameter       
     545    CHARACTER (LEN=20)   ::  reference_state = 'initial_profile'          !< namelist parameter
     546    CHARACTER (LEN=20)   ::  timestep_scheme = 'runge-kutta-3'            !< namelist parameter
    543547    CHARACTER (LEN=20)   ::  turbulence_closure = 'Moeng_Wyngaard'        !< namelist parameter
    544     CHARACTER (LEN=40)   ::  topography = 'flat'                          !< namelist parameter 
     548    CHARACTER (LEN=40)   ::  topography = 'flat'                          !< namelist parameter
    545549    CHARACTER (LEN=64)   ::  host = '????'                                !< configuration identifier as given by palmrun option -c, ENVPAR namelist parameter provided by palmrun
    546550    CHARACTER (LEN=80)   ::  log_message                                  !< user-defined message for debugging (sse data_log.f90)
     
    554558    CHARACTER (LEN=varnamelength), DIMENSION(500) ::  data_output = ' '       !< namelist parameter
    555559    CHARACTER (LEN=varnamelength), DIMENSION(500) ::  data_output_user = ' '  !< namelist parameter
    556     CHARACTER (LEN=varnamelength), DIMENSION(500) ::  doav = ' '              !< label array for multi-dimensional, 
     560    CHARACTER (LEN=varnamelength), DIMENSION(500) ::  doav = ' '              !< label array for multi-dimensional,
    557561                                                                              !< averaged output quantities
    558                                            
     562
    559563    CHARACTER (LEN=varnamelength), DIMENSION(max_masks,100) ::  data_output_masks = ' '       !< namelist parameter
    560564    CHARACTER (LEN=varnamelength), DIMENSION(max_masks,100) ::  data_output_masks_user = ' '  !< namelist parameter
    561565
    562566    CHARACTER (LEN=varnamelength), DIMENSION(300) ::  data_output_pr = ' '  !< namelist parameter
    563    
     567
    564568    CHARACTER (LEN=varnamelength), DIMENSION(200) ::  data_output_pr_user = ' '  !< namelist parameter
    565    
    566     CHARACTER (LEN=varnamelength), DIMENSION(max_masks,0:1,100) ::  domask = ' ' !< label array for multi-dimensional, 
     569
     570    CHARACTER (LEN=varnamelength), DIMENSION(max_masks,0:1,100) ::  domask = ' ' !< label array for multi-dimensional,
    567571                                                                                 !< masked output quantities
    568    
     572
    569573    CHARACTER (LEN=varnamelength), DIMENSION(0:1,500) ::  do2d = ' '  !< label array for 2d output quantities
    570574    CHARACTER (LEN=varnamelength), DIMENSION(0:1,500) ::  do3d = ' '  !< label array for 3d output quantities
     
    572576    INTEGER(iwp), PARAMETER ::  fl_max = 500     !< maximum number of virtual-flight measurements
    573577    INTEGER(iwp), PARAMETER ::  var_fl_max = 20  !< maximum number of different sampling variables in virtual flight measurements
    574    
     578
    575579    INTEGER(iwp) ::  abort_mode = 1                    !< abort condition (nested runs)
    576580    INTEGER(iwp) ::  agt_time_count = 0                !< number of output intervals for agent data output
     
    642646    INTEGER(iwp) ::  timestep_count = 0                !< number of timesteps carried out since the beginning of the initial run
    643647    INTEGER(iwp) ::  y_shift = 0                       !< namelist parameter
    644    
     648
    645649    INTEGER(iwp) ::  dist_nxl(0:1)                               !< left boundary of disturbance region
    646650    INTEGER(iwp) ::  dist_nxr(0:1)                               !< right boundary of disturbance region
     
    662666    INTEGER(iwp) ::  pt_vertical_gradient_level_ind(10) = -9999  !< grid index values of pt_vertical_gradient_level(s)
    663667    INTEGER(iwp) ::  q_vertical_gradient_level_ind(10) = -9999   !< grid index values of q_vertical_gradient_level(s)
    664     INTEGER(iwp) ::  s_vertical_gradient_level_ind(10) = -9999   !< grid index values of s_vertical_gradient_level(s)   
     668    INTEGER(iwp) ::  s_vertical_gradient_level_ind(10) = -9999   !< grid index values of s_vertical_gradient_level(s)
    665669    INTEGER(iwp) ::  section(100,3)                              !< collective array for section_xy/xz/yz
    666670    INTEGER(iwp) ::  section_xy(100) = -9999                     !< namelist parameter
     
    739743    LOGICAL ::  humidity_remote = .FALSE.                        !< switch for receiving near-surface humidity flux (atmosphere-ocean coupling)
    740744    LOGICAL ::  indoor_model = .FALSE.                           !< switch for indoor-climate and energy-demand model
     745    LOGICAL ::  kolmogorov_length_scale = .FALSE.                !< switch to activate calculations in flow_statistics for the kolmogorov length scale
    741746    LOGICAL ::  large_scale_forcing = .FALSE.                    !< namelist parameter
    742747    LOGICAL ::  large_scale_subsidence = .FALSE.                 !< namelist parameter
     
    750755    LOGICAL ::  mg_switch_to_pe0 = .FALSE.                       !< internal multigrid switch for steering the ghost point exchange in case that data has been collected on PE0
    751756    LOGICAL ::  monotonic_limiter_z = .FALSE.                    !< use monotonic flux limiter for vertical scalar advection
    752     LOGICAL ::  nesting_offline = .FALSE.                        !< flag controlling offline nesting in COSMO model 
     757    LOGICAL ::  nesting_offline = .FALSE.                        !< flag controlling offline nesting in COSMO model
    753758    LOGICAL ::  neutral = .FALSE.                                !< namelist parameter
    754759    LOGICAL ::  nudging = .FALSE.                                !< namelist parameter
     
    804809    LOGICAL, DIMENSION(max_masks) ::  mask_surface = .FALSE.   !< flag for surface-following masked output
    805810
    806     REAL(wp) ::  advected_distance_x = 0.0_wp                  !< advected distance of model domain along x 
    807                                                                !< (galilei transformation) 
    808     REAL(wp) ::  advected_distance_y = 0.0_wp                  !< advected distance of model domain along y 
     811    REAL(wp) ::  advected_distance_x = 0.0_wp                  !< advected distance of model domain along x
     812                                                               !< (galilei transformation)
     813    REAL(wp) ::  advected_distance_y = 0.0_wp                  !< advected distance of model domain along y
    809814                                                               !< (galilei transformation)
    810815    REAL(wp) ::  alpha_surface = 0.0_wp                        !< namelist parameter
     
    830835    REAL(wp) ::  cos_alpha_surface                             !< cosine of alpha_surface
    831836    REAL(wp) ::  coupling_start_time = 0.0_wp                  !< namelist parameter
    832     REAL(wp) ::  days_since_reference_point = 0.0_wp           !< days after atmosphere-ocean coupling has been activated, 
    833                                                                !< or after spinup phase of LSM has been finished 
     837    REAL(wp) ::  days_since_reference_point = 0.0_wp           !< days after atmosphere-ocean coupling has been activated,
     838                                                               !< or after spinup phase of LSM has been finished
    834839    REAL(wp) ::  disturbance_amplitude = 0.25_wp               !< namelist parameter
    835840    REAL(wp) ::  disturbance_energy_limit = 0.01_wp            !< namelist parameter
     
    886891    REAL(wp) ::  pt_damping_width = 0.0_wp                     !< namelist parameter
    887892    REAL(wp) ::  pt_reference = 9999999.9_wp                   !< namelist parameter
    888     REAL(wp) ::  pt_slope_offset = 0.0_wp                      !< temperature difference between left and right 
     893    REAL(wp) ::  pt_slope_offset = 0.0_wp                      !< temperature difference between left and right
    889894                                                               !< boundary of total domain
    890895    REAL(wp) ::  pt_surface = 300.0_wp                         !< namelist parameter
     
    935940    REAL(wp) ::  time_do3d = 0.0_wp                            !< time since last 3d output
    936941    REAL(wp) ::  time_do_av = 0.0_wp                           !< time since last averaged-data output
    937     REAL(wp) ::  time_do_sla = 0.0_wp                          !< time since last 
     942    REAL(wp) ::  time_do_sla = 0.0_wp                          !< time since last
    938943    REAL(wp) ::  time_restart = 9999999.9_wp                   !< time at which run shall be terminated and restarted
    939944    REAL(wp) ::  time_run_control = 0.0_wp                     !< time since last RUN_CONTROL output
     
    949954    REAL(wp) ::  tunnel_width_y = 9999999.9_wp                 !< namelist parameter
    950955    REAL(wp) ::  tunnel_wall_depth = 9999999.9_wp              !< namelist parameter
    951     REAL(wp) ::  ug_surface = 0.0_wp                           !< namelist parameter 
    952     REAL(wp) ::  u_bulk = 0.0_wp                               !< namelist parameter 
     956    REAL(wp) ::  ug_surface = 0.0_wp                           !< namelist parameter
     957    REAL(wp) ::  u_bulk = 0.0_wp                               !< namelist parameter
    953958    REAL(wp) ::  u_gtrans = 0.0_wp                             !< transformed wind component (galilei transformation)
    954959    REAL(wp) ::  vg_surface = 0.0_wp                           !< namelist parameter
     
    9951000    REAL(wp) ::  wall_humidityflux(0:5) = 0.0_wp                   !< namelist parameter
    9961001    REAL(wp) ::  wall_salinityflux(0:5) = 0.0_wp                   !< namelist parameter
    997     REAL(wp) ::  wall_scalarflux(0:5) = 0.0_wp                     !< namelist parameter 
    998     REAL(wp) ::  subs_vertical_gradient(10) = 0.0_wp               !< namelist parameter 
     1002    REAL(wp) ::  wall_scalarflux(0:5) = 0.0_wp                     !< namelist parameter
     1003    REAL(wp) ::  subs_vertical_gradient(10) = 0.0_wp               !< namelist parameter
    9991004    REAL(wp) ::  subs_vertical_gradient_level(10) = -9999999.9_wp  !< namelist parameter
    10001005
     
    10041009    REAL(wp), DIMENSION(max_masks,mask_xyz_dimension) ::  mask_y = -1.0_wp  !< namelist parameter
    10051010    REAL(wp), DIMENSION(max_masks,mask_xyz_dimension) ::  mask_z = -1.0_wp  !< namelist parameter
    1006    
     1011
    10071012    REAL(wp), DIMENSION(max_masks,3) ::  mask_x_loop = -1.0_wp  !< namelist parameter
    10081013    REAL(wp), DIMENSION(max_masks,3) ::  mask_y_loop = -1.0_wp  !< namelist parameter
    10091014    REAL(wp), DIMENSION(max_masks,3) ::  mask_z_loop = -1.0_wp  !< namelist parameter
    1010    
     1015
    10111016!
    10121017!--    internal mask arrays ("mask,dimension,selection")
     
    10301035    REAL(wp) ::  ddx          !< 1/dx
    10311036    REAL(wp) ::  ddx2         !< 1/dx2
    1032     REAL(wp) ::  dx = 1.0_wp  !< horizontal grid size (along x-direction) 
     1037    REAL(wp) ::  dx = 1.0_wp  !< horizontal grid size (along x-direction)
    10331038    REAL(wp) ::  dx2          !< dx*dx
    10341039    REAL(wp) ::  ddy          !< 1/dy
     
    10401045    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddy2_mg  !< 1/dy_l**2 (dy_l: grid spacing along y on different multigrid level)
    10411046
    1042     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  zu_s_inner  !< height of topography top on scalar grid 
    1043     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  zw_w_inner  !< height of topography top on w grid 
     1047    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  zu_s_inner  !< height of topography top on scalar grid
     1048    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  zw_w_inner  !< height of topography top on w grid
    10441049
    10451050    SAVE
     
    10901095    INTEGER(idp), DIMENSION(:), ALLOCATABLE ::  ngp_3d        !< number of grid points of the total domain
    10911096    INTEGER(idp), DIMENSION(:), ALLOCATABLE ::  ngp_3d_inner  !< ! need to have 64 bit for grids > 2E9
    1092                    
     1097
    10931098    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_2dh  !< number of grid points of a horizontal cross section through the total domain
    10941099    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nxl_mg   !< left-most grid index of subdomain on different multigrid level
     
    11051110    INTEGER(iwp), DIMENSION(:,:,:), POINTER ::  flags  !< pointer to wall_flags_1-10
    11061111
    1107     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_1   !< topograpyh masking flag on multigrid level 1 
    1108     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_2   !< topograpyh masking flag on multigrid level 2 
    1109     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_3   !< topograpyh masking flag on multigrid level 3 
    1110     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_4   !< topograpyh masking flag on multigrid level 4 
    1111     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_5   !< topograpyh masking flag on multigrid level 5 
    1112     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_6   !< topograpyh masking flag on multigrid level 6 
    1113     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_7   !< topograpyh masking flag on multigrid level 7 
    1114     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_8   !< topograpyh masking flag on multigrid level 8 
    1115     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_9   !< topograpyh masking flag on multigrid level 9 
    1116     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_10  !< topograpyh masking flag on multigrid level 10 
     1112    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_1   !< topograpyh masking flag on multigrid level 1
     1113    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_2   !< topograpyh masking flag on multigrid level 2
     1114    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_3   !< topograpyh masking flag on multigrid level 3
     1115    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_4   !< topograpyh masking flag on multigrid level 4
     1116    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_5   !< topograpyh masking flag on multigrid level 5
     1117    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_6   !< topograpyh masking flag on multigrid level 6
     1118    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_7   !< topograpyh masking flag on multigrid level 7
     1119    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_8   !< topograpyh masking flag on multigrid level 8
     1120    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_9   !< topograpyh masking flag on multigrid level 9
     1121    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE,  TARGET ::  wall_flags_10  !< topograpyh masking flag on multigrid level 10
    11171122
    11181123    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  advc_flags_m            !< flags used to degrade order of advection scheme for momentum
     
    12211226    CHARACTER(LEN=2) ::  send_receive = 'al'     !<
    12221227    CHARACTER(LEN=7) ::  myid_char = ''          !< character string containing processor id number
    1223    
     1228
    12241229    INTEGER(iwp) ::  comm1dx                     !< communicator for domain decomposition along x
    12251230    INTEGER(iwp) ::  comm1dy                     !< communicator for domain decomposition along y
     
    12561261    INTEGER(iwp) ::  tasks_per_node = -9999      !< MPI tasks per compute node
    12571262    INTEGER(iwp) ::  threads_per_task = 1        !< number of OPENMP threads per MPI task
    1258     INTEGER(iwp) ::  type_x                      !< derived MPI datatype for 2-D ghost-point exchange - north / south 
    1259     INTEGER(iwp) ::  type_xy                     !< derived MPI datatype for 2-D ghost-point exchange - north / south 
    1260     INTEGER(iwp) ::  type_y                      !< derived MPI datatype for 2-D exchange in atmosphere-ocean coupler 
     1263    INTEGER(iwp) ::  type_x                      !< derived MPI datatype for 2-D ghost-point exchange - north / south
     1264    INTEGER(iwp) ::  type_xy                     !< derived MPI datatype for 2-D ghost-point exchange - north / south
     1265    INTEGER(iwp) ::  type_y                      !< derived MPI datatype for 2-D exchange in atmosphere-ocean coupler
    12611266
    12621267    INTEGER(iwp) ::  pdims(2) = 1  !< number of processors along x-y dimension
    12631268    INTEGER(iwp) ::  req(100)      !< MPI return variable indicating if send-receive operation is finished
    12641269
    1265     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  hor_index_bounds               !< horizontal index bounds 
     1270    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  hor_index_bounds               !< horizontal index bounds
    12661271    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  hor_index_bounds_previous_run  !< horizontal index bounds of previous run
    12671272
     
    12831288    INTEGER(iwp) ::  pcoord(2)                !< PE coordinates along x and y
    12841289    INTEGER(iwp) ::  status(MPI_STATUS_SIZE)  !< MPI status variable used in various MPI calls
    1285    
     1290
    12861291    INTEGER(iwp), DIMENSION(MPI_STATUS_SIZE,100) ::  wait_stat  !< MPI status variable used in various MPI calls
    1287    
     1292
    12881293    INTEGER(iwp) ::  type_x_byte !< derived MPI datatype for 2-D 8-bit integer ghost-point exchange - north / south
    12891294    INTEGER(iwp) ::  type_y_byte !< derived MPI datatype for 2-D integer ghost-point exchange - left / right
    1290    
     1295
    12911296    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_xz      !< number of ghost points in xz-plane on different multigrid level
    12921297    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_xz_int  !< number of ghost points in xz-plane on different multigrid level
     
    12971302    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_xz_int !< derived MPI datatype for 3-D integer ghost-point exchange - north / south
    12981303    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_y_int  !< derived MPI datatype for 2-D integer ghost-point exchange - left / right
    1299     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_yz     !< derived MPI datatype for 3-D integer ghost-point exchange - left / right 
     1304    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_yz     !< derived MPI datatype for 3-D integer ghost-point exchange - left / right
    13001305    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  type_yz_int !< derived MPI datatype for 3-D integer ghost-point exchange - left / right
    13011306
     
    13541359    INTEGER(iwp) ::  dopr_index(300) = 0                !< index number of respective profile quantity
    13551360    INTEGER(iwp) ::  dopr_initial_index(300) = 0        !< index number of initial profiles to be output
    1356                
     1361
    13571362    SAVE
    13581363
     
    13701375    CHARACTER (LEN=40) ::  region(0:9) =  &  !< label for statistic region
    13711376                           'total domain                            '
    1372  
     1377
    13731378    INTEGER(iwp) ::  pr_palm = 200          !< maximum number of output profiles
    13741379    INTEGER(iwp) ::  statistic_regions = 0  !< identifier for statistic regions
     
    13771382    INTEGER(iwp) ::  v_max_ijk(3) = -1  !< index values (i,j,k) of location where v_max occurs
    13781383    INTEGER(iwp) ::  w_max_ijk(3) = -1  !< index values (i,j,k) of location where w_max occurs
    1379    
     1384
    13801385    LOGICAL ::  flow_statistics_called = .FALSE.  !< flag that tells other routines if flow statistics was executed
    13811386                                                  !< (after each timestep)
    1382    
     1387
    13831388    REAL(wp) ::  u_max = 0.0_wp  !< maximum of absolute u-veloctiy in entire domain
    13841389    REAL(wp) ::  v_max = 0.0_wp  !< maximum of absolute v-veloctiy in entire domain
     
    13861391
    13871392    REAL(wp), DIMENSION(2) ::  z_i  !< inversion height
    1388    
     1393
    13891394    REAL(wp), DIMENSION(:), ALLOCATABLE ::  mean_surface_level_height  !< mean surface level height for the different statistic regions
    1390     REAL(wp), DIMENSION(:), ALLOCATABLE ::  sums_divnew_l              !< subdomain sum (_l) of divergence after pressure 
     1395    REAL(wp), DIMENSION(:), ALLOCATABLE ::  sums_divnew_l              !< subdomain sum (_l) of divergence after pressure
    13911396                                                                       !< solver call (new)
    13921397    REAL(wp), DIMENSION(:), ALLOCATABLE ::  sums_divold_l              !< subdomain sum (_l) of divergence before pressure
     
    13941399    REAL(wp), DIMENSION(:), ALLOCATABLE ::  weight_substep             !< weighting factor for substeps in timestepping
    13951400    REAL(wp), DIMENSION(:), ALLOCATABLE ::  weight_pres                !< substep weighting factor for pressure solver
    1396    
     1401
    13971402    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums             !< global sum array for the various output quantities
    13981403    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_salsa_ws_l  !< subdomain sum of vertical salsa flux w's' (5th-order advection scheme only)
     
    14131418    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_wsss_ws_l   !< subdomain sum of vertical passive scalar flux w's' (5th-order advection scheme only)
    14141419    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  sums_ls_l        !< subdomain sum of large scale forcing and nudging tendencies
    1415                                              
     1420
    14161421    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  hom_sum             !< sum array for horizontal mean
    14171422    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  rmask               !< REAL flag array (0.0 or 1.0) for statistic regions
    14181423    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  sums_l              !< subdomain sum (_l) gathered for various quantities
    14191424    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  sums_l_l            !< subdomain sum (_l) of mixing length from diffusivities
    1420    
     1425
    14211426    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  hom  !< horizontal mean of various quantities (profiles/timeseries)
    14221427
     
    14521457    INTEGER(iwp) ::  nzt_y   !< internal index bound for transpositions
    14531458    INTEGER(iwp) ::  nzt_yd  !< internal index bound for transpositions
    1454                
     1459
    14551460    SAVE
    14561461
Note: See TracChangeset for help on using the changeset viewer.