Changeset 4472 for palm


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

Profile output of the Kolmogorov length scale added

Location:
palm/trunk/SOURCE
Files:
4 edited

Legend:

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

    r4444 r4472  
    2525! -----------------
    2626! $Id$
     27! Kolmogorov length scale eta added to profile output
     28!
     29! 4444 2020-03-05 15:59:50Z raasch
    2730! bugfix: cpp-directives for serial mode added
    28 ! 
     31!
    2932! 4392 2020-01-31 16:14:57Z pavelkrc
    3033! Some error numbers revised to prevent double usage
    31 ! 
     34!
    3235! 11:55:33Z oliver.maas
    3336! Checks for closed channel flow implemented
    34 ! 
     37!
    3538! 11:55:33Z oliver.maas
    3639! Move 2-m potential temperature output to diagnostic_output_quantities
    37 ! 
     40!
    3841! 11:55:33Z oliver.maas
    3942! removed message PA0421, concerning old parameter recycling_yshift
    40 ! 
     43!
    4144! 11:55:33Z oliver.maas
    4245! adjust message to the modified parameter recycling_yshift
    43 ! 
     46!
    4447! 11:55:33Z oliver.maas
    4548! Check if a cross section is specified if any output cross-section quantity
    4649! is given
    47 ! 
     50!
    4851! 11:55:33Z oliver.maas
    4952! Overwrite rotation_angle from namelist by value from static driver
    50 ! 
     53!
    5154! 11:55:33Z oliver.maas
    52 ! removed conversion from recycle_absolute_quantities to raq, added check and 
     55! removed conversion from recycle_absolute_quantities to raq, added check and
    5356! error message for correct input of recycling_method_for_thermodynamic_quantities
    54 ! 
     57!
    5558! 11:55:33Z oliver.maas
    5659! Corrected "Former revisions" section
    57 ! 
     60!
    5861! 11:55:33Z oliver.maas
    5962! bugfix error message: replaced PA184 by PA0184
    60 ! 
     63!
    6164! 11:55:33Z oliver.maas
    62 ! added conversion from recycle_absolute_quantities to raq for recycling of 
     65! added conversion from recycle_absolute_quantities to raq for recycling of
    6366! absolute quantities and added error message PA184 for not implemented quantities
    64 ! 
     67!
    6568! 4142 2019-08-05 12:38:31Z suehring
    6669! Consider spinup in number of output timesteps for averaged 2D output (merge
    6770! from branch resler).
    68 ! 
     71!
    6972! 4069 2019-07-01 14:05:51Z Giersch
    70 ! Masked output running index mid has been introduced as a local variable to 
     73! Masked output running index mid has been introduced as a local variable to
    7174! avoid runtime error (Loop variable has been modified) in time_integration
    72 ! 
     75!
    7376! 4048 2019-06-21 21:00:21Z knoop
    7477! Moved tcm_check_data_output to module_interface
    75 ! 
     78!
    7679! 4039 2019-06-18 10:32:41Z suehring
    7780! Modularize diagnostic output
    78 ! 
     81!
    7982! 4017 2019-06-06 12:16:46Z schwenkel
    8083! output of turbulence intensity added
    81 ! 
     84!
    8285! 3933 2019-04-25 12:33:20Z kanani
    8386! Alphabetical resorting in CASE, condense settings for theta_2m* into one IF clause
    84 ! 
     87!
    8588! 3885 2019-04-11 11:29:34Z kanani
    86 ! Changes related to global restructuring of location messages and introduction 
     89! Changes related to global restructuring of location messages and introduction
    8790! of additional debug messages
    88 ! 
     91!
    8992! 3766 2019-02-26 16:23:41Z raasch
    9093! trim added to avoid truncation compiler warnings
    91 ! 
     94!
    9295! 3761 2019-02-25 15:31:42Z raasch
    9396! unused variables removed
    94 ! 
     97!
    9598! 3735 2019-02-12 09:52:40Z dom_dwd_user
    96 ! Passing variable j (averaged output?) to 
     99! Passing variable j (averaged output?) to
    97100! module_interface.f90:chem_check_data_output.
    98 ! 
     101!
    99102! 3705 2019-01-29 19:56:39Z suehring
    100103! bugfix: renamed thetav_t to vtheta_t
    101 ! 
     104!
    102105! 3702 2019-01-28 13:19:30Z gronemeier
    103106! most_method removed
    104 ! 
     107!
    105108! 3655 2019-01-07 16:51:22Z knoop
    106109! Formatting
     
    158161    USE particle_attributes,                                                   &
    159162        ONLY:  particle_advection, use_sgs_for_particles
    160        
     163
    161164    USE pegrid
    162165
     
    242245       CALL message( 'check_parameters', 'PA0476', 1, 2, 0, 6, 0 )
    243246    ENDIF
    244    
     247
    245248!
    246249!-- Check dt_coupling, restart_time, dt_restart, end_time, dx, dy, nx and ny
     
    522525!
    523526!--    Check illegal/untested parameter combinations for closed channel
    524        If ( topography == 'closed_channel' ) THEN 
     527       If ( topography == 'closed_channel' ) THEN
    525528          symmetry_flag = 1
    526529          message_string = 'Bottom and top boundary are treated equal'
    527530          CALL message( 'check_parameters', 'PA0699', 0, 0, 0, 6, 0 )
    528        
     531
    529532          IF ( dz(1) /= dz(COUNT( dz /= -1.0_wp )) .OR.                        &
    530533               dz_stretch_level /= -9999999.9_wp) THEN
     
    533536             CALL message( 'check_parameters', 'PA0700', 1, 2, 0, 6, 0 )
    534537          ENDIF
    535        
     538
    536539          IF ( constant_flux_layer ) THEN
    537540             WRITE( message_string, * )  'A constant flux layer is not '//     &
     
    540543             CALL message( 'check_parameters', 'PA0701', 1, 2, 0, 6, 0 )
    541544          ENDIF
    542        
     545
    543546          IF ( ocean_mode ) THEN
    544547             WRITE( message_string, * )  'The ocean mode is not allowed if '// &
     
    546549             CALL message( 'check_parameters', 'PA0702', 1, 2, 0, 6, 0 )
    547550          ENDIF
    548        
     551
    549552          IF ( momentum_advec /= 'ws-scheme' .OR.                              &
    550553               scalar_advec /= 'ws-scheme' ) THEN
     
    629632
    630633!
    631 !-- When the land- or urban-surface model is used, the flux output must be 
     634!-- When the land- or urban-surface model is used, the flux output must be
    632635!-- dynamic.
    633636    IF ( land_surface  .OR.  urban_surface )  THEN
     
    663666                                  ' its maximum of dots_max = ', dots_max,     &
    664667                                  '&Please increase dots_max in modules.f90.'
    665        CALL message( 'init_3d_model', 'PA0194', 1, 2, 0, 6, 0 )   
     668       CALL message( 'init_3d_model', 'PA0194', 1, 2, 0, 6, 0 )
    666669    ENDIF
    667670
     
    705708!
    706709!-- Advection schemes:
    707     IF ( momentum_advec /= 'pw-scheme'  .AND.                                  & 
     710    IF ( momentum_advec /= 'pw-scheme'  .AND.                                  &
    708711         momentum_advec /= 'ws-scheme'  .AND.                                  &
    709712         momentum_advec /= 'up-scheme' )                                       &
     
    849852    ENDIF
    850853!
    851 !-- In case of spinup and nested run, spinup end time must be identical 
    852 !-- in order to have synchronously running simulations. 
     854!-- In case of spinup and nested run, spinup end time must be identical
     855!-- in order to have synchronously running simulations.
    853856    IF ( nested_run )  THEN
    854857#if defined( __parallel )
     
    11491152
    11501153!
    1151 !-- Overwrite parameters from namelist if necessary and compute Coriolis parameter. 
     1154!-- Overwrite parameters from namelist if necessary and compute Coriolis parameter.
    11521155!-- @todo - move initialization of f and fs to coriolis_mod.
    11531156    IF ( input_pids_static )  THEN
     
    22792282             ENDIF
    22802283
     2284           CASE ( 'eta' )
     2285              dopr_index(i) = 121
     2286              dopr_unit(i)  = 'mm'
     2287              hom(:,2,121,:) = SPREAD( zu, 2, statistic_regions+1 )
     2288
     2289              kolmogorov_length_scale = .TRUE.
     2290
    22812291          CASE DEFAULT
    22822292             unit = 'illegal'
     
    24632473
    24642474             IF ( ( TRIM( var ) == 'r_a*' .OR.  TRIM( var ) == 'ghf*' )        &
    2465                  .AND.  .NOT.  land_surface  .AND.  .NOT.  urban_surface )     &         
     2475                 .AND.  .NOT.  land_surface  .AND.  .NOT.  urban_surface )     &
    24662476             THEN
    24672477                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
     
    24702480                CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
    24712481             ENDIF
    2472              
     2482
    24732483             IF ( TRIM( var ) == 'ssws*'  .AND.  .NOT.  passive_scalar )  THEN
    24742484                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
     
    24902500             IF ( TRIM( var ) == 'z0h*'   )  unit = 'm'
    24912501!
    2492 !--          Output of surface latent and sensible heat flux will be in W/m2 
    2493 !--          in case of natural- and urban-type surfaces, even if 
     2502!--          Output of surface latent and sensible heat flux will be in W/m2
     2503!--          in case of natural- and urban-type surfaces, even if
    24942504!--          flux_output_mode is set to kinematic units.
    24952505             IF ( land_surface  .OR.  urban_surface )  THEN
     
    27052715       CALL check_dt_do( dt_data_output_av, 'dt_data_output_av' )
    27062716
    2707 !--    Set needed time levels (ntdim) to 
     2717!--    Set needed time levels (ntdim) to
    27082718!--    saved time levels + to be saved time levels.
    27092719       ntdim_3d(0) = do3d_time_count(0) + CEILING(                                    &
     
    27492759       ENDIF
    27502760!
    2751 !--    Please note, for averaged 2D data skip_time_data_output_av is the relavant 
    2752 !--    output control parameter. 
     2761!--    Please note, for averaged 2D data skip_time_data_output_av is the relavant
     2762!--    output control parameter.
    27532763       ntdim_2d_xy(1) = do2d_xy_time_count(1) + CEILING(                              &
    27542764                     ( end_time - MAX( MERGE( skip_time_data_output_av,               &
     
    31583168       CALL message( 'check_parameters', 'PA0157', 1, 2, 0, 6, 0 )
    31593169    ENDIF
    3160    
     3170
    31613171!
    31623172!-- Prevent empty time records in volume, cross-section and masked data in case
     
    31973207
    31983208!
    3199 !-- Check if vertical grid stretching is switched off in case of complex 
     3209!-- Check if vertical grid stretching is switched off in case of complex
    32003210!-- terrain simulations
    32013211    IF ( complex_terrain  .AND.                                                &
  • palm/trunk/SOURCE/flow_statistics.f90

    r4464 r4472  
    2525! -----------------
    2626! $Id$
     27! Calculations of the Kolmogorov lengt scale eta implemented
     28!
     29! 4464 2020-03-17 11:08:46Z Giersch
    2730! Reset last change (r4463)
    28 ! 
     31!
    2932! 4463 2020-03-17 09:27:36Z Giersch
    3033! Calculate horizontally averaged profiles of all velocity components at the
     
    3336! 4444 2020-03-05 15:59:50Z raasch
    3437! bugfix: cpp-directives for serial mode added
    35 ! 
     38!
    3639! 4442 2020-03-04 19:21:13Z suehring
    37 ! Change order of dimension in surface array %frac to allow for better 
     40! Change order of dimension in surface array %frac to allow for better
    3841! vectorization.
    39 ! 
     42!
    4043! 4441 2020-03-04 19:20:35Z suehring
    4144! Introduction of wall_flags_total_0, which currently sets bits based on static
    4245! topography information used in wall_flags_static_0
    43 ! 
     46!
    4447! 4329 2019-12-10 15:46:36Z motisi
    4548! Renamed wall_flags_0 to wall_flags_static_0
    46 ! 
     49!
    4750! 4182 2019-08-22 15:20:23Z scharf
    4851! Corrected "Former revisions" section
    49 ! 
     52!
    5053! 4131 2019-08-02 11:06:18Z monakurppa
    5154! Allow profile output for salsa variables.
    52 ! 
     55!
    5356! 4039 2019-06-18 10:32:41Z suehring
    54 ! Correct conversion to kinematic scalar fluxes in case of pw-scheme and 
     57! Correct conversion to kinematic scalar fluxes in case of pw-scheme and
    5558! statistic regions
    56 ! 
     59!
    5760! 3828 2019-03-27 19:36:23Z raasch
    5861! unused variables removed
    59 ! 
     62!
    6063! 3676 2019-01-16 15:07:05Z knoop
    6164! Bugfix, terminate OMP Parallel block
     
    7174!>
    7275!> @note For simplicity, nzb_s_inner and nzb_diff_s_inner are being used as a
    73 !>       lower vertical index for k-loops for all variables, although strictly 
    74 !>       speaking the k-loops would have to be split up according to the staggered 
    75 !>       grid. However, this implies no error since staggered velocity components 
     76!>       lower vertical index for k-loops for all variables, although strictly
     77!>       speaking the k-loops would have to be split up according to the staggered
     78!>       grid. However, this implies no error since staggered velocity components
    7679!>       are zero at the walls and inside buildings.
    7780!------------------------------------------------------------------------------!
     
    97100    USE control_parameters,                                                    &
    98101        ONLY:   air_chemistry, average_count_pr, cloud_droplets, do_sum,       &
    99                 dt_3d, humidity, initializing_actions, land_surface,           &
    100                 large_scale_forcing, large_scale_subsidence, max_pr_user,      &
    101                 message_string, neutral, ocean_mode, passive_scalar,           &
    102                 simulated_time, simulated_time_at_begin,                       &
     102                dt_3d, humidity, initializing_actions, kolmogorov_length_scale,&
     103                land_surface, large_scale_forcing, large_scale_subsidence,     &
     104                max_pr_user, message_string, neutral, ocean_mode,              &
     105                passive_scalar, simulated_time, simulated_time_at_begin,       &
    103106                use_subsidence_tendencies, use_surface_fluxes, use_top_fluxes, &
    104107                ws_scheme_mom, ws_scheme_sca, salsa, max_pr_salsa
     
    109112    USE grid_variables,                                                        &
    110113        ONLY:   ddx, ddy
    111        
     114
    112115    USE indices,                                                               &
    113116        ONLY:   ngp_2dh, ngp_2dh_s_inner, ngp_3d, ngp_3d_inner, nxl, nxr, nyn, &
     
    118121        ONLY:  ngp_sums, ngp_sums_ls
    119122#endif
    120        
     123
    121124    USE kinds
    122    
     125
    123126    USE land_surface_model_mod,                                                &
    124127        ONLY:   m_soil_h, nzb_soil, nzt_soil, t_soil_h
     
    151154    INTEGER(iwp) ::  j                   !<
    152155    INTEGER(iwp) ::  k                   !<
    153     INTEGER(iwp) ::  ki                  !< 
     156    INTEGER(iwp) ::  ki                  !<
    154157    INTEGER(iwp) ::  k_surface_level     !<
    155     INTEGER(iwp) ::  m                   !< loop variable over all horizontal wall elements 
     158    INTEGER(iwp) ::  m                   !< loop variable over all horizontal wall elements
    156159    INTEGER(iwp) ::  l                   !< loop variable over surface facing -- up- or downward-facing
    157160    INTEGER(iwp) ::  nt                  !<
     
    161164
    162165    LOGICAL ::  first  !<
    163    
    164     REAL(wp) ::  dptdz_threshold  !<
     166
     167    REAL(wp) ::  dissipation      !< dissipation rate
     168    REAL(wp) ::  dptdz_threshold  !<
     169    REAL(wp) ::  du_dx            !< Derivative of u fluctuations with respect to x
     170    REAL(wp) ::  du_dy            !< Derivative of u fluctuations with respect to y
     171    REAL(wp) ::  du_dz            !< Derivative of u fluctuations with respect to z
     172    REAL(wp) ::  dv_dx            !< Derivative of v fluctuations with respect to x
     173    REAL(wp) ::  dv_dy            !< Derivative of v fluctuations with respect to y
     174    REAL(wp) ::  dv_dz            !< Derivative of v fluctuations with respect to z
     175    REAL(wp) ::  dw_dx            !< Derivative of w fluctuations with respect to x
     176    REAL(wp) ::  dw_dy            !< Derivative of w fluctuations with respect to y
     177    REAL(wp) ::  dw_dz            !< Derivative of w fluctuations with respect to z
     178    REAL(wp) ::  eta              !< Kolmogorov length scale
    165179    REAL(wp) ::  fac              !<
    166180    REAL(wp) ::  flag             !<
    167181    REAL(wp) ::  height           !<
    168182    REAL(wp) ::  pts              !<
     183    REAL(wp) ::  s11              !< fluctuating rate-of-strain tensor component 11
     184    REAL(wp) ::  s21              !< fluctuating rate-of-strain tensor component 21
     185    REAL(wp) ::  s31              !< fluctuating rate-of-strain tensor component 31
     186    REAL(wp) ::  s12              !< fluctuating rate-of-strain tensor component 12
     187    REAL(wp) ::  s22              !< fluctuating rate-of-strain tensor component 22
     188    REAL(wp) ::  s32              !< fluctuating rate-of-strain tensor component 32
     189    REAL(wp) ::  s13              !< fluctuating rate-of-strain tensor component 13
     190    REAL(wp) ::  s23              !< fluctuating rate-of-strain tensor component 23
     191    REAL(wp) ::  s33              !< fluctuating rate-of-strain tensor component 33
    169192    REAL(wp) ::  sums_l_etot      !<
    170193    REAL(wp) ::  ust              !<
     
    175198    REAL(wp) ::  v2               !<
    176199    REAL(wp) ::  w2               !<
    177    
     200
    178201    REAL(wp) ::  dptdz(nzb+1:nzt+1)    !<
    179202    REAL(wp) ::  sums_ll(nzb:nzt+1,2)  !<
     
    210233!--    array
    211234       sums_l(:,11,:) = sums_l_l(:,sr,:)      ! mixing length from diffusivities
    212 !--    WARNING: next line still has to be adjusted for OpenMP 
     235!--    WARNING: next line still has to be adjusted for OpenMP
    213236       sums_l(:,21,0) = sums_wsts_bc_l(:,sr) *                                 &
    214237                        heatflux_output_conversion  ! heat flux from advec_s_bc
     
    220243!--    scale) vertical fluxes and velocity variances by using commonly-
    221244!--    applied Reynolds-based methods ( e.g. <w'pt'> = (w-<w>)*(pt-<pt>) )
    222 !--    in combination with the 5th order advection scheme, pronounced 
    223 !--    artificial kinks could be observed in the vertical profiles near the 
    224 !--    surface. Please note: these kinks were not related to the model truth, 
    225 !--    i.e. these kinks are just related to an evaluation problem.   
    226 !--    In order avoid these kinks, vertical fluxes and horizontal as well 
     245!--    in combination with the 5th order advection scheme, pronounced
     246!--    artificial kinks could be observed in the vertical profiles near the
     247!--    surface. Please note: these kinks were not related to the model truth,
     248!--    i.e. these kinks are just related to an evaluation problem.
     249!--    In order avoid these kinks, vertical fluxes and horizontal as well
    227250!--    vertical velocity variances are calculated directly within the advection
    228 !--    routines, according to the numerical discretization, to evaluate the 
    229 !--    statistical quantities as they will appear within the prognostic 
     251!--    routines, according to the numerical discretization, to evaluate the
     252!--    statistical quantities as they will appear within the prognostic
    230253!--    equations.
    231 !--    Copy the turbulent quantities, evaluated in the advection routines to 
     254!--    Copy the turbulent quantities, evaluated in the advection routines to
    232255!--    the local array sums_l() for further computations.
    233256       IF ( ws_scheme_mom .AND. sr == 0 )  THEN
     
    248271             sums_l(:,15,i) = sums_wsvs_ws_l(:,i)                              &
    249272                              * momentumflux_output_conversion ! w*v*
    250              sums_l(:,30,i) = sums_us2_ws_l(:,i)        ! u*2 
    251              sums_l(:,31,i) = sums_vs2_ws_l(:,i)        ! v*2 
    252              sums_l(:,32,i) = sums_ws2_ws_l(:,i)        ! w*2 
    253              sums_l(:,34,i) = sums_l(:,34,i) + 0.5_wp *                        & 
     273             sums_l(:,30,i) = sums_us2_ws_l(:,i)        ! u*2
     274             sums_l(:,31,i) = sums_vs2_ws_l(:,i)        ! v*2
     275             sums_l(:,32,i) = sums_ws2_ws_l(:,i)        ! w*2
     276             sums_l(:,34,i) = sums_l(:,34,i) + 0.5_wp *                        &
    254277                              ( sums_us2_ws_l(:,i) + sums_vs2_ws_l(:,i) +      &
    255278                                sums_ws2_ws_l(:,i) )    ! e*
     
    270293
    271294       ENDIF
    272 ! 
     295!
    273296!--    Horizontally averaged profiles of horizontal velocities and temperature.
    274297!--    They must have been computed before, because they are already required
     
    446469
    447470!
    448 !--    Final values are obtained by division by the total number of grid points 
     471!--    Final values are obtained by division by the total number of grid points
    449472!--    used for summation. After that store profiles.
    450473       sums(:,1) = sums(:,1) / ngp_2dh(sr)
     
    482505!--    Passive scalar
    483506       IF ( passive_scalar )  hom(:,1,115,sr) = sums(:,115) /                  &
    484             ngp_2dh_s_inner(:,sr)                    ! s 
     507            ngp_2dh_s_inner(:,sr)                    ! s
    485508
    486509!
     
    488511!--    variances, the total and the perturbation energy (single values in last
    489512!--    column of sums_l) and some diagnostic quantities.
    490 !--    NOTE: for simplicity, nzb_s_inner is used below, although strictly 
    491 !--    ----  speaking the following k-loop would have to be split up and 
     513!--    NOTE: for simplicity, nzb_s_inner is used below, although strictly
     514!--    ----  speaking the following k-loop would have to be split up and
    492515!--          rearranged according to the staggered grid.
    493516!--          However, this implies no error since staggered velocity components
     
    500523       !$OMP DO
    501524       !$ACC PARALLEL LOOP COLLAPSE(2) PRIVATE(i, j, k, m) &
    502        !$ACC PRIVATE(sums_l_etot, flag) &
     525       !$ACC PRIVATE(sums_l_etot, flag, du_dx, du_dy, du_dz) &
     526       !$ACC PRIVATE(dv_dx, dv_dy, dv_dz, dw_dx, dw_dy, dw_dz) &
     527       !$ACC PRIVATE(s11, s21, s31, s12, s22, s32, s13, s23, s33) &
     528       !$ACC PRIVATE(dissipation, eta) &
    503529       !$ACC PRESENT(wall_flags_total_0, rmask, momentumflux_output_conversion) &
    504        !$ACC PRESENT(hom(:,1,4,sr)) &
     530       !$ACC PRESENT(hom(:,1,1:2,sr), hom(:,1,4,sr)) &
    505531       !$ACC PRESENT(e, u, v, w, km, kh, p, pt) &
     532       !$ACC PRESENT(ddx, ddy, ddzu, ddzw) &
    506533       !$ACC PRESENT(surf_def_h(0), surf_lsm_h, surf_usm_h) &
    507534       !$ACC PRESENT(sums_l)
     
    557584                                        w(k,j,i)**2 )            * rmask(j,i,sr)&
    558585                                                                 * flag
    559              ENDDO
     586
     587!
     588!--             Computation of the Kolmogorov length scale. Calculation is based
     589!--             on gradients of the deviations from the horizontal mean.
     590!--             Kolmogorov scale at the boundaries (k=0/z=0m and k=nzt+1) is set to zero.
     591                IF ( kolmogorov_length_scale .AND. k /= nzb .AND. k /= nzt+1) THEN
     592                   flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 22 ) )
     593
     594!
     595!--                Calculate components of the fluctuating rate-of-strain tensor
     596!--                (0.5*(del u'_i/del x_j + del u'_j/del x_i)) defined in the
     597!--                center of each grid box.
     598                   du_dx = ( ( u(k,j,i+1) - hom(k,1,1,sr) ) -                  &
     599                             ( u(k,j,i) - hom(k,1,1,sr) ) ) * ddx
     600                   du_dy = 0.25_wp * ddy *                                     &
     601                           ( ( u(k,j+1,i) - hom(k,1,1,sr) ) -                  &
     602                             ( u(k,j-1,i) - hom(k,1,1,sr) ) +                  &
     603                             ( u(k,j+1,i+1) - hom(k,1,1,sr) ) -                &
     604                             ( u(k,j-1,i+1) - hom(k,1,1,sr) ) )
     605                   du_dz = 0.25_wp * ( ( ( u(k+1,j,i) - hom(k+1,1,1,sr) ) -    &
     606                                         ( u(k,j,i) - hom(k,1,1,sr) ) ) *      &
     607                                        ddzu(k+1) +                            &
     608                                       ( ( u(k,j,i) - hom(k,1,1,sr) ) -        &
     609                                         ( u(k-1,j,i) - hom(k-1,1,1,sr) ) )*   &
     610                                        ddzu(k) +                              &
     611                                       ( ( u(k+1,j,i+1) - hom(k+1,1,1,sr) )-   &
     612                                         ( u(k,j,i+1) - hom(k,1,1,sr) ) ) *    &
     613                                        ddzu(k+1) +                            &
     614                                       ( ( u(k,j,i+1) - hom(k,1,1,sr) ) -      &
     615                                         ( u(k-1,j,i+1) - hom(k-1,1,1,sr) ) ) *&
     616                                        ddzu(k) )
     617
     618                   dv_dx = 0.25_wp * ddx *                                     &
     619                           ( ( v(k,j,i+1) - hom(k,1,2,sr) ) -                  &
     620                             ( v(k,j,i-1) - hom(k,1,2,sr) ) +                  &
     621                             ( v(k,j+1,i+1) - hom(k,1,2,sr) ) -                &
     622                             ( v(k,j+1,i-1) - hom(k,1,2,sr) ) )
     623                   dv_dy = ( ( v(k,j+1,i) - hom(k,1,2,sr) ) -                  &
     624                             ( v(k,j,i) - hom(k,1,2,sr) ) ) * ddy
     625                   dv_dz = 0.25_wp * ( ( ( v(k+1,j,i) - hom(k+1,1,2,sr) ) -    &
     626                                         ( v(k,j,i) - hom(k,1,2,sr) ) ) *      &
     627                                        ddzu(k+1) +                            &
     628                                       ( ( v(k,j,i) - hom(k,1,2,sr) ) -        &
     629                                         ( v(k-1,j,i) - hom(k-1,1,2,sr) ) ) *  &
     630                                        ddzu(k) +                              &
     631                                       ( ( v(k+1,j+1,i) - hom(k+1,1,2,sr) ) -  &
     632                                         ( v(k,j+1,i) - hom(k,1,2,sr) ) ) *    &
     633                                        ddzu(k+1) +                            &
     634                                       ( ( v(k,j+1,i) - hom(k,1,2,sr) ) -      &
     635                                         ( v(k-1,j+1,i) - hom(k-1,1,2,sr) ) ) *&
     636                                        ddzu(k) )
     637
     638                   dw_dx = 0.25_wp * ddx * ( w(k,j,i+1) - w(k,j,i-1) +         &
     639                                             w(k-1,j,i+1) - w(k-1,j,i-1) )
     640                   dw_dy = 0.25_wp * ddy * ( w(k,j+1,i) - w(k,j-1,i) +         &
     641                                             w(k-1,j+1,i) - w(k-1,j-1,i) )
     642                   dw_dz = ( w(k,j,i) - w(k-1,j,i) ) * ddzw(k)
     643
     644                   s11 = 0.5_wp * ( du_dx + du_dx )
     645                   s21 = 0.5_wp * ( dv_dx + du_dy )
     646                   s31 = 0.5_wp * ( dw_dx + du_dz )
     647
     648                   s12 = s21
     649                   s22 = 0.5 * ( dv_dy + dv_dy )
     650                   s32 = 0.5 * ( dw_dy + dv_dz )
     651
     652                   s13 = s31
     653                   s23 = s32
     654                   s33 = 0.5_wp * ( dw_dz + dw_dz )
     655
     656!--                Calculate 3D instantaneous energy dissipation rate after
     657!--                Pope (2000): Turbulent flows, p.259. It is defined in the center
     658!--                of each grid volume.
     659                   dissipation = 2.0_wp * km(k,j,i) *                          &
     660                                ( s11*s11 + s21*s21 + s31*s31 +                &
     661                                 s12*s12 + s22*s22 + s32*s32 +                 &
     662                                s13*s13 + s23*s23 + s33*s33 )
     663                   eta         = ( km(k,j,i)**3.0_wp / ( dissipation+1.0E-12 ) )**(1.0_wp/4.0_wp)
     664
     665                   !$ACC ATOMIC
     666                   sums_l(k,121,tn) = sums_l(k,121,tn) + eta * rmask(j,i,sr)   &
     667                                                                * flag
     668
     669
     670                ENDIF !Kolmogorov length scale
     671
     672             ENDDO !k-loop
    560673!
    561674!--          Total and perturbation energy for the total domain (being
     
    661774                                            rmask(j,i,sr)
    662775             ENDIF
    663           ENDDO
    664        ENDDO
     776          ENDDO !j-loop
     777       ENDDO !i-loop
    665778       !$ACC UPDATE &
    666779       !$ACC HOST(sums_l(:,3,tn), sums_l(:,8,tn), sums_l(:,9,tn)) &
    667780       !$ACC HOST(sums_l(:,10,tn), sums_l(:,40,tn), sums_l(:,33,tn)) &
    668        !$ACC HOST(sums_l(:,38,tn)) &
     781       !$ACC HOST(sums_l(:,38,tn), sums_l(:,121,tn)) &
    669782       !$ACC HOST(sums_l(nzb:nzb+4,pr_palm,tn), sums_l(nzb+14:nzb+14,pr_palm,tn))
    670783
    671784!
    672 !--    Computation of statistics when ws-scheme is not used. Else these 
     785!--    Computation of statistics when ws-scheme is not used. Else these
    673786!--    quantities are evaluated in the advection routines.
    674787       IF ( .NOT. ws_scheme_mom .OR. sr /= 0 .OR. simulated_time == 0.0_wp )   &
     
    703816       ENDIF
    704817!
    705 !--    Computaion of domain-averaged perturbation energy. Please note, 
    706 !--    to prevent that perturbation energy is larger (even if only slightly) 
     818!--    Computaion of domain-averaged perturbation energy. Please note,
     819!--    to prevent that perturbation energy is larger (even if only slightly)
    707820!--    than the total kinetic energy, calculation is based on deviations from
    708821!--    the horizontal mean, instead of spatial descretization of the advection
    709 !--    term. 
     822!--    term.
    710823       !$OMP DO
    711824       !$ACC PARALLEL LOOP COLLAPSE(3) PRIVATE(i, j, k, flag, w2, ust2, vst2) &
     
    727840                                 * rmask(j,i,sr)                               &
    728841                                 * flag
     842
    729843             ENDDO
    730844          ENDDO
     
    746860          DO  j = nys, nyn
    747861!
    748 !--          Subgridscale fluxes (without Prandtl layer from k=nzb, 
     862!--          Subgridscale fluxes (without Prandtl layer from k=nzb,
    749863!--          oterwise from k=nzb+1)
    750864!--          NOTE: for simplicity, nzb_diff_s_inner is used below, although
    751865!--          ----  strictly speaking the following k-loop would have to be
    752866!--                split up according to the staggered grid.
    753 !--                However, this implies no error since staggered velocity 
     867!--                However, this implies no error since staggered velocity
    754868!--                components are zero at the walls and inside buildings.
    755869!--          Flag 23 is used to mask surface fluxes as well as model-top fluxes,
    756 !--          which are added further below. 
     870!--          which are added further below.
    757871             DO  k = nzb, nzt
    758872                flag = MERGE( 1.0_wp, 0.0_wp,                                  &
     
    11841298                                    0.0_wp * rmask(j,i,sr)        ! u"pt"
    11851299                sums_l(nzt:nzt+1,61,tn) = sums_l(nzt:nzt+1,61,tn) + &
    1186                                     0.0_wp * rmask(j,i,sr)        ! v"pt" 
     1300                                    0.0_wp * rmask(j,i,sr)        ! v"pt"
    11871301#endif
    11881302#ifndef _OPENACC
     
    12271341!
    12281342!--          Resolved fluxes (can be computed for all horizontal points)
    1229 !--          NOTE: for simplicity, nzb_s_inner is used below, although strictly 
    1230 !--          ----  speaking the following k-loop would have to be split up and 
     1343!--          NOTE: for simplicity, nzb_s_inner is used below, although strictly
     1344!--          ----  speaking the following k-loop would have to be split up and
    12311345!--                rearranged according to the staggered grid.
    12321346             DO  k = nzb, nzt
     
    13031417                            sums_l(k,73,tn) = sums_l(k,73,tn) + nr(k,j,i) *    &
    13041418                                                                rmask(j,i,sr) *&
    1305                                                                 flag 
     1419                                                                flag
    13061420                            sums_l(k,74,tn) = sums_l(k,74,tn) + qr(k,j,i) *    &
    13071421                                                                rmask(j,i,sr) *&
     
    13201434                                                             flag
    13211435                      ELSE IF ( ws_scheme_sca .AND. sr == 0 )  THEN
    1322                          sums_l(k,46,tn) = ( ( 1.0_wp + 0.61_wp *              & 
     1436                         sums_l(k,46,tn) = ( ( 1.0_wp + 0.61_wp *              &
    13231437                                               hom(k,1,41,sr) ) *              &
    13241438                                             sums_l(k,17,tn) +                 &
     
    13591473       !$ACC HOST(sums_l(:,35,tn), sums_l(:,36,tn), sums_l(:,37,tn))
    13601474!
    1361 !--    Treat land-surface quantities according to new wall model structure. 
     1475!--    Treat land-surface quantities according to new wall model structure.
    13621476       IF ( land_surface )  THEN
    13631477          tn = 0
     
    13681482             i = surf_lsm_h%i(m)
    13691483             j = surf_lsm_h%j(m)
    1370        
     1484
    13711485             IF ( i >= nxl  .AND.  i <= nxr  .AND.                             &
    1372                   j >= nys  .AND.  j <= nyn )  THEN 
     1486                  j >= nys  .AND.  j <= nyn )  THEN
    13731487                sums_l(nzb,93,tn)  = sums_l(nzb,93,tn) + surf_lsm_h%ghf(m)
    13741488                sums_l(nzb,94,tn)  = sums_l(nzb,94,tn) + surf_lsm_h%qsws_liq(m)
     
    13871501          DO  m = 1, surf_lsm_h%ns
    13881502
    1389              i = surf_lsm_h%i(m)           
     1503             i = surf_lsm_h%i(m)
    13901504             j = surf_lsm_h%j(m)
    13911505
    13921506             IF ( i >= nxl  .AND.  i <= nxr  .AND.                             &
    1393                   j >= nys  .AND.  j <= nyn )  THEN 
     1507                  j >= nys  .AND.  j <= nyn )  THEN
    13941508
    13951509                DO  k = nzb_soil, nzt_soil
     
    14171531                DO  k = nzb, nzt
    14181532!
    1419 !--                Flag 23 is used to mask surface fluxes as well as model-top 
    1420 !--                fluxes, which are added further below. 
     1533!--                Flag 23 is used to mask surface fluxes as well as model-top
     1534!--                fluxes, which are added further below.
    14211535                   flag = MERGE( 1.0_wp, 0.0_wp,                               &
    14221536                                 BTEST( wall_flags_total_0(k,j,i), 23 ) ) *    &
     
    15691683
    15701684!
    1571 !--    Horizontal heat fluxes (subgrid, resolved, total). 
    1572 !--    Do it only, if profiles shall be plotted. 
     1685!--    Horizontal heat fluxes (subgrid, resolved, total).
     1686!--    Do it only, if profiles shall be plotted.
    15731687       IF ( hom(nzb+1,2,58,0) /= 0.0_wp ) THEN
    15741688
     
    16281742       IF ( large_scale_forcing  .AND.  ( simulated_time > 0.0_wp ) )  THEN
    16291743!
    1630 !--       Interpolation in time of LSF_DATA 
     1744!--       Interpolation in time of LSF_DATA
    16311745          nt = 1
    16321746          DO WHILE ( simulated_time - dt_3d > time_vert(nt) )
     
    16691783       tn = 0
    16701784       !$OMP PARALLEL PRIVATE( i, j, k, tn )
    1671        !$ tn = omp_get_thread_num()       
     1785       !$ tn = omp_get_thread_num()
    16721786       IF ( radiation .AND. radiation_scheme == 'rrtmg' )  THEN
    16731787          !$OMP DO
     
    17181832
    17191833             IF ( air_chemistry )  THEN
    1720                 IF ( max_pr_cs > 0 )  THEN                                 
     1834                IF ( max_pr_cs > 0 )  THEN
    17211835                     sums_l(:,pr_palm+max_pr_user+1:pr_palm + max_pr_user+ max_pr_cs,0) =          &
    17221836                               sums_l(:,pr_palm+max_pr_user+1:pr_palm + max_pr_user+max_pr_cs,0) + &
     
    17741888
    17751889!
    1776 !--    Final values are obtained by division by the total number of grid points 
     1890!--    Final values are obtained by division by the total number of grid points
    17771891!--    used for summation. After that store profiles.
    17781892!--    Check, if statistical regions do contain at least one grid point at the
     
    18341948
    18351949       IF ( air_chemistry ) THEN
    1836           IF ( max_pr_cs > 0 )  THEN                 
     1950          IF ( max_pr_cs > 0 )  THEN
    18371951             DO k = nzb, nzt+1
    18381952                sums(k, pr_palm+1:pr_palm+max_pr_user+max_pr_cs) = &
     
    18401954                                 ngp_2dh_s_inner(k,sr)
    18411955             ENDDO
    1842           ENDIF 
     1956          ENDIF
    18431957       ENDIF
    18441958
     
    18501964                  / ngp_2dh_s_inner(k,sr)
    18511965             ENDDO
    1852           ENDIF 
     1966          ENDIF
    18531967       ENDIF
    18541968
     
    18731987       hom(:,1,22,sr) = sums(:,16) + sums(:,21)    ! wptBC
    18741988                                       ! profile 24 is initial profile (sa)
    1875                                        ! profiles 25-29 left empty for initial 
     1989                                       ! profiles 25-29 left empty for initial
    18761990                                       ! profiles
    18771991       hom(:,1,30,sr) = sums(:,30)     ! u*2
     
    18872001       hom(:,1,40,sr) = sums(:,40)     ! p
    18882002       hom(:,1,45,sr) = sums(:,45)     ! w"vpt"
    1889        hom(:,1,46,sr) = sums(:,46)     ! w*vpt*       
     2003       hom(:,1,46,sr) = sums(:,46)     ! w*vpt*
    18902004       hom(:,1,47,sr) = sums(:,45) + sums(:,46)    ! wvpt
    18912005       hom(:,1,48,sr) = sums(:,48)     ! w"q" (w"qv")
     
    18932007       hom(:,1,50,sr) = sums(:,48) + sums(:,49)    ! wq (wqv)
    18942008       hom(:,1,51,sr) = sums(:,51)     ! w"qv"
    1895        hom(:,1,52,sr) = sums(:,52)     ! w*qv*       
     2009       hom(:,1,52,sr) = sums(:,52)     ! w*qv*
    18962010       hom(:,1,53,sr) = sums(:,52) + sums(:,51)    ! wq (wqv)
    18972011       hom(:,1,54,sr) = sums(:,54)     ! ql
     
    19792093          hom(:,1,117,sr) = sums(:,117)     ! w"s"
    19802094          hom(:,1,114,sr) = sums(:,114)     ! w*s*
    1981           hom(:,1,118,sr) = sums(:,117) + sums(:,114)    ! ws 
     2095          hom(:,1,118,sr) = sums(:,117) + sums(:,114)    ! ws
    19822096          hom(:,1,116,sr) = sums(:,116)     ! s*2
    19832097       ENDIF
     
    19852099       hom(:,1,119,sr) = rho_air       ! rho_air in Kg/m^3
    19862100       hom(:,1,120,sr) = rho_air_zw    ! rho_air_zw in Kg/m^3
     2101
     2102       IF ( kolmogorov_length_scale ) THEN
     2103          hom(:,1,121,sr) = sums(:,121) * 1E3_wp  ! eta in mm
     2104       ENDIF
     2105
    19872106
    19882107       hom(:,1,pr_palm,sr) =   sums(:,pr_palm)
     
    19952114
    19962115       IF ( air_chemistry )  THEN
    1997           IF ( max_pr_cs > 0 )  THEN    ! chem_spcs profiles     
     2116          IF ( max_pr_cs > 0 )  THEN    ! chem_spcs profiles
    19982117             hom(:, 1, pr_palm+max_pr_user+1:pr_palm + max_pr_user+max_pr_cs, sr) = &
    19992118                               sums(:, pr_palm+max_pr_user+1:pr_palm+max_pr_user+max_pr_cs)
     
    20132132!--    The corresponding height is assumed as the boundary layer height, if it
    20142133!--    is less than 1.5 times the height where the heat flux becomes negative
    2015 !--    (positive) for the first time. Attention: the resolved vertical sensible 
     2134!--    (positive) for the first time. Attention: the resolved vertical sensible
    20162135!--    heat flux (hom(:,1,17,sr) = w*pt*) is not known at the beginning because
    2017 !--    the calculation happens in advec_s_ws which is called after 
    2018 !--    flow_statistics. Therefore z_i is directly taken from restart data at 
    2019 !--    the beginning of restart runs. 
     2136!--    the calculation happens in advec_s_ws which is called after
     2137!--    flow_statistics. Therefore z_i is directly taken from restart data at
     2138!--    the beginning of restart runs.
    20202139       IF ( TRIM( initializing_actions ) /= 'read_restart_data' .OR.           &
    20212140            simulated_time_at_begin /= simulated_time ) THEN
     
    20592178
    20602179!
    2061 !--       Second scheme: Gradient scheme from Sullivan et al. (1998), modified 
    2062 !--       by Uhlenbrock(2006). The boundary layer height is the height with the 
     2180!--       Second scheme: Gradient scheme from Sullivan et al. (1998), modified
     2181!--       by Uhlenbrock(2006). The boundary layer height is the height with the
    20632182!--       maximal local temperature gradient: starting from the second (the
    2064 !--       last but one) vertical gridpoint, the local gradient must be at least 
     2183!--       last but one) vertical gridpoint, the local gradient must be at least
    20652184!--       0.2K/100m and greater than the next four gradients.
    20662185!--       WARNING: The threshold value of 0.2K/100m must be adjusted for the
    2067 !--       ocean case! 
     2186!--       ocean case!
    20682187          z_i(2) = 0.0_wp
    20692188          DO  k = nzb+1, nzt+1
     
    21262245
    21272246!
    2128 !--    Collect the time series quantities. Please note, timeseries quantities 
    2129 !--    which are collected from horizontally averaged profiles, e.g. wpt 
    2130 !--    or pt(zp), are treated specially. In case of elevated model surfaces, 
     2247!--    Collect the time series quantities. Please note, timeseries quantities
     2248!--    which are collected from horizontally averaged profiles, e.g. wpt
     2249!--    or pt(zp), are treated specially. In case of elevated model surfaces,
    21312250!--    index nzb+1 might be within topography and data will be zero. Therefore,
    2132 !--    take value for the first atmosphere index, which is topo_min_level+1. 
     2251!--    take value for the first atmosphere index, which is topo_min_level+1.
    21332252       ts_value(1,sr) = hom(nzb+4,1,pr_palm,sr)        ! E
    21342253       ts_value(2,sr) = hom(nzb+5,1,pr_palm,sr)        ! E*
  • 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
  • palm/trunk/SOURCE/time_integration.f90

    r4466 r4472  
    2020! Current revisions:
    2121! ------------------
    22 ! 
    23 ! 
     22!
     23!
    2424! Former revisions:
    2525! -----------------
    2626! $Id$
     27! OPENACC COPYIN directive for ddx and ddy added
     28!
     29! 4466 2020-03-20 16:14:41Z suehring
    2730! Add advection fluxes to ACC copyin
    2831!
     
    289292        ONLY:  flight_measurement
    290293
     294    USE grid_variables,                                                                            &
     295        ONLY:  ddx, ddy
     296
    291297    USE indices,                                                                                   &
    292298        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, nzb, nzt
     
    524530!$ACC DATA &
    525531!$ACC COPYIN(tsc(1:5))
     532
     533!
     534!-- Copy data from grid_variables
     535!$ACC DATA &
     536!$ACC COPYIN(ddx, ddy)
    526537
    527538!
     
    565576!$ACC COPY(sums_wsss_ws_l(nzb:nzt+1,0)) &
    566577!$ACC COPY(sums_salsa_ws_l(nzb:nzt+1,0))
     578
     579!
     580!-- Next statement is to avoid compiler warnings about unused variables. Please
     581!-- remove in case that you are using them. ddx and ddy need to be defined in
     582!-- time_integration because of ACC COPYIN directive.
     583    ddx = ddx
     584    ddy = ddy
    567585
    568586#if defined( _OPENACC )
     
    17271745!$ACC END DATA
    17281746!$ACC END DATA
     1747!$ACC END DATA
    17291748
    17301749#if defined( __parallel )
Note: See TracChangeset for help on using the changeset viewer.