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

files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

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

    r4536 r4559  
    11!> @file check_parameters.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    5 ! PALM is free software: you can redistribute it and/or modify it under the
    6 ! terms of the GNU General Public License as published by the Free Software
    7 ! Foundation, either version 3 of the License, or (at your option) any later
    8 ! version.
    9 !
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    11 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    12 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
    13 !
    14 ! You should have received a copy of the GNU General Public License along with
    15 ! PALM. If not, see <http://www.gnu.org/licenses/>.
     5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     6! Public License as published by the Free Software Foundation, either version 3 of the License, or
     7! (at your option) any later version.
     8!
     9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     11! Public License for more details.
     12!
     13! You should have received a copy of the GNU General Public License along with PALM. If not, see
     14! <http://www.gnu.org/licenses/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
     
    2524! -----------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4536 2020-05-17 17:24:13Z raasch
    2729! unneccessary query for restart data format removed
    28 ! 
     30!
    2931! 4534 2020-05-14 18:35:22Z raasch
    3032! adjustments for I/O on reduced number of cores using shared memory MPI
    31 ! 
     33!
    3234! 4514 2020-04-30 16:29:59Z suehring
    3335! Enable output of qsurf and ssurf
    34 ! 
     36!
    3537! 4513 2020-04-30 13:45:47Z raasch
    3638! unused modules removed
    37 ! 
     39!
    3840! 4511 2020-04-30 12:20:40Z raasch
    3941! call of chem_boundary_conds removed (respective settings are now done in the chemistry module)
    40 ! 
     42!
    4143! 4495 2020-04-13 20:11:20Z raasch
    4244! check new restart_data_format parameters
    43 ! 
     45!
    4446! 4493 2020-04-10 09:49:43Z pavelkrc
    4547! Kolmogorov length scale eta added to profile output
     
    134136! ------------
    135137!> Check control parameters and deduce further quantities.
    136 !------------------------------------------------------------------------------!
     138!--------------------------------------------------------------------------------------------------!
    137139 SUBROUTINE check_parameters
    138140
     
    142144    USE basic_constants_and_equations_mod
    143145
    144     USE bulk_cloud_model_mod,                                                  &
     146    USE bulk_cloud_model_mod,                                                                      &
    145147        ONLY:  bulk_cloud_model
    146148
     
    153155    USE indices
    154156
    155     USE model_1d_mod,                                                          &
     157    USE model_1d_mod,                                                                              &
    156158        ONLY:  damp_level_1d, damp_level_ind_1d
    157159
    158     USE module_interface,                                                      &
    159         ONLY:  module_interface_check_parameters,                              &
    160                module_interface_check_data_output_ts,                          &
    161                module_interface_check_data_output_pr,                          &
    162                module_interface_check_data_output
    163 
    164     USE netcdf_data_input_mod,                                                 &
    165         ONLY:  init_model, input_pids_static, netcdf_data_input_check_dynamic, &
     160    USE module_interface,                                                                          &
     161        ONLY:  module_interface_check_data_output,                                                 &
     162               module_interface_check_data_output_pr,                                              &
     163               module_interface_check_data_output_ts,                                              &
     164               module_interface_check_parameters
     165
     166    USE netcdf_data_input_mod,                                                                     &
     167        ONLY:  init_model, input_pids_static, netcdf_data_input_check_dynamic,                     &
    166168               netcdf_data_input_check_static
    167169
    168     USE netcdf_interface,                                                      &
    169         ONLY:  dopr_unit, do2d_unit, do3d_unit, netcdf_data_format,            &
    170                netcdf_data_format_string, dots_unit, heatflux_output_unit,     &
    171                waterflux_output_unit, momentumflux_output_unit,                &
    172                dots_max, dots_num, dots_label
    173 
    174     USE particle_attributes,                                                   &
     170    USE netcdf_interface,                                                                          &
     171        ONLY:  do2d_unit, do3d_unit, dopr_unit, dots_label, dots_max, dots_num, dots_unit,         &
     172               heatflux_output_unit, momentumflux_output_unit, netcdf_data_format,                 &
     173               netcdf_data_format_string, waterflux_output_unit
     174
     175    USE particle_attributes,                                                                       &
    175176        ONLY:  particle_advection, use_sgs_for_particles
    176177
    177178    USE pegrid
    178179
    179     USE pmc_interface,                                                         &
     180    USE pmc_interface,                                                                             &
    180181        ONLY:  cpl_id, nested_run
    181182
     
    189190
    190191#if defined( __parallel )
    191     USE vertical_nesting_mod,                                                  &
    192         ONLY:  vnested,                                                        &
     192    USE vertical_nesting_mod,                                                                      &
     193        ONLY:  vnested,                                                                            &
    193194               vnest_check_parameters
    194195#endif
     
    228229    CALL location_message( 'checking parameters', 'start' )
    229230!
    230 !-- At first, check static and dynamic input for consistency
     231!-- At first, check static and dynamic input for consistency.
    231232    CALL netcdf_data_input_check_dynamic
    232233    CALL netcdf_data_input_check_static
     
    240241!
    241242!-- Check the coupling mode
    242     IF ( coupling_mode /= 'uncoupled'            .AND.                         &
    243          coupling_mode /= 'precursor_atmos'      .AND.                         &
    244          coupling_mode /= 'precursor_ocean'      .AND.                         &
    245          coupling_mode /= 'vnested_crse'         .AND.                         &
    246          coupling_mode /= 'vnested_fine'         .AND.                         &
    247          coupling_mode /= 'atmosphere_to_ocean'  .AND.                         &
     243    IF ( coupling_mode /= 'uncoupled'            .AND.                                             &
     244         coupling_mode /= 'precursor_atmos'      .AND.                                             &
     245         coupling_mode /= 'precursor_ocean'      .AND.                                             &
     246         coupling_mode /= 'vnested_crse'         .AND.                                             &
     247         coupling_mode /= 'vnested_fine'         .AND.                                             &
     248         coupling_mode /= 'atmosphere_to_ocean'  .AND.                                             &
    248249         coupling_mode /= 'ocean_to_atmosphere' )  THEN
    249250       message_string = 'illegal coupling mode: ' // TRIM( coupling_mode )
     
    252253
    253254!
    254 !-- Check if humidity is set to TRUE in case of the atmospheric run (for coupled runs)
     255!-- Check if humidity is set to .TRUE. in case of the atmospheric run (for coupled runs)
    255256    IF ( coupling_mode == 'atmosphere_to_ocean' .AND. .NOT. humidity) THEN
    256        message_string = ' Humidity has to be set to .T. in the _p3d file ' //  &
     257       message_string = ' Humidity has to be set to .T. in the _p3d file ' //                      &
    257258                        'for coupled runs between ocean and atmosphere.'
    258259       CALL message( 'check_parameters', 'PA0476', 1, 2, 0, 6, 0 )
     
    297298!
    298299!-- Check dt_coupling, restart_time, dt_restart, end_time, dx, dy, nx and ny
    299     IF ( coupling_mode /= 'uncoupled'       .AND.                              &
    300          coupling_mode(1:8) /= 'vnested_'   .AND.                              &
    301          coupling_mode /= 'precursor_atmos' .AND.                              &
     300    IF ( coupling_mode /= 'uncoupled'        .AND.                                                 &
     301         coupling_mode(1:8) /= 'vnested_'    .AND.                                                 &
     302         coupling_mode /= 'precursor_atmos'  .AND.                                                 &
    302303         coupling_mode /= 'precursor_ocean' )  THEN
    303304
    304305       IF ( dt_coupling == 9999999.9_wp )  THEN
    305           message_string = 'dt_coupling is not set but required for coup' //   &
    306                            'ling mode "' //  TRIM( coupling_mode ) // '"'
     306          message_string = 'dt_coupling is not set but required for coupling mode "' //            &
     307                           TRIM( coupling_mode ) // '"'
    307308          CALL message( 'check_parameters', 'PA0003', 1, 2, 0, 6, 0 )
    308309       ENDIF
     
    312313
    313314       IF ( myid == 0 ) THEN
    314           CALL MPI_SEND( dt_coupling, 1, MPI_REAL, target_id, 11, comm_inter,  &
    315                          ierr )
    316           CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 11, comm_inter,       &
    317                          status, ierr )
     315          CALL MPI_SEND( dt_coupling, 1, MPI_REAL, target_id, 11, comm_inter, ierr )
     316          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 11, comm_inter, status, ierr )
    318317       ENDIF
    319318       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
    320319
    321320       IF ( dt_coupling /= remote )  THEN
    322           WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
    323                  '": dt_coupling = ', dt_coupling, '& is not equal to ',       &
    324                  'dt_coupling_remote = ', remote
     321          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), '": dt_coupling = ',&
     322                 dt_coupling, '& is not equal to ', 'dt_coupling_remote = ', remote
    325323          CALL message( 'check_parameters', 'PA0004', 1, 2, 0, 6, 0 )
    326324       ENDIF
     
    329327          IF ( myid == 0  ) THEN
    330328             CALL MPI_SEND( dt_max, 1, MPI_REAL, target_id, 19, comm_inter, ierr )
    331              CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 19, comm_inter,    &
    332                             status, ierr )
     329             CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 19, comm_inter, status, ierr )
    333330          ENDIF
    334331          CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
    335332
    336333          dt_coupling = MAX( dt_max, remote )
    337           WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
    338                  '": dt_coupling <= 0.0 & is not allowed and is reset to ',   &
    339                  'MAX(dt_max(A,O)) = ', dt_coupling
     334          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ),                     &
     335                 '": dt_coupling <= 0.0 & is not allowed and is reset to ', 'MAX(dt_max(A,O)) = ', &
     336                 dt_coupling
    340337          CALL message( 'check_parameters', 'PA0005', 0, 1, 0, 6, 0 )
    341338       ENDIF
    342339
    343340       IF ( myid == 0 ) THEN
    344           CALL MPI_SEND( restart_time, 1, MPI_REAL, target_id, 12, comm_inter, &
    345                          ierr )
    346           CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 12, comm_inter,       &
    347                          status, ierr )
     341          CALL MPI_SEND( restart_time, 1, MPI_REAL, target_id, 12, comm_inter, ierr )
     342          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 12, comm_inter, status, ierr )
    348343       ENDIF
    349344       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
    350345
    351346       IF ( restart_time /= remote )  THEN
    352           WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
    353                  '": restart_time = ', restart_time, '& is not equal to ',     &
     347          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ),                     &
     348                 '": restart_time = ', restart_time, '& is not equal to ',                         &
    354349                 'restart_time_remote = ', remote
    355350          CALL message( 'check_parameters', 'PA0006', 1, 2, 0, 6, 0 )
     
    357352
    358353       IF ( myid == 0 ) THEN
    359           CALL MPI_SEND( dt_restart, 1, MPI_REAL, target_id, 13, comm_inter,   &
    360                          ierr )
    361           CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 13, comm_inter,       &
    362                          status, ierr )
     354          CALL MPI_SEND( dt_restart, 1, MPI_REAL, target_id, 13, comm_inter, ierr )
     355          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 13, comm_inter, status, ierr )
    363356       ENDIF
    364357       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
    365358
    366359       IF ( dt_restart /= remote )  THEN
    367           WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
    368                  '": dt_restart = ', dt_restart, '& is not equal to ',         &
    369                  'dt_restart_remote = ', remote
     360          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), '": dt_restart = ', &
     361                 dt_restart, '& is not equal to ', 'dt_restart_remote = ', remote
    370362          CALL message( 'check_parameters', 'PA0007', 1, 2, 0, 6, 0 )
    371363       ENDIF
     
    373365       time_to_be_simulated_from_reference_point = end_time-coupling_start_time
    374366
    375        IF  ( myid == 0 ) THEN
    376           CALL MPI_SEND( time_to_be_simulated_from_reference_point, 1,         &
    377                          MPI_REAL, target_id, 14, comm_inter, ierr )
    378           CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 14, comm_inter,       &
    379                          status, ierr )
     367       IF ( myid == 0 ) THEN
     368          CALL MPI_SEND( time_to_be_simulated_from_reference_point, 1, MPI_REAL, target_id, 14,    &
     369                         comm_inter, ierr )
     370          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 14, comm_inter, status, ierr )
    380371       ENDIF
    381372       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
    382373
    383374       IF ( time_to_be_simulated_from_reference_point /= remote )  THEN
    384           WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
    385                  '": time_to_be_simulated_from_reference_point = ',            &
    386                  time_to_be_simulated_from_reference_point, '& is not equal ', &
    387                  'to time_to_be_simulated_from_reference_point_remote = ',     &
     375          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ),                     &
     376                 '": time_to_be_simulated_from_reference_point = ',                                &
     377                 time_to_be_simulated_from_reference_point, '& is not equal ',                     &
     378                 'to time_to_be_simulated_from_reference_point_remote = ',                         &
    388379                 remote
    389380          CALL message( 'check_parameters', 'PA0008', 1, 2, 0, 6, 0 )
     
    392383       IF ( myid == 0 ) THEN
    393384          CALL MPI_SEND( dx, 1, MPI_REAL, target_id, 15, comm_inter, ierr )
    394           CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 15, comm_inter,       &
    395                                                              status, ierr )
     385          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 15, comm_inter, status, ierr )
    396386       ENDIF
    397387       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
     
    401391
    402392          IF ( dx < remote ) THEN
    403              WRITE( message_string, * ) 'coupling mode "',                     &
    404                    TRIM( coupling_mode ),                                      &
    405            '": dx in Atmosphere is not equal to or not larger than dx in ocean'
     393             WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ),                  &
     394                    '": dx in Atmosphere is not equal to or not larger than dx in ocean'
    406395             CALL message( 'check_parameters', 'PA0009', 1, 2, 0, 6, 0 )
    407396          ENDIF
    408397
    409398          IF ( (nx_a+1)*dx /= (nx_o+1)*remote )  THEN
    410              WRITE( message_string, * ) 'coupling mode "',                     &
    411                     TRIM( coupling_mode ),                                     &
    412              '": Domain size in x-direction is not equal in ocean and atmosphere'
     399             WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ),                  &
     400                    '": Domain size in x-direction is not equal in ocean and atmosphere'
    413401             CALL message( 'check_parameters', 'PA0010', 1, 2, 0, 6, 0 )
    414402          ENDIF
     
    418406       IF ( myid == 0) THEN
    419407          CALL MPI_SEND( dy, 1, MPI_REAL, target_id, 16, comm_inter, ierr )
    420           CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 16, comm_inter,       &
    421                          status, ierr )
     408          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 16, comm_inter, status, ierr )
    422409       ENDIF
    423410       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
     
    426413
    427414          IF ( dy < remote )  THEN
    428              WRITE( message_string, * ) 'coupling mode "',                     &
    429                     TRIM( coupling_mode ),                                     &
    430                  '": dy in Atmosphere is not equal to or not larger than dy in ocean'
     415             WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ),                  &
     416                    '": dy in Atmosphere is not equal to or not larger than dy in ocean'
    431417             CALL message( 'check_parameters', 'PA0011', 1, 2, 0, 6, 0 )
    432418          ENDIF
    433419
    434420          IF ( (ny_a+1)*dy /= (ny_o+1)*remote )  THEN
    435              WRITE( message_string, * ) 'coupling mode "',                     &
    436                    TRIM( coupling_mode ),                                      &
    437              '": Domain size in y-direction is not equal in ocean and atmosphere'
     421             WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ),                  &
     422                    '": Domain size in y-direction is not equal in ocean and atmosphere'
    438423             CALL message( 'check_parameters', 'PA0012', 1, 2, 0, 6, 0 )
    439424          ENDIF
    440425
    441           IF ( MOD(nx_o+1,nx_a+1) /= 0 )  THEN
    442              WRITE( message_string, * ) 'coupling mode "',                     &
    443                    TRIM( coupling_mode ),                                      &
    444              '": nx+1 in ocean is not divisible by nx+1 in',                   &
    445              ' atmosphere without remainder'
     426          IF ( MOD( nx_o+1, nx_a+1 ) /= 0 )  THEN
     427             WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ),                  &
     428                    '": nx+1 in ocean is not divisible by nx+1 in', ' atmosphere without remainder'
    446429             CALL message( 'check_parameters', 'PA0339', 1, 2, 0, 6, 0 )
    447430          ENDIF
    448431
    449432          IF ( MOD(ny_o+1,ny_a+1) /= 0 )  THEN
    450              WRITE( message_string, * ) 'coupling mode "',                     &
    451                    TRIM( coupling_mode ),                                      &
    452              '": ny+1 in ocean is not divisible by ny+1 in', &
    453              ' atmosphere without remainder'
     433             WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ),                  &
     434                    '": ny+1 in ocean is not divisible by ny+1 in', ' atmosphere without remainder'
    454435
    455436             CALL message( 'check_parameters', 'PA0340', 1, 2, 0, 6, 0 )
     
    458439       ENDIF
    459440#else
    460        WRITE( message_string, * ) 'coupling requires PALM to be compiled with',&
    461             ' cpp-option "-D__parallel"'
     441       WRITE( message_string, * ) 'coupling requires PALM to be compiled with',                    &
     442              ' cpp-option "-D__parallel"'
    462443       CALL message( 'check_parameters', 'PA0141', 1, 2, 0, 6, 0 )
    463444#endif
     
    467448!
    468449!-- Exchange via intercommunicator
    469     IF ( coupling_mode == 'atmosphere_to_ocean' .AND. myid == 0 )  THEN
    470        CALL MPI_SEND( humidity, 1, MPI_LOGICAL, target_id, 19, comm_inter,     &
    471                       ierr )
    472     ELSEIF ( coupling_mode == 'ocean_to_atmosphere' .AND. myid == 0)  THEN
    473        CALL MPI_RECV( humidity_remote, 1, MPI_LOGICAL, target_id, 19,          &
    474                       comm_inter, status, ierr )
     450    IF ( coupling_mode == 'atmosphere_to_ocean'  .AND.  myid == 0 )  THEN
     451       CALL MPI_SEND( humidity, 1, MPI_LOGICAL, target_id, 19, comm_inter, ierr )
     452    ELSEIF ( coupling_mode == 'ocean_to_atmosphere'  .AND.  myid == 0)  THEN
     453       CALL MPI_RECV( humidity_remote, 1, MPI_LOGICAL, target_id, 19, comm_inter, status, ierr )
    475454    ENDIF
    476455    CALL MPI_BCAST( humidity_remote, 1, MPI_LOGICAL, 0, comm2d, ierr)
     
    479458
    480459!
    481 !-- User settings for restart times requires that "restart" has been given as
    482 !-- file activation string. Otherwise, binary output would not be saved by
    483 !-- palmrun.
    484     IF (  ( restart_time /= 9999999.9_wp  .OR.  dt_restart /= 9999999.9_wp )   &
     460!-- User settings for restart times requires that "restart" has been given as file activation
     461!-- string. Otherwise, binary output would not be saved by palmrun.
     462    IF ( ( restart_time /= 9999999.9_wp  .OR.  dt_restart /= 9999999.9_wp )                        &
    485463         .AND.  .NOT. write_binary )  THEN
    486        WRITE( message_string, * ) 'manual restart settings requires file ',    &
     464       WRITE( message_string, * ) 'manual restart settings requires file ',                        &
    487465                                  'activation string "restart"'
    488466       CALL message( 'check_parameters', 'PA0001', 1, 2, 0, 6, 0 )
     
    491469
    492470!
    493 !-- Generate the file header which is used as a header for most of PALM's
    494 !-- output files
     471!-- Generate the file header which is used as a header for most of PALM's output files
    495472    CALL DATE_AND_TIME( date, time, run_zone )
    496     run_date = date(1:4)//'-'//date(5:6)//'-'//date(7:8)
    497     run_time = time(1:2)//':'//time(3:4)//':'//time(5:6)
     473    run_date = date(1:4) // '-' // date(5:6) // '-' // date(7:8)
     474    run_time = time(1:2) // ':' // time(3:4) // ':' // time(5:6)
    498475    IF ( coupling_mode == 'uncoupled' )  THEN
    499476       coupling_string = ''
     
    518495    ENDIF
    519496
    520     WRITE ( run_description_header,                                            &
    521             '(A,2X,A,2X,A,A,A,I2.2,A,A,A,2X,A,A,2X,A,1X,A)' )                  &
    522           TRIM( version ), TRIM( revision ), 'run: ',                          &
    523           TRIM( run_identifier ), '.', runnr, TRIM( coupling_string ),         &
    524           TRIM( nest_string ), TRIM( ensemble_string), 'host: ', TRIM( host ), &
    525           run_date, run_time
     497    WRITE ( run_description_header, '(A,2X,A,2X,A,A,A,I2.2,A,A,A,2X,A,A,2X,A,1X,A)' )              &
     498          TRIM( version ), TRIM( revision ), 'run: ', TRIM( run_identifier ), '.', runnr,          &
     499          TRIM( coupling_string ), TRIM( nest_string ), TRIM( ensemble_string), 'host: ',          &
     500          TRIM( host ), run_date, run_time
    526501
    527502!
     
    533508
    534509       CASE DEFAULT
    535           message_string = 'illegal value given for loop_optimization: "' //   &
     510          message_string = 'illegal value given for loop_optimization: "' //                       &
    536511                           TRIM( loop_optimization ) // '"'
    537512          CALL message( 'check_parameters', 'PA0013', 1, 2, 0, 6, 0 )
     
    543518    IF ( topography /= 'flat' )  THEN
    544519       action = ' '
    545        IF ( scalar_advec /= 'pw-scheme' .AND. scalar_advec /= 'ws-scheme'      &
    546           )  THEN
     520       IF ( scalar_advec /= 'pw-scheme'  .AND.  scalar_advec /= 'ws-scheme' )  THEN
    547521          WRITE( action, '(A,A)' )  'scalar_advec = ', scalar_advec
    548522       ENDIF
    549        IF ( momentum_advec /= 'pw-scheme' .AND. momentum_advec /= 'ws-scheme' )&
    550        THEN
     523       IF ( momentum_advec /= 'pw-scheme'  .AND.  momentum_advec /= 'ws-scheme' )  THEN
    551524          WRITE( action, '(A,A)' )  'momentum_advec = ', momentum_advec
    552525       ENDIF
     
    563536          WRITE( action, '(A)' )  'cloud_droplets = .TRUE.'
    564537       ENDIF
    565        IF ( .NOT. constant_flux_layer .AND. topography /= 'closed_channel' )   &
    566        THEN
     538       IF ( .NOT. constant_flux_layer  .AND.  topography /= 'closed_channel' )  THEN
    567539          WRITE( action, '(A)' )  'constant_flux_layer = .FALSE.'
    568540       ENDIF
    569541       IF ( action /= ' ' )  THEN
    570           message_string = 'The specified topography does not allow ' //       &
    571                            TRIM( action )
     542          message_string = 'The specified topography does not allow ' // TRIM( action )
    572543          CALL message( 'check_parameters', 'PA0014', 1, 2, 0, 6, 0 )
    573544       ENDIF
    574545!
    575546!--    Check illegal/untested parameter combinations for closed channel
    576        If ( topography == 'closed_channel' ) THEN
     547       If ( topography == 'closed_channel' )  THEN
    577548          symmetry_flag = 1
    578549          message_string = 'Bottom and top boundary are treated equal'
    579550          CALL message( 'check_parameters', 'PA0699', 0, 0, 0, 6, 0 )
    580551
    581           IF ( dz(1) /= dz(COUNT( dz /= -1.0_wp )) .OR.                        &
    582                dz_stretch_level /= -9999999.9_wp) THEN
    583              WRITE( message_string, * )  'dz should be equal close to the ' // &
     552          IF ( dz(1) /= dz(COUNT( dz /= -1.0_wp ))  .OR.  dz_stretch_level /= -9999999.9_wp)  THEN
     553             WRITE( message_string, * )  'dz should be equal close to the ' //                     &
    584554                                         'boundaries due to symmetrical problem'
    585555             CALL message( 'check_parameters', 'PA0700', 1, 2, 0, 6, 0 )
    586556          ENDIF
    587557
    588           IF ( constant_flux_layer ) THEN
    589              WRITE( message_string, * )  'A constant flux layer is not '//     &
    590                                          'allowed if a closed channel '//      &
    591                                          'shall be used'
     558          IF ( constant_flux_layer )  THEN
     559             WRITE( message_string, * )  'A constant flux layer is not ' //                        &
     560                                         'allowed if a closed channel shall be used'
    592561             CALL message( 'check_parameters', 'PA0701', 1, 2, 0, 6, 0 )
    593562          ENDIF
    594563
    595           IF ( ocean_mode ) THEN
    596              WRITE( message_string, * )  'The ocean mode is not allowed if '// &
     564          IF ( ocean_mode )  THEN
     565             WRITE( message_string, * )  'The ocean mode is not allowed if ' //                    &
    597566                                         'a closed channel shall be used'
    598567             CALL message( 'check_parameters', 'PA0702', 1, 2, 0, 6, 0 )
    599568          ENDIF
    600569
    601           IF ( momentum_advec /= 'ws-scheme' .OR.                              &
    602                scalar_advec /= 'ws-scheme' ) THEN
    603              WRITE( message_string, * )  'A closed channel require the '//     &
    604                                          'upwind scheme of Wicker and ' //     &
    605                                          'Skamarock as the advection scheme'
     570          IF ( momentum_advec /= 'ws-scheme'  .OR.                                                 &
     571               scalar_advec /= 'ws-scheme' )  THEN
     572             WRITE( message_string, * )  'A closed channel require the upwind scheme of Wicker' // &
     573                                         ' and Skamarock as the advection scheme'
    606574             CALL message( 'check_parameters', 'PA0703', 1, 2, 0, 6, 0 )
    607575          ENDIF
     
    611579!
    612580!-- Check approximation
    613     IF ( TRIM( approximation ) /= 'boussinesq'   .AND.                         &
    614          TRIM( approximation ) /= 'anelastic' )  THEN
    615        message_string = 'unknown approximation: approximation = "' //          &
    616                         TRIM( approximation ) // '"'
     581    IF ( TRIM( approximation ) /= 'boussinesq'  .AND.  TRIM( approximation ) /= 'anelastic' )  THEN
     582       message_string = 'unknown approximation: approximation = "' // TRIM( approximation ) // '"'
    617583       CALL message( 'check_parameters', 'PA0446', 1, 2, 0, 6, 0 )
    618584    ENDIF
     
    620586!
    621587!-- Check approximation requirements
    622     IF ( TRIM( approximation ) == 'anelastic'   .AND.                          &
    623          TRIM( momentum_advec ) /= 'ws-scheme' )  THEN
    624        message_string = 'Anelastic approximation requires ' //                 &
    625                         'momentum_advec = "ws-scheme"'
     588    IF ( TRIM( approximation ) == 'anelastic'  .AND.  TRIM( momentum_advec ) /= 'ws-scheme' )  THEN
     589       message_string = 'Anelastic approximation requires momentum_advec = "ws-scheme"'
    626590       CALL message( 'check_parameters', 'PA0447', 1, 2, 0, 6, 0 )
    627591    ENDIF
    628     IF ( TRIM( approximation ) == 'anelastic'   .AND.                          &
    629          TRIM( psolver ) == 'multigrid' )  THEN
    630        message_string = 'Anelastic approximation currently only supports ' //  &
    631                         'psolver = "poisfft", ' //                             &
    632                         'psolver = "sor" and ' //                              &
    633                         'psolver = "multigrid_noopt"'
     592    IF ( TRIM( approximation ) == 'anelastic'  .AND.  TRIM( psolver ) == 'multigrid' )  THEN
     593       message_string = 'Anelastic approximation currently only supports psolver = "poisfft", ' // &
     594                        'psolver = "sor" and psolver = "multigrid_noopt"'
    634595       CALL message( 'check_parameters', 'PA0448', 1, 2, 0, 6, 0 )
    635596    ENDIF
    636     IF ( TRIM( approximation ) == 'anelastic'   .AND.                          &
    637          conserve_volume_flow )  THEN
    638        message_string = 'Anelastic approximation is not allowed with ' //      &
     597    IF ( TRIM( approximation ) == 'anelastic'  .AND.  conserve_volume_flow )  THEN
     598       message_string = 'Anelastic approximation is not allowed with ' //                          &
    639599                        'conserve_volume_flow = .TRUE.'
    640600       CALL message( 'check_parameters', 'PA0449', 1, 2, 0, 6, 0 )
     
    643603!
    644604!-- Check flux input mode
    645     IF ( TRIM( flux_input_mode ) /= 'dynamic'    .AND.                         &
    646          TRIM( flux_input_mode ) /= 'kinematic'  .AND.                         &
    647          TRIM( flux_input_mode ) /= 'approximation-specific' )  THEN
    648        message_string = 'unknown flux input mode: flux_input_mode = "' //      &
     605    IF ( TRIM( flux_input_mode ) /= 'dynamic'  .AND.  TRIM( flux_input_mode ) /= 'kinematic'       &
     606         .AND.  TRIM( flux_input_mode ) /= 'approximation-specific' )  THEN
     607       message_string = 'unknown flux input mode: flux_input_mode = "' //                          &
    649608                        TRIM( flux_input_mode ) // '"'
    650609       CALL message( 'check_parameters', 'PA0450', 1, 2, 0, 6, 0 )
     
    662621!
    663622!-- Check flux output mode
    664     IF ( TRIM( flux_output_mode ) /= 'dynamic'    .AND.                        &
    665          TRIM( flux_output_mode ) /= 'kinematic'  .AND.                        &
    666          TRIM( flux_output_mode ) /= 'approximation-specific' )  THEN
    667        message_string = 'unknown flux output mode: flux_output_mode = "' //    &
     623    IF ( TRIM( flux_output_mode ) /= 'dynamic'  .AND.  TRIM( flux_output_mode ) /= 'kinematic'     &
     624         .AND.  TRIM( flux_output_mode ) /= 'approximation-specific' )  THEN
     625       message_string = 'unknown flux output mode: flux_output_mode = "' //                        &
    668626                        TRIM( flux_output_mode ) // '"'
    669627       CALL message( 'check_parameters', 'PA0451', 1, 2, 0, 6, 0 )
     
    681639
    682640!
    683 !-- When the land- or urban-surface model is used, the flux output must be
    684 !-- dynamic.
     641!-- When the land- or urban-surface model is used, the flux output must be dynamic.
    685642    IF ( land_surface  .OR.  urban_surface )  THEN
    686643       flux_output_mode = 'dynamic'
     
    689646!
    690647!-- Set the flux output units according to flux_output_mode
    691     IF ( TRIM( flux_output_mode ) == 'kinematic' ) THEN
     648    IF ( TRIM( flux_output_mode ) == 'kinematic' )  THEN
    692649        heatflux_output_unit              = 'K m/s'
    693650        waterflux_output_unit             = 'kg/kg m/s'
    694651        momentumflux_output_unit          = 'm2/s2'
    695     ELSEIF ( TRIM( flux_output_mode ) == 'dynamic' ) THEN
     652    ELSEIF ( TRIM( flux_output_mode ) == 'dynamic' )  THEN
    696653        heatflux_output_unit              = 'W/m2'
    697654        waterflux_output_unit             = 'W/m2'
     
    712669!-- Check if maximum number of allowed timeseries is exceeded
    713670    IF ( dots_num > dots_max )  THEN
    714        WRITE( message_string, * ) 'number of time series quantities exceeds',  &
    715                                   ' its maximum of dots_max = ', dots_max,     &
     671       WRITE( message_string, * ) 'number of time series quantities exceeds',                      &
     672                                  ' its maximum of dots_max = ', dots_max,                         &
    716673                                  '&Please increase dots_max in modules.f90.'
    717674       CALL message( 'init_3d_model', 'PA0194', 1, 2, 0, 6, 0 )
     
    721678!-- Check whether there are any illegal values
    722679!-- Pressure solver:
    723     IF ( psolver /= 'poisfft'  .AND.  psolver /= 'sor'  .AND.                  &
    724          psolver /= 'multigrid'  .AND.  psolver /= 'multigrid_noopt' )  THEN
    725        message_string = 'unknown solver for perturbation pressure: psolver' // &
     680    IF ( psolver /= 'poisfft'  .AND.  psolver /= 'sor'  .AND.  psolver /= 'multigrid'  .AND.       &
     681         psolver /= 'multigrid_noopt' )  THEN
     682       message_string = 'unknown solver for perturbation pressure: psolver' //                     &
    726683                        ' = "' // TRIM( psolver ) // '"'
    727684       CALL message( 'check_parameters', 'PA0016', 1, 2, 0, 6, 0 )
     
    734691          gamma_mg = 1
    735692       ELSE
    736           message_string = 'unknown multigrid cycle: cycle_mg = "' //          &
    737                            TRIM( cycle_mg ) // '"'
     693          message_string = 'unknown multigrid cycle: cycle_mg = "' //  TRIM( cycle_mg ) // '"'
    738694          CALL message( 'check_parameters', 'PA0020', 1, 2, 0, 6, 0 )
    739695       ENDIF
    740696    ENDIF
    741697
    742     IF ( fft_method /= 'singleton-algorithm'  .AND.                            &
    743          fft_method /= 'temperton-algorithm'  .AND.                            &
    744          fft_method /= 'fftw'                 .AND.                            &
    745          fft_method /= 'system-specific' )  THEN
    746        message_string = 'unknown fft-algorithm: fft_method = "' //             &
    747                         TRIM( fft_method ) // '"'
     698    IF ( fft_method /= 'singleton-algorithm'  .AND.  fft_method /= 'temperton-algorithm'  .AND.    &
     699         fft_method /= 'fftw'                 .AND.  fft_method /= 'system-specific' )  THEN
     700       message_string = 'unknown fft-algorithm: fft_method = "' // TRIM( fft_method ) // '"'
    748701       CALL message( 'check_parameters', 'PA0021', 1, 2, 0, 6, 0 )
    749702    ENDIF
    750703
    751     IF( momentum_advec == 'ws-scheme' .AND.                                    &
    752         .NOT. call_psolver_at_all_substeps  ) THEN
    753         message_string = 'psolver must be called at each RK3 substep when "'// &
    754                       TRIM(momentum_advec) // ' "is used for momentum_advec'
     704    IF( momentum_advec == 'ws-scheme' .AND.  .NOT. call_psolver_at_all_substeps  ) THEN
     705        message_string = 'psolver must be called at each RK3 substep when "'//                     &
     706                         TRIM(momentum_advec) // ' "is used for momentum_advec'
    755707        CALL message( 'check_parameters', 'PA0344', 1, 2, 0, 6, 0 )
    756708    END IF
    757709!
    758710!-- Advection schemes:
    759     IF ( momentum_advec /= 'pw-scheme'  .AND.                                  &
    760          momentum_advec /= 'ws-scheme'  .AND.                                  &
    761          momentum_advec /= 'up-scheme' )                                       &
    762     THEN
    763        message_string = 'unknown advection scheme: momentum_advec = "' //      &
     711    IF ( momentum_advec /= 'pw-scheme'  .AND.  momentum_advec /= 'ws-scheme'  .AND.                &
     712         momentum_advec /= 'up-scheme' )  THEN
     713       message_string = 'unknown advection scheme: momentum_advec = "' //                          &
    764714                        TRIM( momentum_advec ) // '"'
    765715       CALL message( 'check_parameters', 'PA0022', 1, 2, 0, 6, 0 )
    766716    ENDIF
    767     IF ( ( momentum_advec == 'ws-scheme' .OR.  scalar_advec == 'ws-scheme' )   &
    768            .AND. ( timestep_scheme == 'euler' .OR.                             &
    769                    timestep_scheme == 'runge-kutta-2' ) )                      &
    770     THEN
    771        message_string = 'momentum_advec or scalar_advec = "'                   &
    772          // TRIM( momentum_advec ) // '" is not allowed with ' //              &
    773          'timestep_scheme = "' // TRIM( timestep_scheme ) // '"'
     717    IF ( ( momentum_advec == 'ws-scheme' .OR. scalar_advec == 'ws-scheme' )                        &
     718         .AND. ( timestep_scheme == 'euler' .OR.  timestep_scheme == 'runge-kutta-2' ) )  THEN
     719       message_string = 'momentum_advec or scalar_advec = "' // TRIM( momentum_advec ) //          &
     720                        '" is not allowed with timestep_scheme = "' //                             &
     721                        TRIM( timestep_scheme ) // '"'
    774722       CALL message( 'check_parameters', 'PA0023', 1, 2, 0, 6, 0 )
    775723    ENDIF
    776     IF ( scalar_advec /= 'pw-scheme'  .AND.  scalar_advec /= 'ws-scheme' .AND. &
    777          scalar_advec /= 'bc-scheme' .AND. scalar_advec /= 'up-scheme' )       &
    778     THEN
    779        message_string = 'unknown advection scheme: scalar_advec = "' //        &
    780                         TRIM( scalar_advec ) // '"'
     724    IF ( scalar_advec /= 'pw-scheme'  .AND.  scalar_advec /= 'ws-scheme'  .AND.                    &
     725         scalar_advec /= 'bc-scheme'  .AND.  scalar_advec /= 'up-scheme' )  THEN
     726       message_string = 'unknown advection scheme: scalar_advec = "' // TRIM( scalar_advec ) // '"'
    781727       CALL message( 'check_parameters', 'PA0024', 1, 2, 0, 6, 0 )
    782728    ENDIF
    783     IF ( scalar_advec == 'bc-scheme'  .AND.  loop_optimization == 'cache' )    &
    784     THEN
    785        message_string = 'advection_scheme scalar_advec = "'                    &
    786          // TRIM( scalar_advec ) // '" not implemented for ' //                &
    787          'loop_optimization = "' // TRIM( loop_optimization ) // '"'
     729    IF ( scalar_advec == 'bc-scheme'  .AND.  loop_optimization == 'cache' )  THEN
     730       message_string = 'advection_scheme scalar_advec = "' // TRIM( scalar_advec ) //             &
     731                        '" not implemented for loop_optimization = "' //                           &
     732                        TRIM( loop_optimization ) // '"'
    788733       CALL message( 'check_parameters', 'PA0026', 1, 2, 0, 6, 0 )
    789734    ENDIF
    790735
    791     IF ( use_sgs_for_particles  .AND.  .NOT. cloud_droplets  .AND.             &
    792          .NOT. use_upstream_for_tke  .AND.                                     &
    793          scalar_advec /= 'ws-scheme'                                           &
    794        )  THEN
     736    IF ( use_sgs_for_particles  .AND.  .NOT. cloud_droplets  .AND.  .NOT. use_upstream_for_tke     &
     737         .AND.  scalar_advec /= 'ws-scheme' )  THEN
    795738       use_upstream_for_tke = .TRUE.
    796        message_string = 'use_upstream_for_tke is set to .TRUE. because ' //    &
    797                         'use_sgs_for_particles = .TRUE. '          //          &
    798                         'and scalar_advec /= ws-scheme'
     739       message_string = 'use_upstream_for_tke is set to .TRUE. because ' //                        &
     740                        'use_sgs_for_particles = .TRUE. and scalar_advec /= ws-scheme'
    799741       CALL message( 'check_parameters', 'PA0025', 0, 1, 0, 6, 0 )
    800742    ENDIF
     
    820762
    821763       CASE DEFAULT
    822           message_string = 'unknown timestep scheme: timestep_scheme = "' //   &
     764          message_string = 'unknown timestep scheme: timestep_scheme = "' //                       &
    823765                           TRIM( timestep_scheme ) // '"'
    824766          CALL message( 'check_parameters', 'PA0027', 1, 2, 0, 6, 0 )
     
    826768    END SELECT
    827769
    828     IF ( (momentum_advec /= 'pw-scheme' .AND. momentum_advec /= 'ws-scheme')   &
    829          .AND. timestep_scheme(1:5) == 'runge' ) THEN
    830        message_string = 'momentum advection scheme "' // &
    831                         TRIM( momentum_advec ) // '" & does not work with ' // &
    832                         'timestep_scheme "' // TRIM( timestep_scheme ) // '"'
     770    IF ( ( momentum_advec /= 'pw-scheme' .AND. momentum_advec /= 'ws-scheme' )                     &
     771         .AND.  timestep_scheme(1:5) == 'runge' ) THEN
     772       message_string = 'momentum advection scheme "' // TRIM( momentum_advec ) //                 &
     773                        '" & does not work with timestep_scheme "' // TRIM( timestep_scheme )      &
     774                        // '"'
    833775       CALL message( 'check_parameters', 'PA0029', 1, 2, 0, 6, 0 )
    834776    ENDIF
     
    836778!-- Check for proper settings for microphysics
    837779    IF ( bulk_cloud_model  .AND.  cloud_droplets )  THEN
    838        message_string = 'bulk_cloud_model = .TRUE. is not allowed with ' //    &
    839                         'cloud_droplets = .TRUE.'
     780       message_string = 'bulk_cloud_model = .TRUE. is not allowed with cloud_droplets = .TRUE.'
    840781       CALL message( 'check_parameters', 'PA0442', 1, 2, 0, 6, 0 )
    841782    ENDIF
     
    848789    ENDIF
    849790
    850     IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.            &
     791    IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.                                &
    851792         TRIM( initializing_actions ) /= 'cyclic_fill' )  THEN
    852793!
     
    857798          SELECT CASE ( action(1:position-1) )
    858799
    859              CASE ( 'set_constant_profiles', 'set_1d-model_profiles',          &
    860                     'by_user', 'initialize_vortex', 'initialize_ptanom',       &
    861                     'initialize_bubble', 'inifor' )
     800             CASE ( 'set_constant_profiles', 'set_1d-model_profiles', 'by_user',                   &
     801                    'initialize_vortex', 'initialize_ptanom', 'initialize_bubble', 'inifor' )
    862802                action = action(position+1:)
    863803
    864804             CASE DEFAULT
    865                 message_string = 'initializing_action = "' //                  &
     805                message_string = 'initializing_action = "' //                                      &
    866806                                 TRIM( action ) // '" unknown or not allowed'
    867807                CALL message( 'check_parameters', 'PA0030', 1, 2, 0, 6, 0 )
     
    871811    ENDIF
    872812
    873     IF ( TRIM( initializing_actions ) == 'initialize_vortex'  .AND.            &
    874          conserve_volume_flow ) THEN
    875          message_string = 'initializing_actions = "initialize_vortex"' //      &
    876                         ' is not allowed with conserve_volume_flow = .T.'
     813    IF ( TRIM( initializing_actions ) == 'initialize_vortex'  .AND.  conserve_volume_flow ) THEN
     814         message_string = 'initializing_actions = "initialize_vortex"' //                          &
     815                          ' is not allowed with conserve_volume_flow = .T.'
    877816       CALL message( 'check_parameters', 'PA0343', 1, 2, 0, 6, 0 )
    878817    ENDIF
    879818
    880819
    881     IF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0  .AND.    &
     820    IF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0  .AND.                        &
    882821         INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
    883        message_string = 'initializing_actions = "set_constant_profiles"' //    &
    884                         ' and "set_1d-model_profiles" are not allowed ' //     &
    885                         'simultaneously'
     822       message_string = 'initializing_actions = "set_constant_profiles"' //                        &
     823                        ' and "set_1d-model_profiles" are not allowed simultaneously'
    886824       CALL message( 'check_parameters', 'PA0031', 1, 2, 0, 6, 0 )
    887825    ENDIF
    888826
    889     IF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0  .AND.    &
     827    IF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0  .AND.                        &
    890828         INDEX( initializing_actions, 'by_user' ) /= 0 )  THEN
    891        message_string = 'initializing_actions = "set_constant_profiles"' //    &
     829       message_string = 'initializing_actions = "set_constant_profiles"' //                        &
    892830                        ' and "by_user" are not allowed simultaneously'
    893831       CALL message( 'check_parameters', 'PA0032', 1, 2, 0, 6, 0 )
    894832    ENDIF
    895833
    896     IF ( INDEX( initializing_actions, 'by_user' ) /= 0  .AND.                  &
     834    IF ( INDEX( initializing_actions, 'by_user' ) /= 0  .AND.                                      &
    897835         INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
    898        message_string = 'initializing_actions = "by_user" and ' //             &
     836       message_string = 'initializing_actions = "by_user" and ' //                                 &
    899837                        '"set_1d-model_profiles" are not allowed simultaneously'
    900838       CALL message( 'check_parameters', 'PA0033', 1, 2, 0, 6, 0 )
    901839    ENDIF
    902840!
    903 !-- In case of spinup and nested run, spinup end time must be identical
    904 !-- in order to have synchronously running simulations.
     841!-- In case of spinup and nested run, spinup end time must be identical in order to have
     842!-- synchronously running simulations.
    905843    IF ( nested_run )  THEN
    906844#if defined( __parallel )
    907        CALL MPI_ALLREDUCE( spinup_time, spinup_time_max, 1, MPI_REAL,          &
    908                            MPI_MAX, MPI_COMM_WORLD, ierr )
    909        CALL MPI_ALLREDUCE( dt_spinup,   dt_spinup_max,   1, MPI_REAL,          &
    910                            MPI_MAX, MPI_COMM_WORLD, ierr )
    911 
    912        IF ( spinup_time /= spinup_time_max  .OR.  dt_spinup /= dt_spinup_max ) &
    913        THEN
    914           message_string = 'In case of nesting, spinup_time and ' //           &
    915                            'dt_spinup must be identical in all parent ' //     &
    916                            'and child domains.'
     845       CALL MPI_ALLREDUCE( spinup_time, spinup_time_max, 1, MPI_REAL, MPI_MAX, MPI_COMM_WORLD,     &
     846                           ierr )
     847       CALL MPI_ALLREDUCE( dt_spinup,   dt_spinup_max,   1, MPI_REAL, MPI_MAX, MPI_COMM_WORLD,     &
     848                           ierr )
     849
     850       IF ( spinup_time /= spinup_time_max  .OR.  dt_spinup /= dt_spinup_max )  THEN
     851          message_string = 'In case of nesting, spinup_time and ' //                               &
     852                           'dt_spinup must be identical in all parent and child domains.'
    917853          CALL message( 'check_parameters', 'PA0489', 3, 2, 0, 6, 0 )
    918854       ENDIF
     
    920856    ENDIF
    921857
    922     IF ( bulk_cloud_model  .AND.  .NOT.  humidity )  THEN
    923        WRITE( message_string, * ) 'bulk_cloud_model = ', bulk_cloud_model,     &
     858    IF ( bulk_cloud_model  .AND.  .NOT. humidity )  THEN
     859       WRITE( message_string, * ) 'bulk_cloud_model = ', bulk_cloud_model,                         &
    924860              ' is not allowed with humidity = ', humidity
    925861       CALL message( 'check_parameters', 'PA0034', 1, 2, 0, 6, 0 )
     
    927863
    928864    IF ( humidity  .AND.  sloping_surface )  THEN
    929        message_string = 'humidity = .TRUE. and sloping_surface = .TRUE. ' //   &
     865       message_string = 'humidity = .TRUE. and sloping_surface = .TRUE. ' //                       &
    930866                        'are not allowed simultaneously'
    931867       CALL message( 'check_parameters', 'PA0036', 1, 2, 0, 6, 0 )
     
    936872
    937873!
    938 !-- In case of no restart run, check initialising parameters and calculate
    939 !-- further quantities
     874!-- In case of no restart run, check initialising parameters and calculate further quantities
    940875    IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
    941876
     
    947882
    948883!--
    949 !--    If required, compute initial profile of the geostrophic wind
    950 !--    (component ug)
     884!--    If required, compute initial profile of the geostrophic wind (component ug)
    951885       i = 1
    952886       gradient = 0.0_wp
     
    958892          DO  k = 1, nzt+1
    959893             IF ( i < 11 )  THEN
    960                 IF ( ug_vertical_gradient_level(i) < zu(k)  .AND.              &
     894                IF ( ug_vertical_gradient_level(i) < zu(k)  .AND.                                  &
    961895                     ug_vertical_gradient_level(i) >= 0.0_wp )  THEN
    962896                   gradient = ug_vertical_gradient(i) / 100.0_wp
     
    982916          DO  k = nzt, nzb, -1
    983917             IF ( i < 11 )  THEN
    984                 IF ( ug_vertical_gradient_level(i) > zu(k)  .AND.              &
     918                IF ( ug_vertical_gradient_level(i) > zu(k)  .AND.                                  &
    985919                     ug_vertical_gradient_level(i) <= 0.0_wp )  THEN
    986920                   gradient = ug_vertical_gradient(i) / 100.0_wp
     
    1011945!
    1012946!--
    1013 !--    If required, compute initial profile of the geostrophic wind
    1014 !--    (component vg)
     947!--    If required, compute initial profile of the geostrophic wind (component vg)
    1015948       i = 1
    1016949       gradient = 0.0_wp
     
    1022955          DO  k = 1, nzt+1
    1023956             IF ( i < 11 )  THEN
    1024                 IF ( vg_vertical_gradient_level(i) < zu(k)  .AND.              &
     957                IF ( vg_vertical_gradient_level(i) < zu(k)  .AND.                                  &
    1025958                     vg_vertical_gradient_level(i) >= 0.0_wp )  THEN
    1026959                   gradient = vg_vertical_gradient(i) / 100.0_wp
     
    1046979          DO  k = nzt, nzb, -1
    1047980             IF ( i < 11 )  THEN
    1048                 IF ( vg_vertical_gradient_level(i) > zu(k)  .AND.              &
     981                IF ( vg_vertical_gradient_level(i) > zu(k)  .AND.                                  &
    1049982                     vg_vertical_gradient_level(i) <= 0.0_wp )  THEN
    1050983                   gradient = vg_vertical_gradient(i) / 100.0_wp
     
    10741007
    10751008!
    1076 !--    Let the initial wind profiles be the calculated ug/vg profiles or
    1077 !--    interpolate them from wind profile data (if given)
     1009!--    Let the initial wind profiles be the calculated ug/vg profiles or interpolate them from wind
     1010!--    profile data (if given)
    10781011       IF ( u_profile(1) == 9999999.9_wp  .AND.  v_profile(1) == 9999999.9_wp )  THEN
    10791012
     
    10891022
    10901023          IF ( omega /= 0.0_wp )  THEN
    1091              message_string = 'Coriolis force must be switched off (by setting omega=0.0)' //  &
     1024             message_string = 'Coriolis force must be switched off (by setting omega=0.0)' //      &
    10921025                              ' when prescribing the forcing by u_profile and v_profile'
    10931026             CALL message( 'check_parameters', 'PA0347', 1, 2, 0, 6, 0 )
     
    11101043
    11111044             IF ( kk < 200  .AND.  uv_heights(kk+1) /= 9999999.9_wp )  THEN
    1112                 u_init(k) = u_profile(kk) + ( zu(k) - uv_heights(kk) ) /       &
    1113                                        ( uv_heights(kk+1) - uv_heights(kk) ) * &
    1114                                        ( u_profile(kk+1) - u_profile(kk) )
    1115                 v_init(k) = v_profile(kk) + ( zu(k) - uv_heights(kk) ) /       &
    1116                                        ( uv_heights(kk+1) - uv_heights(kk) ) * &
    1117                                        ( v_profile(kk+1) - v_profile(kk) )
     1045                u_init(k) = u_profile(kk) + ( zu(k) - uv_heights(kk) ) /                           &
     1046                                            ( uv_heights(kk+1) - uv_heights(kk) ) *                &
     1047                                            ( u_profile(kk+1) - u_profile(kk) )
     1048                v_init(k) = v_profile(kk) + ( zu(k) - uv_heights(kk) ) /                           &
     1049                                            ( uv_heights(kk+1) - uv_heights(kk) ) *                &
     1050                                            ( v_profile(kk+1) - v_profile(kk) )
    11181051             ELSE
    11191052                u_init(k) = u_profile(kk)
     
    11331066!--    Compute initial temperature profile using the given temperature gradients
    11341067       IF (  .NOT.  neutral )  THEN
    1135           CALL init_vertical_profiles( pt_vertical_gradient_level_ind,          &
    1136                                        pt_vertical_gradient_level,              &
    1137                                        pt_vertical_gradient, pt_init,           &
    1138                                        pt_surface, bc_pt_t_val )
     1068          CALL init_vertical_profiles( pt_vertical_gradient_level_ind, pt_vertical_gradient_level, &
     1069                                       pt_vertical_gradient, pt_init, pt_surface, bc_pt_t_val )
    11391070       ENDIF
    11401071!
    11411072!--    Compute initial humidity profile using the given humidity gradients
    11421073       IF ( humidity )  THEN
    1143           CALL init_vertical_profiles( q_vertical_gradient_level_ind,          &
    1144                                        q_vertical_gradient_level,              &
    1145                                        q_vertical_gradient, q_init,            &
    1146                                        q_surface, bc_q_t_val )
     1074          CALL init_vertical_profiles( q_vertical_gradient_level_ind, q_vertical_gradient_level,   &
     1075                                       q_vertical_gradient, q_init, q_surface, bc_q_t_val )
    11471076       ENDIF
    11481077!
    11491078!--    Compute initial scalar profile using the given scalar gradients
    11501079       IF ( passive_scalar )  THEN
    1151           CALL init_vertical_profiles( s_vertical_gradient_level_ind,          &
    1152                                        s_vertical_gradient_level,              &
    1153                                        s_vertical_gradient, s_init,            &
    1154                                        s_surface, bc_s_t_val )
     1080          CALL init_vertical_profiles( s_vertical_gradient_level_ind, s_vertical_gradient_level,   &
     1081                                       s_vertical_gradient, s_init, s_surface, bc_s_t_val )
    11551082       ENDIF
    11561083!
     
    11641091!-- Check if the control parameter use_subsidence_tendencies is used correctly
    11651092    IF ( use_subsidence_tendencies  .AND.  .NOT.  large_scale_subsidence )  THEN
    1166        message_string = 'The usage of use_subsidence_tendencies ' //           &
    1167                             'requires large_scale_subsidence = .T..'
     1093       message_string = 'The usage of use_subsidence_tendencies ' //                               &
     1094                        'requires large_scale_subsidence = .T..'
    11681095       CALL message( 'check_parameters', 'PA0396', 1, 2, 0, 6, 0 )
    11691096    ELSEIF ( use_subsidence_tendencies  .AND.  .NOT. large_scale_forcing )  THEN
    11701097       message_string = 'The usage of use_subsidence_tendencies ' //           &
    1171                             'requires large_scale_forcing = .T..'
     1098                        'requires large_scale_forcing = .T..'
    11721099       CALL message( 'check_parameters', 'PA0397', 1, 2, 0, 6, 0 )
    11731100    ENDIF
     
    11761103!-- Initialize large scale subsidence if required
    11771104    If ( large_scale_subsidence )  THEN
    1178        IF ( subs_vertical_gradient_level(1) /= -9999999.9_wp  .AND.            &
    1179                                      .NOT.  large_scale_forcing )  THEN
     1105       IF ( subs_vertical_gradient_level(1) /= -9999999.9_wp  .AND. .NOT. large_scale_forcing )    &
     1106       THEN
    11801107          CALL init_w_subsidence
    11811108       ENDIF
    11821109!
    1183 !--    In case large_scale_forcing is used, profiles for subsidence velocity
    1184 !--    are read in from file LSF_DATA
    1185 
    1186        IF ( subs_vertical_gradient_level(1) == -9999999.9_wp  .AND.            &
    1187             .NOT.  large_scale_forcing )  THEN
    1188           message_string = 'There is no default large scale vertical ' //      &
    1189                            'velocity profile set. Specify the subsidence ' //  &
    1190                            'velocity profile via subs_vertical_gradient ' //   &
    1191                            'and subs_vertical_gradient_level.'
     1110!--    In case large_scale_forcing is used, profiles for subsidence velocity are read in from file
     1111!--    LSF_DATA
     1112
     1113       IF ( subs_vertical_gradient_level(1) == -9999999.9_wp  .AND. .NOT. large_scale_forcing )    &
     1114       THEN
     1115          message_string = 'There is no default large scale vertical velocity profile set. ' //    &
     1116                           'Specify the subsidence velocity profile via subs_vertical_gradient' // &
     1117                           ' and subs_vertical_gradient_level.'
    11921118          CALL message( 'check_parameters', 'PA0380', 1, 2, 0, 6, 0 )
    11931119       ENDIF
    11941120    ELSE
    11951121        IF ( subs_vertical_gradient_level(1) /= -9999999.9_wp )  THEN
    1196            message_string = 'Enable usage of large scale subsidence by ' //    &
     1122           message_string = 'Enable usage of large scale subsidence by ' //                        &
    11971123                            'setting large_scale_subsidence = .T..'
    11981124          CALL message( 'check_parameters', 'PA0381', 1, 2, 0, 6, 0 )
     
    12231149       vpt_reference = pt_reference * ( 1.0_wp + 0.61_wp * q_surface )
    12241150    ELSE
    1225        message_string = 'illegal value for reference_state: "' //              &
    1226                         TRIM( reference_state ) // '"'
     1151       message_string = 'illegal value for reference_state: "' // TRIM( reference_state ) // '"'
    12271152       CALL message( 'check_parameters', 'PA0056', 1, 2, 0, 6, 0 )
    12281153    ENDIF
     
    12321157    IF ( alpha_surface /= 0.0_wp )  THEN
    12331158       IF ( ABS( alpha_surface ) > 90.0_wp )  THEN
    1234           WRITE( message_string, * ) 'ABS( alpha_surface = ', alpha_surface,   &
    1235                                      ' ) must be < 90.0'
     1159          WRITE( message_string, * ) 'ABS( alpha_surface = ', alpha_surface, ' ) must be < 90.0'
    12361160          CALL message( 'check_parameters', 'PA0043', 1, 2, 0, 6, 0 )
    12371161       ENDIF
     
    12621186          ENDIF
    12631187       ELSE
    1264           WRITE( message_string, * ) 'cfl_factor = ', cfl_factor,              &
     1188          WRITE( message_string, * ) 'cfl_factor = ', cfl_factor,                                  &
    12651189                 ' out of range &0.0 < cfl_factor <= 1.0 is required'
    12661190          CALL message( 'check_parameters', 'PA0045', 1, 2, 0, 6, 0 )
     
    12731197
    12741198!
    1275 !-- Store reference time for coupled runs and change the coupling flag,
    1276 !-- if ...
     1199!-- Store reference time for coupled runs and change the coupling flag, if ...
    12771200    IF ( simulated_time == 0.0_wp )  THEN
    12781201       IF ( coupling_start_time == 0.0_wp )  THEN
     
    12861209!-- Set wind speed in the Galilei-transformed system
    12871210    IF ( galilei_transformation )  THEN
    1288        IF ( use_ug_for_galilei_tr                    .AND.                     &
    1289             ug_vertical_gradient_level(1) == 0.0_wp  .AND.                     &
    1290             ug_vertical_gradient(1) == 0.0_wp        .AND.                     &
    1291             vg_vertical_gradient_level(1) == 0.0_wp  .AND.                     &
    1292             vg_vertical_gradient(1) == 0.0_wp )  THEN
     1211       IF ( use_ug_for_galilei_tr                    .AND.                                         &
     1212            ug_vertical_gradient_level(1) == 0.0_wp  .AND.                                         &
     1213            ug_vertical_gradient(1)       == 0.0_wp  .AND.                                         &
     1214            vg_vertical_gradient_level(1) == 0.0_wp  .AND.                                         &
     1215            vg_vertical_gradient(1)       == 0.0_wp )  THEN
    12931216          u_gtrans = ug_surface * 0.6_wp
    12941217          v_gtrans = vg_surface * 0.6_wp
    1295        ELSEIF ( use_ug_for_galilei_tr  .AND.                                   &
    1296                 ( ug_vertical_gradient_level(1) /= 0.0_wp  .OR.                &
    1297                 ug_vertical_gradient(1) /= 0.0_wp ) )  THEN
    1298           message_string = 'baroclinity (ug) not allowed simultaneously' //    &
     1218       ELSEIF ( use_ug_for_galilei_tr  .AND.  ( ug_vertical_gradient_level(1) /= 0.0_wp .OR.       &
     1219                                                ug_vertical_gradient(1) /= 0.0_wp ) )  THEN
     1220          message_string = 'baroclinity (ug) not allowed simultaneously' //                        &
    12991221                           ' with galilei transformation'
    13001222          CALL message( 'check_parameters', 'PA0046', 1, 2, 0, 6, 0 )
    1301        ELSEIF ( use_ug_for_galilei_tr  .AND.                                   &
    1302                 ( vg_vertical_gradient_level(1) /= 0.0_wp  .OR.                &
    1303                 vg_vertical_gradient(1) /= 0.0_wp ) )  THEN
    1304           message_string = 'baroclinity (vg) not allowed simultaneously' //    &
     1223       ELSEIF ( use_ug_for_galilei_tr  .AND.  ( vg_vertical_gradient_level(1) /= 0.0_wp  .OR.      &
     1224                                                vg_vertical_gradient(1) /= 0.0_wp ) )  THEN
     1225          message_string = 'baroclinity (vg) not allowed simultaneously' //                        &
    13051226                           ' with galilei transformation'
    13061227          CALL message( 'check_parameters', 'PA0047', 1, 2, 0, 6, 0 )
    13071228       ELSE
    1308           message_string = 'variable translation speed used for Galilei-' //   &
    1309              'transformation, which may cause & instabilities in stably ' //   &
    1310              'stratified regions'
     1229          message_string = 'variable translation speed used for Galilei-transformation, which ' // &
     1230                           'may cause & instabilities in stably stratified regions'
    13111231          CALL message( 'check_parameters', 'PA0048', 0, 1, 0, 6, 0 )
    13121232       ENDIF
     
    13141234
    13151235!
    1316 !-- In case of using a prandtl-layer, calculated (or prescribed) surface
    1317 !-- fluxes have to be used in the diffusion-terms
     1236!-- In case of using a prandtl-layer, calculated (or prescribed) surface fluxes have to be used in
     1237!-- the diffusion-terms
    13181238    IF ( constant_flux_layer )  use_surface_fluxes = .TRUE.
    13191239
    13201240!
    13211241!-- Check boundary conditions and set internal variables:
    1322 !-- Attention: the lateral boundary conditions have been already checked in
    1323 !-- parin
    1324 !
    1325 !-- Non-cyclic lateral boundaries require the multigrid method and Piascek-
    1326 !-- Willimas or Wicker - Skamarock advection scheme. Several schemes
    1327 !-- and tools do not work with non-cyclic boundary conditions.
     1242!-- Attention: the lateral boundary conditions have been already checked in parin
     1243!
     1244!-- Non-cyclic lateral boundaries require the multigrid method and Piascek-Willimas or
     1245!-- Wicker - Skamarock advection scheme. Several schemes and tools do not work with non-cyclic
     1246!-- boundary conditions.
    13281247    IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
    13291248       IF ( psolver(1:9) /= 'multigrid' )  THEN
    1330           message_string = 'non-cyclic lateral boundaries do not allow ' //    &
    1331                            'psolver = "' // TRIM( psolver ) // '"'
     1249          message_string = 'non-cyclic lateral boundaries do not allow ' // 'psolver = "' //       &
     1250                           TRIM( psolver ) // '"'
    13321251          CALL message( 'check_parameters', 'PA0051', 1, 2, 0, 6, 0 )
    13331252       ENDIF
    1334        IF ( momentum_advec /= 'pw-scheme'  .AND.                               &
    1335             momentum_advec /= 'ws-scheme' )  THEN
    1336 
    1337           message_string = 'non-cyclic lateral boundaries do not allow ' //    &
    1338                            'momentum_advec = "' // TRIM( momentum_advec ) // '"'
     1253       IF ( momentum_advec /= 'pw-scheme'  .AND.  momentum_advec /= 'ws-scheme' )  THEN
     1254
     1255          message_string = 'non-cyclic lateral boundaries do not allow momentum_advec = "' //      &
     1256                           TRIM( momentum_advec ) // '"'
    13391257          CALL message( 'check_parameters', 'PA0052', 1, 2, 0, 6, 0 )
    13401258       ENDIF
    1341        IF ( scalar_advec /= 'pw-scheme'  .AND.                                 &
    1342             scalar_advec /= 'ws-scheme' )  THEN
    1343           message_string = 'non-cyclic lateral boundaries do not allow ' //    &
    1344                            'scalar_advec = "' // TRIM( scalar_advec ) // '"'
     1259       IF ( scalar_advec /= 'pw-scheme'  .AND.  scalar_advec /= 'ws-scheme' )  THEN
     1260          message_string = 'non-cyclic lateral boundaries do not allow scalar_advec = "' //        &
     1261                           TRIM( scalar_advec ) // '"'
    13451262          CALL message( 'check_parameters', 'PA0053', 1, 2, 0, 6, 0 )
    13461263       ENDIF
    13471264       IF ( galilei_transformation )  THEN
    1348           message_string = 'non-cyclic lateral boundaries do not allow ' //    &
    1349                            'galilei_transformation = .T.'
     1265          message_string = 'non-cyclic lateral boundaries do not allow galilei_transformation = .T.'
    13501266          CALL message( 'check_parameters', 'PA0054', 1, 2, 0, 6, 0 )
    13511267       ENDIF
     
    13611277          bc_e_b = 'neumann'
    13621278          ibc_e_b = 1
    1363           message_string = 'boundary condition bc_e_b changed to "' //         &
    1364                            TRIM( bc_e_b ) // '"'
     1279          message_string = 'boundary condition bc_e_b changed to "' // TRIM( bc_e_b ) // '"'
    13651280          CALL message( 'check_parameters', 'PA0057', 0, 1, 0, 6, 0 )
    13661281       ENDIF
    13671282    ELSE
    1368        message_string = 'unknown boundary condition: bc_e_b = "' //            &
    1369                         TRIM( bc_e_b ) // '"'
     1283       message_string = 'unknown boundary condition: bc_e_b = "' // TRIM( bc_e_b ) // '"'
    13701284       CALL message( 'check_parameters', 'PA0058', 1, 2, 0, 6, 0 )
    13711285    ENDIF
     
    13781292       ibc_p_b = 1
    13791293    ELSE
    1380        message_string = 'unknown boundary condition: bc_p_b = "' //            &
    1381                         TRIM( bc_p_b ) // '"'
     1294       message_string = 'unknown boundary condition: bc_p_b = "' // TRIM( bc_p_b ) // '"'
    13821295       CALL message( 'check_parameters', 'PA0059', 1, 2, 0, 6, 0 )
    13831296    ENDIF
     
    13891302       ibc_p_t = 1
    13901303    ELSE
    1391        message_string = 'unknown boundary condition: bc_p_t = "' //            &
    1392                         TRIM( bc_p_t ) // '"'
     1304       message_string = 'unknown boundary condition: bc_p_t = "' // TRIM( bc_p_t ) // '"'
    13931305       CALL message( 'check_parameters', 'PA0061', 1, 2, 0, 6, 0 )
    13941306    ENDIF
     
    14041316          ibc_pt_b = 1
    14051317       ELSE
    1406           message_string = 'unknown boundary condition: bc_pt_b = "' //        &
    1407                            TRIM( bc_pt_b ) // '"'
     1318          message_string = 'unknown boundary condition: bc_pt_b = "' // TRIM( bc_pt_b ) // '"'
    14081319          CALL message( 'check_parameters', 'PA0062', 1, 2, 0, 6, 0 )
    14091320       ENDIF
     
    14191330       ibc_pt_t = 3
    14201331    ELSE
    1421        message_string = 'unknown boundary condition: bc_pt_t = "' //           &
    1422                         TRIM( bc_pt_t ) // '"'
     1332       message_string = 'unknown boundary condition: bc_pt_t = "' // TRIM( bc_pt_t ) // '"'
    14231333       CALL message( 'check_parameters', 'PA0063', 1, 2, 0, 6, 0 )
    14241334    ENDIF
    14251335
    1426     IF ( ANY( wall_heatflux /= 0.0_wp )  .AND.                        &
    1427          surface_heatflux == 9999999.9_wp )  THEN
    1428        message_string = 'wall_heatflux additionally requires ' //     &
    1429                         'setting of surface_heatflux'
     1336    IF ( ANY( wall_heatflux /= 0.0_wp )  .AND.  surface_heatflux == 9999999.9_wp )  THEN
     1337       message_string = 'wall_heatflux additionally requires setting of surface_heatflux'
    14301338       CALL message( 'check_parameters', 'PA0443', 1, 2, 0, 6, 0 )
    14311339    ENDIF
     
    14511359    IF ( neutral )  THEN
    14521360
    1453        IF ( surface_heatflux /= 0.0_wp  .AND.                                  &
    1454             surface_heatflux /= 9999999.9_wp )  THEN
     1361       IF ( surface_heatflux /= 0.0_wp  .AND.  surface_heatflux /= 9999999.9_wp )  THEN
    14551362          message_string = 'heatflux must not be set for pure neutral flow'
    14561363          CALL message( 'check_parameters', 'PA0351', 1, 2, 0, 6, 0 )
    14571364       ENDIF
    14581365
    1459        IF ( top_heatflux /= 0.0_wp  .AND.  top_heatflux /= 9999999.9_wp )      &
    1460        THEN
     1366       IF ( top_heatflux /= 0.0_wp  .AND.  top_heatflux /= 9999999.9_wp )  THEN
    14611367          message_string = 'heatflux must not be set for pure neutral flow'
    14621368          CALL message( 'check_parameters', 'PA0351', 1, 2, 0, 6, 0 )
     
    14651371    ENDIF
    14661372
    1467     IF ( top_momentumflux_u /= 9999999.9_wp  .AND.                             &
    1468          top_momentumflux_v /= 9999999.9_wp )  THEN
     1373    IF ( top_momentumflux_u /= 9999999.9_wp  .AND.  top_momentumflux_v /= 9999999.9_wp )  THEN
    14691374       constant_top_momentumflux = .TRUE.
    1470     ELSEIF (  .NOT. ( top_momentumflux_u == 9999999.9_wp  .AND.                &
     1375    ELSEIF ( .NOT. ( top_momentumflux_u == 9999999.9_wp  .AND.                                     &
    14711376           top_momentumflux_v == 9999999.9_wp ) )  THEN
    1472        message_string = 'both, top_momentumflux_u AND top_momentumflux_v ' //  &
    1473                         'must be set'
     1377       message_string = 'both, top_momentumflux_u AND top_momentumflux_v must be set'
    14741378       CALL message( 'check_parameters', 'PA0064', 1, 2, 0, 6, 0 )
    14751379    ENDIF
    14761380
    14771381!
    1478 !-- A given surface temperature implies Dirichlet boundary condition for
    1479 !-- temperature. In this case specification of a constant heat flux is
    1480 !-- forbidden.
    1481     IF ( ibc_pt_b == 0  .AND.  constant_heatflux  .AND.                        &
    1482          surface_heatflux /= 0.0_wp )  THEN
    1483        message_string = 'boundary_condition: bc_pt_b = "' // TRIM( bc_pt_b ) //&
     1382!-- A given surface temperature implies Dirichlet boundary condition for temperature. In this case
     1383!-- specification of a constant heat flux is forbidden.
     1384    IF ( ibc_pt_b == 0  .AND.  constant_heatflux  .AND.  surface_heatflux /= 0.0_wp )  THEN
     1385       message_string = 'boundary_condition: bc_pt_b = "' // TRIM( bc_pt_b ) //                    &
    14841386                        '& is not allowed with constant_heatflux = .TRUE.'
    14851387       CALL message( 'check_parameters', 'PA0065', 1, 2, 0, 6, 0 )
    14861388    ENDIF
    14871389    IF ( constant_heatflux  .AND.  pt_surface_initial_change /= 0.0_wp )  THEN
    1488        WRITE ( message_string, * )  'constant_heatflux = .TRUE. is not allo',  &
    1489                'wed with pt_surface_initial_change (/=0) = ',                  &
    1490                pt_surface_initial_change
     1390       WRITE ( message_string, * )  'constant_heatflux = .TRUE. is not allo',                      &
     1391               'wed with pt_surface_initial_change (/=0) = ', pt_surface_initial_change
    14911392       CALL message( 'check_parameters', 'PA0066', 1, 2, 0, 6, 0 )
    14921393    ENDIF
    14931394
    14941395!
    1495 !-- A given temperature at the top implies Dirichlet boundary condition for
    1496 !-- temperature. In this case specification of a constant heat flux is
    1497 !-- forbidden.
    1498     IF ( ibc_pt_t == 0  .AND.  constant_top_heatflux  .AND.                    &
    1499          top_heatflux /= 0.0_wp )  THEN
    1500        message_string = 'boundary_condition: bc_pt_t = "' // TRIM( bc_pt_t ) //&
     1396!-- A given temperature at the top implies Dirichlet boundary condition for temperature. In this
     1397!-- case specification of a constant heat flux is forbidden.
     1398    IF ( ibc_pt_t == 0  .AND.  constant_top_heatflux  .AND.  top_heatflux /= 0.0_wp )  THEN
     1399       message_string = 'boundary_condition: bc_pt_t = "' // TRIM( bc_pt_t ) //                    &
    15011400                        '" is not allowed with constant_top_heatflux = .TRUE.'
    15021401       CALL message( 'check_parameters', 'PA0067', 1, 2, 0, 6, 0 )
     
    15071406    IF ( humidity )  THEN
    15081407
    1509        IF ( ANY( wall_humidityflux /= 0.0_wp )  .AND.                        &
    1510             surface_waterflux == 9999999.9_wp )  THEN
    1511           message_string = 'wall_humidityflux additionally requires ' //     &
    1512                            'setting of surface_waterflux'
     1408       IF ( ANY( wall_humidityflux /= 0.0_wp )  .AND.  surface_waterflux == 9999999.9_wp )  THEN
     1409          message_string = 'wall_humidityflux additionally requires setting of surface_waterflux'
    15131410          CALL message( 'check_parameters', 'PA0444', 1, 2, 0, 6, 0 )
    15141411       ENDIF
    15151412
    1516        CALL set_bc_scalars( 'q', bc_q_b, bc_q_t, ibc_q_b, ibc_q_t,           &
    1517                             'PA0071', 'PA0072' )
     1413       CALL set_bc_scalars( 'q', bc_q_b, bc_q_t, ibc_q_b, ibc_q_t, 'PA0071', 'PA0072' )
    15181414
    15191415       IF ( surface_waterflux == 9999999.9_wp  )  THEN
     
    15301426       ENDIF
    15311427
    1532        CALL check_bc_scalars( 'q', bc_q_b, ibc_q_b, 'PA0073', 'PA0074',        &
    1533                               constant_waterflux, q_surface_initial_change )
     1428       CALL check_bc_scalars( 'q', bc_q_b, ibc_q_b, 'PA0073', 'PA0074', constant_waterflux,        &
     1429                              q_surface_initial_change )
    15341430
    15351431    ENDIF
     
    15371433    IF ( passive_scalar )  THEN
    15381434
    1539        IF ( ANY( wall_scalarflux /= 0.0_wp )  .AND.                            &
    1540             surface_scalarflux == 9999999.9_wp )  THEN
    1541           message_string = 'wall_scalarflux additionally requires ' //         &
    1542                            'setting of surface_scalarflux'
     1435       IF ( ANY( wall_scalarflux /= 0.0_wp )  .AND.  surface_scalarflux == 9999999.9_wp )  THEN
     1436          message_string = 'wall_scalarflux additionally requires setting of surface_scalarflux'
    15431437          CALL message( 'check_parameters', 'PA0445', 1, 2, 0, 6, 0 )
    15441438       ENDIF
     
    15461440       IF ( surface_scalarflux == 9999999.9_wp )  constant_scalarflux = .FALSE.
    15471441
    1548        CALL set_bc_scalars( 's', bc_s_b, bc_s_t, ibc_s_b, ibc_s_t,             &
    1549                             'PA0071', 'PA0072' )
    1550 
    1551        CALL check_bc_scalars( 's', bc_s_b, ibc_s_b, 'PA0073', 'PA0074',        &
    1552                               constant_scalarflux, s_surface_initial_change )
     1442       CALL set_bc_scalars( 's', bc_s_b, bc_s_t, ibc_s_b, ibc_s_t, 'PA0071', 'PA0072' )
     1443
     1444       CALL check_bc_scalars( 's', bc_s_b, ibc_s_b, 'PA0073', 'PA0074', constant_scalarflux,       &
     1445                              s_surface_initial_change )
    15531446
    15541447       IF ( top_scalarflux == 9999999.9_wp )  constant_top_scalarflux = .FALSE.
    15551448!
    1556 !--    A fixed scalar concentration at the top implies Dirichlet boundary
    1557 !--    condition for scalar. Hence, in this case specification of a constant
    1558 !--    scalar flux is forbidden.
    1559        IF ( ( ibc_s_t == 0 .OR. ibc_s_t == 2 )  .AND.  constant_top_scalarflux &
    1560                .AND.  top_scalarflux /= 0.0_wp )  THEN
    1561           message_string = 'boundary condition: bc_s_t = "' //                 &
    1562                            TRIM( bc_s_t ) // '" is not allowed with ' //       &
    1563                            'top_scalarflux /= 0.0'
     1449!--    A fixed scalar concentration at the top implies Dirichlet boundary condition for scalar.
     1450!--    Hence, in this case specification of a constant scalar flux is forbidden.
     1451       IF ( ( ibc_s_t == 0 .OR. ibc_s_t == 2 )  .AND.  constant_top_scalarflux  .AND.              &
     1452              top_scalarflux /= 0.0_wp )  THEN
     1453          message_string = 'boundary condition: bc_s_t = "' // TRIM( bc_s_t ) //                   &
     1454                           '" is not allowed with top_scalarflux /= 0.0'
    15641455          CALL message( 'check_parameters', 'PA0441', 1, 2, 0, 6, 0 )
    15651456       ENDIF
     
    15731464       ibc_uv_b = 1
    15741465       IF ( constant_flux_layer )  THEN
    1575           message_string = 'boundary condition: bc_uv_b = "' //                &
    1576                TRIM( bc_uv_b ) // '" is not allowed with constant_flux_layer'  &
    1577                // ' = .TRUE.'
     1466          message_string = 'boundary condition: bc_uv_b = "' // TRIM( bc_uv_b ) //                 &
     1467                           '" is not allowed with constant_flux_layer = .TRUE.'
    15781468          CALL message( 'check_parameters', 'PA0075', 1, 2, 0, 6, 0 )
    15791469       ENDIF
    15801470    ELSE
    1581        message_string = 'unknown boundary condition: bc_uv_b = "' //           &
    1582                         TRIM( bc_uv_b ) // '"'
     1471       message_string = 'unknown boundary condition: bc_uv_b = "' // TRIM( bc_uv_b ) // '"'
    15831472       CALL message( 'check_parameters', 'PA0076', 1, 2, 0, 6, 0 )
    15841473    ENDIF
    15851474!
    1586 !-- In case of coupled simulations u and v at the ground in atmosphere will be
    1587 !-- assigned with the u and v values of the ocean surface
     1475!-- In case of coupled simulations u and v at the ground in atmosphere will be assigned with the u
     1476!-- and v values of the ocean surface
    15881477    IF ( coupling_mode == 'atmosphere_to_ocean' )  THEN
    15891478       ibc_uv_b = 2
     
    15981487          IF ( bc_uv_t == 'dirichlet_0' )  THEN
    15991488!
    1600 !--          Velocities for the initial u,v-profiles are set zero at the top
    1601 !--          in case of dirichlet_0 conditions
     1489!--          Velocities for the initial u,v-profiles are set zero at the top in case of dirichlet_0
     1490!--          conditions
    16021491             u_init(nzt+1)    = 0.0_wp
    16031492             v_init(nzt+1)    = 0.0_wp
     
    16081497          ibc_uv_t = 3
    16091498       ELSE
    1610           message_string = 'unknown boundary condition: bc_uv_t = "' //        &
    1611                            TRIM( bc_uv_t ) // '"'
     1499          message_string = 'unknown boundary condition: bc_uv_t = "' // TRIM( bc_uv_t ) // '"'
    16121500          CALL message( 'check_parameters', 'PA0077', 1, 2, 0, 6, 0 )
    16131501       ENDIF
     
    16191507       rayleigh_damping_factor = 0.0_wp
    16201508    ELSE
    1621        IF ( rayleigh_damping_factor < 0.0_wp  .OR.                             &
    1622             rayleigh_damping_factor > 1.0_wp )  THEN
    1623           WRITE( message_string, * )  'rayleigh_damping_factor = ',            &
    1624                               rayleigh_damping_factor, ' out of range [0.0,1.0]'
     1509       IF ( rayleigh_damping_factor < 0.0_wp  .OR.  rayleigh_damping_factor > 1.0_wp )  THEN
     1510          WRITE( message_string, * )  'rayleigh_damping_factor = ', rayleigh_damping_factor,       &
     1511                 ' out of range [0.0,1.0]'
    16251512          CALL message( 'check_parameters', 'PA0078', 1, 2, 0, 6, 0 )
    16261513       ENDIF
     
    16281515
    16291516    IF ( rayleigh_damping_height == -1.0_wp )  THEN
    1630        IF (  .NOT. ocean_mode )  THEN
     1517       IF ( .NOT. ocean_mode )  THEN
    16311518          rayleigh_damping_height = 0.66666666666_wp * zu(nzt)
    16321519       ELSE
     
    16341521       ENDIF
    16351522    ELSE
    1636        IF (  .NOT.  ocean_mode )  THEN
    1637           IF ( rayleigh_damping_height < 0.0_wp  .OR.                          &
    1638                rayleigh_damping_height > zu(nzt) )  THEN
    1639              WRITE( message_string, * )  'rayleigh_damping_height = ',         &
    1640                    rayleigh_damping_height, ' out of range [0.0,', zu(nzt), ']'
     1523       IF ( .NOT. ocean_mode )  THEN
     1524          IF ( rayleigh_damping_height < 0.0_wp  .OR.  rayleigh_damping_height > zu(nzt) )  THEN
     1525             WRITE( message_string, * )  'rayleigh_damping_height = ',  rayleigh_damping_height,   &
     1526                    ' out of range [0.0,', zu(nzt), ']'
    16411527             CALL message( 'check_parameters', 'PA0079', 1, 2, 0, 6, 0 )
    16421528          ENDIF
    16431529       ELSE
    1644           IF ( rayleigh_damping_height > 0.0_wp  .OR.                          &
    1645                rayleigh_damping_height < zu(nzb) )  THEN
    1646              WRITE( message_string, * )  'rayleigh_damping_height = ',         &
    1647                    rayleigh_damping_height, ' out of range [0.0,', zu(nzb), ']'
     1530          IF ( rayleigh_damping_height > 0.0_wp  .OR.  rayleigh_damping_height < zu(nzb) )  THEN
     1531             WRITE( message_string, * )  'rayleigh_damping_height = ', rayleigh_damping_height,    &
     1532                    ' out of range [0.0,', zu(nzb), ']'
    16481533             CALL message( 'check_parameters', 'PA0079', 1, 2, 0, 6, 0 )
    16491534          ENDIF
     
    16541539!-- Check number of chosen statistic regions
    16551540    IF ( statistic_regions < 0 )  THEN
    1656        WRITE ( message_string, * ) 'number of statistic_regions = ',           &
    1657                    statistic_regions+1, ' is not allowed'
     1541       WRITE ( message_string, * ) 'number of statistic_regions = ', statistic_regions+1,          &
     1542               ' is not allowed'
    16581543       CALL message( 'check_parameters', 'PA0082', 1, 2, 0, 6, 0 )
    16591544    ENDIF
    1660     IF ( normalizing_region > statistic_regions  .OR.                          &
    1661          normalizing_region < 0)  THEN
    1662        WRITE ( message_string, * ) 'normalizing_region = ',                    &
    1663                 normalizing_region, ' must be >= 0 and <= ',statistic_regions, &
    1664                 ' (value of statistic_regions)'
     1545    IF ( normalizing_region > statistic_regions  .OR.  normalizing_region < 0)  THEN
     1546       WRITE ( message_string, * ) 'normalizing_region = ', normalizing_region,                    &
     1547               ' must be >= 0 and <= ',statistic_regions, ' (value of statistic_regions)'
    16651548       CALL message( 'check_parameters', 'PA0083', 1, 2, 0, 6, 0 )
    16661549    ENDIF
     
    16841567!
    16851568!-- Set the default skip time intervals for data output, if necessary
    1686     IF ( skip_time_dopr    == 9999999.9_wp )                                   &
    1687                                        skip_time_dopr    = skip_time_data_output
    1688     IF ( skip_time_do2d_xy == 9999999.9_wp )                                   &
    1689                                        skip_time_do2d_xy = skip_time_data_output
    1690     IF ( skip_time_do2d_xz == 9999999.9_wp )                                   &
    1691                                        skip_time_do2d_xz = skip_time_data_output
    1692     IF ( skip_time_do2d_yz == 9999999.9_wp )                                   &
    1693                                        skip_time_do2d_yz = skip_time_data_output
    1694     IF ( skip_time_do3d    == 9999999.9_wp )                                   &
    1695                                        skip_time_do3d    = skip_time_data_output
    1696     IF ( skip_time_data_output_av == 9999999.9_wp )                            &
    1697                                 skip_time_data_output_av = skip_time_data_output
     1569    IF ( skip_time_dopr    == 9999999.9_wp )  skip_time_dopr    = skip_time_data_output
     1570    IF ( skip_time_do2d_xy == 9999999.9_wp )  skip_time_do2d_xy = skip_time_data_output
     1571    IF ( skip_time_do2d_xz == 9999999.9_wp )  skip_time_do2d_xz = skip_time_data_output
     1572    IF ( skip_time_do2d_yz == 9999999.9_wp )  skip_time_do2d_yz = skip_time_data_output
     1573    IF ( skip_time_do3d    == 9999999.9_wp )  skip_time_do3d    = skip_time_data_output
     1574    IF ( skip_time_data_output_av == 9999999.9_wp )                                                &
     1575                                       skip_time_data_output_av = skip_time_data_output
    16981576    DO  mid = 1, max_masks
    1699        IF ( skip_time_domask(mid) == 9999999.9_wp )                            &
    1700                                 skip_time_domask(mid)    = skip_time_data_output
     1577       IF ( skip_time_domask(mid) == 9999999.9_wp )                                                &
     1578                                       skip_time_domask(mid)    = skip_time_data_output
    17011579    ENDDO
    17021580
     
    17041582!-- Check the average intervals (first for 3d-data, then for profiles)
    17051583    IF ( averaging_interval > dt_data_output_av )  THEN
    1706        WRITE( message_string, * )  'averaging_interval = ',                    &
    1707              averaging_interval, ' must be <= dt_data_output_av = ',           &
    1708              dt_data_output_av
     1584       WRITE( message_string, * )  'averaging_interval = ', averaging_interval,                    &
     1585              ' must be <= dt_data_output_av = ', dt_data_output_av
    17091586       CALL message( 'check_parameters', 'PA0085', 1, 2, 0, 6, 0 )
    17101587    ENDIF
     
    17151592
    17161593    IF ( averaging_interval_pr > dt_dopr )  THEN
    1717        WRITE( message_string, * )  'averaging_interval_pr = ',                 &
    1718              averaging_interval_pr, ' must be <= dt_dopr = ', dt_dopr
     1594       WRITE( message_string, * )  'averaging_interval_pr = ', averaging_interval_pr,              &
     1595              ' must be <= dt_dopr = ', dt_dopr
    17191596       CALL message( 'check_parameters', 'PA0086', 1, 2, 0, 6, 0 )
    17201597    ENDIF
     
    17271604
    17281605!
    1729 !-- Set the default interval for the output of timeseries to a reasonable
    1730 !-- value (tries to minimize the number of calls of flow_statistics)
     1606!-- Set the default interval for the output of timeseries to a reasonable value (tries to minimize
     1607!-- the number of calls of flow_statistics)
    17311608    IF ( dt_dots == 9999999.9_wp )  THEN
    17321609       IF ( averaging_interval_pr == 0.0_wp )  THEN
     
    17401617!-- Check the sample rate for averaging (first for 3d-data, then for profiles)
    17411618    IF ( dt_averaging_input > averaging_interval )  THEN
    1742        WRITE( message_string, * )  'dt_averaging_input = ',                    &
    1743                 dt_averaging_input, ' must be <= averaging_interval = ',       &
    1744                 averaging_interval
     1619       WRITE( message_string, * )  'dt_averaging_input = ', dt_averaging_input,                    &
     1620              ' must be <= averaging_interval = ', averaging_interval
    17451621       CALL message( 'check_parameters', 'PA0088', 1, 2, 0, 6, 0 )
    17461622    ENDIF
    17471623
    17481624    IF ( dt_averaging_input_pr > averaging_interval_pr )  THEN
    1749        WRITE( message_string, * )  'dt_averaging_input_pr = ',                 &
    1750                 dt_averaging_input_pr, ' must be <= averaging_interval_pr = ', &
    1751                 averaging_interval_pr
     1625       WRITE( message_string, * )  'dt_averaging_input_pr = ', dt_averaging_input_pr,              &
     1626              ' must be <= averaging_interval_pr = ', averaging_interval_pr
    17521627       CALL message( 'check_parameters', 'PA0089', 1, 2, 0, 6, 0 )
    17531628    ENDIF
    17541629
    17551630!
    1756 !-- Determine the number of output profiles and check whether they are
    1757 !-- permissible
     1631!-- Determine the number of output profiles and check whether they are permissible
    17581632    DO  WHILE ( data_output_pr(dopr_n+1) /= '          ' )
    17591633
     
    17621636
    17631637!
    1764 !--    Determine internal profile number (for hom, homs)
    1765 !--    and store height levels
     1638!--    Determine internal profile number (for hom, homs) and store height levels
    17661639       SELECT CASE ( TRIM( data_output_pr(i) ) )
    17671640
     
    17921665
    17931666          CASE ( 'theta', '#theta' )
    1794              IF ( .NOT. bulk_cloud_model ) THEN
     1667             IF ( .NOT. bulk_cloud_model )  THEN
    17951668                dopr_index(i) = 4
    17961669                dopr_unit(i)  = 'K'
     
    19741847          CASE ( 'q', '#q' )
    19751848             IF ( .NOT. humidity )  THEN
    1976                 message_string = 'data_output_pr = ' //                        &
    1977                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    1978                                  'lemented for humidity = .FALSE.'
     1849                message_string = 'data_output_pr = ' // TRIM( data_output_pr(i) ) //               &
     1850                                 ' is not implemented for humidity = .FALSE.'
    19791851                CALL message( 'check_parameters', 'PA0092', 1, 2, 0, 6, 0 )
    19801852             ELSE
     
    19921864          CASE ( 's', '#s' )
    19931865             IF ( .NOT. passive_scalar )  THEN
    1994                 message_string = 'data_output_pr = ' //                        &
    1995                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    1996                                  'lemented for passive_scalar = .FALSE.'
     1866                message_string = 'data_output_pr = ' // TRIM( data_output_pr(i) ) //               &
     1867                                 ' is not implemented for passive_scalar = .FALSE.'
    19971868                CALL message( 'check_parameters', 'PA0093', 1, 2, 0, 6, 0 )
    19981869             ELSE
     
    20331904          CASE ( 'thetal', '#thetal' )
    20341905             IF ( .NOT. bulk_cloud_model ) THEN
    2035                 message_string = 'data_output_pr = ' //                        &
    2036                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    2037                                  'lemented for bulk_cloud_model = .FALSE.'
     1906                message_string = 'data_output_pr = ' // TRIM( data_output_pr(i) ) //               &
     1907                                 ' is not implemented for bulk_cloud_model = .FALSE.'
    20381908                CALL message( 'check_parameters', 'PA0094', 1, 2, 0, 6, 0 )
    20391909             ELSE
     
    20761946
    20771947          CASE ( 'w"q"' )
    2078              IF (  .NOT.  humidity )  THEN
    2079                 message_string = 'data_output_pr = ' //                        &
    2080                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    2081                                  'lemented for humidity = .FALSE.'
     1948             IF ( .NOT. humidity )  THEN
     1949                message_string = 'data_output_pr = ' // TRIM( data_output_pr(i) ) //               &
     1950                                 ' is not implemented for humidity = .FALSE.'
    20821951                CALL message( 'check_parameters', 'PA0092', 1, 2, 0, 6, 0 )
    20831952             ELSE
     
    20881957
    20891958          CASE ( 'w*q*' )
    2090              IF (  .NOT.  humidity )  THEN
    2091                 message_string = 'data_output_pr = ' //                        &
    2092                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    2093                                  'lemented for humidity = .FALSE.'
     1959             IF ( .NOT. humidity )  THEN
     1960                message_string = 'data_output_pr = ' // TRIM( data_output_pr(i) ) //               &
     1961                                 ' is not implemented for humidity = .FALSE.'
    20941962                CALL message( 'check_parameters', 'PA0092', 1, 2, 0, 6, 0 )
    20951963             ELSE
     
    21001968
    21011969          CASE ( 'wq' )
    2102              IF (  .NOT.  humidity )  THEN
    2103                 message_string = 'data_output_pr = ' //                        &
    2104                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    2105                                  'lemented for humidity = .FALSE.'
     1970             IF ( .NOT. humidity )  THEN
     1971                message_string = 'data_output_pr = ' // TRIM( data_output_pr(i) ) //               &
     1972                                 ' is not implemented for humidity = .FALSE.'
    21061973                CALL message( 'check_parameters', 'PA0092', 1, 2, 0, 6, 0 )
    21071974             ELSE
     
    21121979
    21131980          CASE ( 'w"s"' )
    2114              IF (  .NOT.  passive_scalar )  THEN
    2115                 message_string = 'data_output_pr = ' //                        &
    2116                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    2117                                  'lemented for passive_scalar = .FALSE.'
     1981             IF ( .NOT. passive_scalar )  THEN
     1982                message_string = 'data_output_pr = ' // TRIM( data_output_pr(i) ) //               &
     1983                                 ' is not implemented for passive_scalar = .FALSE.'
    21181984                CALL message( 'check_parameters', 'PA0093', 1, 2, 0, 6, 0 )
    21191985             ELSE
     
    21241990
    21251991          CASE ( 'w*s*' )
    2126              IF (  .NOT.  passive_scalar )  THEN
    2127                 message_string = 'data_output_pr = ' //                        &
    2128                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    2129                                  'lemented for passive_scalar = .FALSE.'
     1992             IF ( .NOT. passive_scalar )  THEN
     1993                message_string = 'data_output_pr = ' // TRIM( data_output_pr(i) ) //               &
     1994                                 ' is not implemented for passive_scalar = .FALSE.'
    21301995                CALL message( 'check_parameters', 'PA0093', 1, 2, 0, 6, 0 )
    21311996             ELSE
     
    21362001
    21372002          CASE ( 'ws' )
    2138              IF (  .NOT.  passive_scalar )  THEN
    2139                 message_string = 'data_output_pr = ' //                        &
    2140                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    2141                                  'lemented for passive_scalar = .FALSE.'
     2003             IF ( .NOT. passive_scalar )  THEN
     2004                message_string = 'data_output_pr = ' // TRIM( data_output_pr(i) ) //               &
     2005                                 ' is not implemented for passive_scalar = .FALSE.'
    21422006                CALL message( 'check_parameters', 'PA0093', 1, 2, 0, 6, 0 )
    21432007             ELSE
     
    21482012
    21492013          CASE ( 'w"qv"' )
    2150              IF ( humidity  .AND.  .NOT.  bulk_cloud_model )  THEN
     2014             IF ( humidity  .AND.  .NOT. bulk_cloud_model )  THEN
    21512015                dopr_index(i) = 48
    21522016                dopr_unit(i)  = TRIM ( waterflux_output_unit )
     
    21572021                hom(:,2,51,:) = SPREAD( zw, 2, statistic_regions+1 )
    21582022             ELSE
    2159                 message_string = 'data_output_pr = ' //                        &
    2160                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    2161                                  'lemented for bulk_cloud_model = .FALSE. ' // &
     2023                message_string = 'data_output_pr = ' // TRIM( data_output_pr(i) ) //               &
     2024                                 ' is not implemented for bulk_cloud_model = .FALSE. ' //          &
    21622025                                 'and humidity = .FALSE.'
    21632026                CALL message( 'check_parameters', 'PA0095', 1, 2, 0, 6, 0 )
     
    21692032                dopr_unit(i)  = TRIM ( waterflux_output_unit )
    21702033                hom(:,2,49,:) = SPREAD( zw, 2, statistic_regions+1 )
    2171              ELSEIF( humidity .AND. bulk_cloud_model ) THEN
     2034             ELSEIF( humidity  .AND.  bulk_cloud_model ) THEN
    21722035                dopr_index(i) = 52
    21732036                dopr_unit(i)  = TRIM ( waterflux_output_unit )
    21742037                hom(:,2,52,:) = SPREAD( zw, 2, statistic_regions+1 )
    21752038             ELSE
    2176                 message_string = 'data_output_pr = ' //                        &
    2177                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    2178                                  'lemented for bulk_cloud_model = .FALSE. ' // &
     2039                message_string = 'data_output_pr = ' // TRIM( data_output_pr(i) ) //               &
     2040                                 ' is not implemented for bulk_cloud_model = .FALSE. ' //          &
    21792041                                 'and humidity = .FALSE.'
    21802042                CALL message( 'check_parameters', 'PA0095', 1, 2, 0, 6, 0 )
     
    21822044
    21832045          CASE ( 'wqv' )
    2184              IF ( humidity  .AND.  .NOT.  bulk_cloud_model )  THEN
     2046             IF ( humidity  .AND.  .NOT. bulk_cloud_model )  THEN
    21852047                dopr_index(i) = 50
    21862048                dopr_unit(i)  = TRIM ( waterflux_output_unit )
     
    21912053                hom(:,2,53,:) = SPREAD( zw, 2, statistic_regions+1 )
    21922054             ELSE
    2193                 message_string = 'data_output_pr = ' //                        &
    2194                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    2195                                  'lemented for bulk_cloud_model = .FALSE. ' // &
     2055                message_string = 'data_output_pr = ' // TRIM( data_output_pr(i) ) //               &
     2056                                 ' is not implemented for bulk_cloud_model = .FALSE. ' //          &
    21962057                                 'and humidity = .FALSE.'
    21972058                CALL message( 'check_parameters', 'PA0095', 1, 2, 0, 6, 0 )
     
    21992060
    22002061          CASE ( 'ql' )
    2201              IF (  .NOT.  bulk_cloud_model  .AND.  .NOT.  cloud_droplets )  THEN
    2202                 message_string = 'data_output_pr = ' //                        &
    2203                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    2204                                  'lemented for bulk_cloud_model = .FALSE. ' // &
     2062             IF ( .NOT. bulk_cloud_model  .AND.  .NOT. cloud_droplets )  THEN
     2063                message_string = 'data_output_pr = ' // TRIM( data_output_pr(i) ) //               &
     2064                                 ' is not implemented for bulk_cloud_model = .FALSE. ' //          &
    22052065                                 'and cloud_droplets = .FALSE.'
    22062066                CALL message( 'check_parameters', 'PA0096', 1, 2, 0, 6, 0 )
     
    22682128          CASE ( 'q*2' )
    22692129             IF (  .NOT.  humidity )  THEN
    2270                 message_string = 'data_output_pr = ' //                        &
    2271                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    2272                                  'lemented for humidity = .FALSE.'
     2130                message_string = 'data_output_pr = ' // TRIM( data_output_pr(i) ) //               &
     2131                                 ' is not implemented for humidity = .FALSE.'
    22732132                CALL message( 'check_parameters', 'PA0092', 1, 2, 0, 6, 0 )
    22742133             ELSE
     
    23052164          CASE ( 'w_subs' )
    23062165             IF (  .NOT.  large_scale_subsidence )  THEN
    2307                 message_string = 'data_output_pr = ' //                        &
    2308                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    2309                                  'lemented for large_scale_subsidence = .FALSE.'
     2166                message_string = 'data_output_pr = ' // TRIM( data_output_pr(i) ) //               &
     2167                                 ' is not implemented for large_scale_subsidence = .FALSE.'
    23102168                CALL message( 'check_parameters', 'PA0382', 1, 2, 0, 6, 0 )
    23112169             ELSE
     
    23172175          CASE ( 's*2' )
    23182176             IF (  .NOT.  passive_scalar )  THEN
    2319                 message_string = 'data_output_pr = ' //                        &
    2320                                  TRIM( data_output_pr(i) ) // ' is not imp' // &
    2321                                  'lemented for passive_scalar = .FALSE.'
     2177                message_string = 'data_output_pr = ' // TRIM( data_output_pr(i) ) //               &
     2178                                 ' is not implemented for passive_scalar = .FALSE.'
    23222179                CALL message( 'check_parameters', 'PA0185', 1, 2, 0, 6, 0 )
    23232180             ELSE
     
    23382195!
    23392196!--          Check for other modules
    2340              CALL module_interface_check_data_output_pr( data_output_pr(i), i, &
    2341                                                          unit, dopr_unit(i) )
     2197             CALL module_interface_check_data_output_pr( data_output_pr(i), i, unit, dopr_unit(i) )
    23422198
    23432199!
     
    23452201             IF ( unit == 'illegal' )  THEN
    23462202                IF ( data_output_pr_user(1) /= ' ' )  THEN
    2347                    message_string = 'illegal value for data_output_pr or ' //  &
    2348                                     'data_output_pr_user = "' //               &
    2349                                     TRIM( data_output_pr(i) ) // '"'
     2203                   message_string = 'illegal value for data_output_pr or ' //                      &
     2204                                    'data_output_pr_user = "' // TRIM( data_output_pr(i) ) // '"'
    23502205                   CALL message( 'check_parameters', 'PA0097', 1, 2, 0, 6, 0 )
    23512206                ELSE
    2352                    message_string = 'illegal value for data_output_pr = "' //  &
     2207                   message_string = 'illegal value for data_output_pr = "' //                      &
    23532208                                    TRIM( data_output_pr(i) ) // '"'
    23542209                   CALL message( 'check_parameters', 'PA0098', 1, 2, 0, 6, 0 )
     
    23712226       DO  WHILE ( data_output_user(j) /= ' '  .AND.  j <= 500 )
    23722227          IF ( i > 500 )  THEN
    2373              message_string = 'number of output quantitities given by data' // &
    2374                 '_output and data_output_user exceeds the limit of 500'
     2228             message_string = 'number of output quantitities given by data' //                     &
     2229                              '_output and data_output_user exceeds the limit of 500'
    23752230             CALL message( 'check_parameters', 'PA0102', 1, 2, 0, 6, 0 )
    23762231          ENDIF
     
    24012256       var = data_output(i)(1:ilen)
    24022257       IF ( ilen > 3 )  THEN
    2403           IF ( data_output(i)(ilen-2:ilen) == '_xy'  .OR.                      &
    2404                data_output(i)(ilen-2:ilen) == '_xz'  .OR.                      &
    2405                data_output(i)(ilen-2:ilen) == '_yz' )  THEN
     2258          IF ( data_output(i)(ilen-2:ilen) == '_xy'  .OR.  data_output(i)(ilen-2:ilen) == '_xz'    &
     2259               .OR.  data_output(i)(ilen-2:ilen) == '_yz' )  THEN
    24062260             k = 1                                             ! 2d data
    24072261             var = data_output(i)(1:ilen-3)
     
    24152269          CASE ( 'e' )
    24162270             IF ( constant_diffusion )  THEN
    2417                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    2418                                  'res constant_diffusion = .FALSE.'
     2271                message_string = 'output of "' // TRIM( var ) // '" requires ' //                  &
     2272                                 'constant_diffusion = .FALSE.'
    24192273                CALL message( 'check_parameters', 'PA0103', 1, 2, 0, 6, 0 )
    24202274             ENDIF
     
    24222276
    24232277          CASE ( 'thetal' )
    2424              IF (  .NOT. bulk_cloud_model )  THEN
    2425                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    2426                          'res bulk_cloud_model = .TRUE.'
     2278             IF ( .NOT. bulk_cloud_model )  THEN
     2279                message_string = 'output of "' // TRIM( var ) // '" requires ' //                  &
     2280                                 'bulk_cloud_model = .TRUE.'
    24272281                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
    24282282             ENDIF
     
    24302284
    24312285          CASE ( 'pc', 'pr' )
    2432              IF (  .NOT.  particle_advection )  THEN
    2433                 message_string = 'output of "' // TRIM( var ) // '" requir' // &
    2434                    'es a "particle_parameters"-NAMELIST in the parameter ' //  &
    2435                    'file (PARIN)'
     2286             IF ( .NOT. particle_advection )  THEN
     2287                message_string = 'output of "' // TRIM( var ) // '" requires ' //                  &
     2288                                 'a "particle_parameters"-NAMELIST in the parameter file (PARIN)'
    24362289                CALL message( 'check_parameters', 'PA0104', 1, 2, 0, 6, 0 )
    24372290             ENDIF
     
    24402293
    24412294          CASE ( 'q', 'thetav' )
    2442              IF (  .NOT.  humidity )  THEN
    2443                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    2444                                  'res humidity = .TRUE.'
     2295             IF ( .NOT. humidity )  THEN
     2296                message_string = 'output of "' // TRIM( var ) // '" requires humidity = .TRUE.'
    24452297                CALL message( 'check_parameters', 'PA0105', 1, 2, 0, 6, 0 )
    24462298             ENDIF
     
    24502302          CASE ( 'ql' )
    24512303             IF ( .NOT.  ( bulk_cloud_model  .OR.  cloud_droplets ) )  THEN
    2452                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    2453                       'res bulk_cloud_model = .TRUE. or cloud_droplets = .TRUE.'
     2304                message_string = 'output of "' // TRIM( var ) // '" requires ' //                  &
     2305                                 'bulk_cloud_model = .TRUE. or cloud_droplets = .TRUE.'
    24542306                CALL message( 'check_parameters', 'PA0106', 1, 2, 0, 6, 0 )
    24552307             ENDIF
     
    24572309
    24582310          CASE ( 'ql_c', 'ql_v', 'ql_vp' )
    2459              IF (  .NOT. cloud_droplets )  THEN
    2460                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    2461                                  'res cloud_droplets = .TRUE.'
     2311             IF ( .NOT. cloud_droplets )  THEN
     2312                message_string = 'output of "' // TRIM( var ) // '" requires ' //                  &
     2313                                 'cloud_droplets = .TRUE.'
    24622314                CALL message( 'check_parameters', 'PA0107', 1, 2, 0, 6, 0 )
    24632315             ENDIF
     
    24672319
    24682320          CASE ( 'qv' )
    2469              IF (  .NOT. bulk_cloud_model )  THEN
    2470                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    2471                                  'res bulk_cloud_model = .TRUE.'
     2321             IF ( .NOT. bulk_cloud_model )  THEN
     2322                message_string = 'output of "' // TRIM( var ) // '" requires ' //                  &
     2323                                 'bulk_cloud_model = .TRUE.'
    24722324                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
    24732325             ENDIF
     
    24752327
    24762328          CASE ( 's' )
    2477              IF (  .NOT. passive_scalar )  THEN
    2478                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    2479                                  'res passive_scalar = .TRUE.'
     2329             IF ( .NOT. passive_scalar )  THEN
     2330                message_string = 'output of "' // TRIM( var ) // '" requires ' //                  &
     2331                                 'passive_scalar = .TRUE.'
    24802332                CALL message( 'check_parameters', 'PA0110', 1, 2, 0, 6, 0 )
    24812333             ENDIF
     
    24902342             CONTINUE
    24912343
    2492           CASE ( 'ghf*', 'lwp*', 'ol*', 'qsurf*', 'qsws*', 'r_a*',             &
    2493                  'shf*', 'ssurf*', 'ssws*', 't*', 'tsurf*', 'us*',             &
    2494                  'z0*', 'z0h*', 'z0q*'  )
     2344          CASE ( 'ghf*', 'lwp*', 'ol*', 'qsurf*', 'qsws*', 'r_a*', 'shf*', 'ssurf*', 'ssws*', 't*',&
     2345                 'tsurf*', 'us*', 'z0*', 'z0h*', 'z0q*' )
    24952346             IF ( k == 0  .OR.  data_output(i)(ilen-2:ilen) /= '_xy' )  THEN
    2496                 message_string = 'illegal value for data_output: "' //         &
    2497                                  TRIM( var ) // '" & only 2d-horizontal ' //   &
    2498                                  'cross sections are allowed for this value'
     2347                message_string = 'illegal value for data_output: "' // TRIM( var ) //              &
     2348                                 '" & only 2d-horizontal cross sections are allowed for this value'
    24992349                CALL message( 'check_parameters', 'PA0111', 1, 2, 0, 6, 0 )
    25002350             ENDIF
    25012351
    25022352             IF ( TRIM( var ) == 'lwp*'  .AND.  .NOT. bulk_cloud_model )  THEN
    2503                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    2504                                  'res bulk_cloud_model = .TRUE.'
     2353                message_string = 'output of "' // TRIM( var ) // '" requires ' //                  &
     2354                                 'bulk_cloud_model = .TRUE.'
    25052355                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
    25062356             ENDIF
    25072357             IF ( TRIM( var ) == 'qsws*'  .AND.  .NOT.  humidity )  THEN
    2508                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    2509                                  'res humidity = .TRUE.'
     2358                message_string = 'output of "' // TRIM( var ) // '" requires humidity = .TRUE.'
    25102359                CALL message( 'check_parameters', 'PA0322', 1, 2, 0, 6, 0 )
    25112360             ENDIF
    25122361
    25132362             IF ( TRIM( var ) == 'ghf*'  .AND.  .NOT.  land_surface )  THEN
    2514                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    2515                                  'res land_surface = .TRUE.'
     2363                message_string = 'output of "' // TRIM( var ) // '" requires land_surface = .TRUE.'
    25162364                CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
    25172365             ENDIF
    25182366
    2519              IF ( ( TRIM( var ) == 'r_a*' .OR.  TRIM( var ) == 'ghf*' )        &
    2520                  .AND.  .NOT.  land_surface  .AND.  .NOT.  urban_surface )     &
    2521              THEN
    2522                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    2523                                  'res land_surface = .TRUE. or ' //            &
    2524                                  'urban_surface = .TRUE.'
     2367             IF ( (  TRIM( var ) == 'r_a*' .OR. TRIM( var ) == 'ghf*' )  .AND.  .NOT. land_surface &
     2368                   .AND.  .NOT. urban_surface )  THEN
     2369                message_string = 'output of "' // TRIM( var ) // '" requires ' //                  &
     2370                                 'land_surface = .TRUE. or ' // 'urban_surface = .TRUE.'
    25252371                CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
    25262372             ENDIF
    25272373
    2528              IF ( TRIM( var ) == 'ssws*'  .AND.  .NOT.  passive_scalar )  THEN
    2529                 message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    2530                                  'res passive_scalar = .TRUE.'
     2374             IF ( TRIM( var ) == 'ssws*'  .AND.  .NOT. passive_scalar )  THEN
     2375                message_string = 'output of "' // TRIM( var ) // '" requires ' //                  &
     2376                                 'passive_scalar = .TRUE.'
    25312377                CALL message( 'check_parameters', 'PA0361', 1, 2, 0, 6, 0 )
    25322378             ENDIF
     
    25472393             IF ( TRIM( var ) == 'z0h*'   )  unit = 'm'
    25482394!
    2549 !--          Output of surface latent and sensible heat flux will be in W/m2
    2550 !--          in case of natural- and urban-type surfaces, even if
    2551 !--          flux_output_mode is set to kinematic units.
     2395!--          Output of surface latent and sensible heat flux will be in W/m2 in case of natural- and
     2396!--          urban-type surfaces, even if flux_output_mode is set to kinematic units.
    25522397             IF ( land_surface  .OR.  urban_surface )  THEN
    25532398                IF ( TRIM( var ) == 'shf*'   )  unit = 'W/m2'
     
    25622407             IF ( unit == 'illegal' )  THEN
    25632408                IF ( data_output_user(1) /= ' ' )  THEN
    2564                    message_string = 'illegal value for data_output or ' //     &
    2565                          'data_output_user = "' // TRIM( data_output(i) ) // '"'
     2409                   message_string = 'illegal value for data_output or ' //                         &
     2410                                    'data_output_user = "' // TRIM( data_output(i) ) // '"'
    25662411                   CALL message( 'check_parameters', 'PA0114', 1, 2, 0, 6, 0 )
    25672412                ELSE
    2568                    message_string = 'illegal value for data_output = "' //     &
     2413                   message_string = 'illegal value for data_output = "' //                         &
    25692414                                    TRIM( data_output(i) ) // '"'
    25702415                   CALL message( 'check_parameters', 'PA0115', 1, 2, 0, 6, 0 )
     
    26142459!-- Averaged 2d or 3d output requires that an averaging interval has been set
    26152460    IF ( doav_n > 0  .AND.  averaging_interval == 0.0_wp )  THEN
    2616        WRITE( message_string, * )  'output of averaged quantity "',            &
    2617                                    TRIM( doav(1) ), '_av" requires to set a ', &
    2618                                    'non-zero averaging interval'
     2461       WRITE( message_string, * )  'output of averaged quantity "', TRIM( doav(1) ),               &
     2462                                   '_av" requires to set a ', 'non-zero averaging interval'
    26192463       CALL message( 'check_parameters', 'PA0323', 1, 2, 0, 6, 0 )
    26202464    ENDIF
     
    26382482    section(:,3) = section_yz
    26392483
    2640     IF ( ANY( data_output_xy ) .AND. .NOT. ANY( section(:,1) /= -9999 ) )  THEN
    2641        WRITE( message_string, * )  'section_xy not defined for requested '  // &
    2642                                    'xy-cross section output.&At least one ' // &
    2643                                    'cross section must be given.'
     2484    IF ( ANY( data_output_xy )  .AND.  .NOT. ANY( section(:,1) /= -9999 ) )  THEN
     2485       WRITE( message_string, * )  'section_xy not defined for requested xy-cross section ' //     &
     2486                                   'output.&At least one cross section must be given.'
    26442487       CALL message( 'check_parameters', 'PA0681', 1, 2, 0, 6, 0 )
    26452488    ENDIF
    2646     IF ( ANY( data_output_xz ) .AND. .NOT. ANY( section(:,2) /= -9999 ) )  THEN
    2647        WRITE( message_string, * )  'section_xz not defined for requested '  // &
    2648                                    'xz-cross section output.&At least one ' // &
    2649                                    'cross section must be given.'
     2489    IF ( ANY( data_output_xz )  .AND.  .NOT. ANY( section(:,2) /= -9999 ) )  THEN
     2490       WRITE( message_string, * )  'section_xz not defined for requested xz-cross section ' //     &
     2491                                   'output.&At least one cross section must be given.'
    26502492       CALL message( 'check_parameters', 'PA0681', 1, 2, 0, 6, 0 )
    26512493    ENDIF
    2652     IF ( ANY( data_output_yz ) .AND. .NOT. ANY( section(:,3) /= -9999 ) )  THEN
    2653        WRITE( message_string, * )  'section_yz not defined for requested '  // &
    2654                                    'yz-cross section output.&At least one ' // &
    2655                                    'cross section must be given.'
     2494    IF ( ANY( data_output_yz )  .AND.  .NOT. ANY( section(:,3) /= -9999 ) )  THEN
     2495       WRITE( message_string, * )  'section_yz not defined for requested yz-cross section ' //     &
     2496                                   'output.&At least one cross section must be given.'
    26562497       CALL message( 'check_parameters', 'PA0681', 1, 2, 0, 6, 0 )
    26572498    ENDIF
     
    26812522!-- Check mask conditions
    26822523    DO mid = 1, max_masks
    2683        IF ( data_output_masks(mid,1) /= ' '  .OR.                              &
    2684             data_output_masks_user(mid,1) /= ' ' ) THEN
     2524       IF ( data_output_masks(mid,1) /= ' '  .OR.  data_output_masks_user(mid,1) /= ' ' )  THEN
    26852525          masks = masks + 1
    26862526       ENDIF
     
    26882528
    26892529    IF ( masks < 0  .OR.  masks > max_masks )  THEN
    2690        WRITE( message_string, * )  'illegal value: masks must be >= 0 and ',   &
    2691             '<= ', max_masks, ' (=max_masks)'
     2530       WRITE( message_string, * )  'illegal value: masks must be >= 0 and ', '<= ', max_masks,     &
     2531              ' (=max_masks)'
    26922532       CALL message( 'check_parameters', 'PA0325', 1, 2, 0, 6, 0 )
    26932533    ENDIF
     
    26972537       mask_scale(3) = mask_scale_z
    26982538       IF ( ANY( mask_scale <= 0.0_wp ) )  THEN
    2699           WRITE( message_string, * )                                           &
    2700                'illegal value: mask_scale_x, mask_scale_y and mask_scale_z',   &
    2701                'must be > 0.0'
     2539          WRITE( message_string, * )  'illegal value: mask_scale_x, mask_scale_y and mask_scale_z',&
     2540                 'must be > 0.0'
    27022541          CALL message( 'check_parameters', 'PA0326', 1, 2, 0, 6, 0 )
    27032542       ENDIF
    27042543!
    2705 !--    Generate masks for masked data output
    2706 !--    Parallel netcdf output is not tested so far for masked data, hence
    2707 !--    netcdf_data_format is switched back to non-parallel output.
     2544!--    Generate masks for masked data output.
     2545!--    Parallel netcdf output is not tested so far for masked data, hence netcdf_data_format is
     2546!--    switched back to non-parallel output.
    27082547       netcdf_data_format_save = netcdf_data_format
    27092548       IF ( netcdf_data_format > 4 )  THEN
    27102549          IF ( netcdf_data_format == 5 ) netcdf_data_format = 3
    27112550          IF ( netcdf_data_format == 6 ) netcdf_data_format = 4
    2712           message_string = 'netCDF file formats '//                            &
    2713                            '5 (parallel netCDF 4) and ' //                     &
    2714                            '6 (parallel netCDF 4 Classic model) '//            &
    2715                            '& are currently not supported (not yet tested) ' //&
    2716                            'for masked data. &Using respective non-parallel' //&
     2551          message_string = 'netCDF file formats '// '5 (parallel netCDF 4) and 6 (parallel ' //    &
     2552                           'netCDF 4 Classic model) & are currently not supported (not yet ' //    &
     2553                           'tested) for masked data. &Using respective non-parallel' //            &
    27172554                           ' output for masked data.'
    27182555          CALL message( 'check_parameters', 'PA0383', 0, 0, 0, 6, 0 )
     
    27282565       CONTINUE
    27292566#else
    2730        message_string = 'netCDF: netCDF4 format requested but no ' //          &
    2731                         'cpp-directive __netcdf4 given & switch '  //          &
    2732                         'back to 64-bit offset format'
     2567       message_string = 'netCDF: netCDF4 format requested but no ' //                              &
     2568                        'cpp-directive __netcdf4 given & switch back to 64-bit offset format'
    27332569       CALL message( 'check_parameters', 'PA0171', 0, 1, 0, 6, 0 )
    27342570       netcdf_data_format = 2
     
    27392575       CONTINUE
    27402576#else
    2741        message_string = 'netCDF: netCDF4 parallel output requested but no ' // &
    2742                         'cpp-directive __netcdf4_parallel given & switch '   //&
     2577       message_string = 'netCDF: netCDF4 parallel output requested but no ' //                     &
     2578                        'cpp-directive __netcdf4_parallel given & switch ' //                      &
    27432579                        'back to netCDF4 non-parallel output'
    27442580       CALL message( 'check_parameters', 'PA0099', 0, 1, 0, 6, 0 )
     
    27492585!
    27502586!-- Calculate fixed number of output time levels for parallel netcdf output.
    2751 !-- The time dimension has to be defined as limited for parallel output,
    2752 !-- because otherwise the I/O performance drops significantly.
     2587!-- The time dimension has to be defined as limited for parallel output, because otherwise the I/O
     2588!-- performance drops significantly.
    27532589    IF ( netcdf_data_format > 4 )  THEN
    27542590
    27552591!
    2756 !--    Check if any of the follwoing data output interval is 0.0s, which is
    2757 !--    not allowed for parallel output.
     2592!--    Check if any of the follwoing data output interval is 0.0s, which is not allowed for parallel
     2593!--    output.
    27582594       CALL check_dt_do( dt_do3d,           'dt_do3d'           )
    27592595       CALL check_dt_do( dt_do2d_xy,        'dt_do2d_xy'        )
     
    27622598       CALL check_dt_do( dt_data_output_av, 'dt_data_output_av' )
    27632599
    2764 !--    Set needed time levels (ntdim) to
    2765 !--    saved time levels + to be saved time levels.
    2766        ntdim_3d(0) = do3d_time_count(0) + CEILING(                                    &
    2767                      ( end_time - MAX(                                                &
    2768                          MERGE(skip_time_do3d, skip_time_do3d + spinup_time,          &
    2769                                data_output_during_spinup ),                           &
    2770                          simulated_time_at_begin )                                    &
     2600!--    Set needed time levels (ntdim) to saved time levels + to be saved time levels.
     2601       ntdim_3d(0) = do3d_time_count(0) + CEILING(                                                 &
     2602                     ( end_time - MAX(                                                             &
     2603                         MERGE( skip_time_do3d, skip_time_do3d + spinup_time,                      &
     2604                                data_output_during_spinup ),                                       &
     2605                         simulated_time_at_begin )                                                 &
    27712606                     ) / dt_do3d )
    27722607       IF ( do3d_at_begin ) ntdim_3d(0) = ntdim_3d(0) + 1
    27732608
    2774        ntdim_3d(1) = do3d_time_count(1) + CEILING(                                    &
    2775                      ( end_time - MAX(                                                &
    2776                          MERGE(   skip_time_data_output_av, skip_time_data_output_av  &
    2777                                 + spinup_time, data_output_during_spinup ),           &
    2778                          simulated_time_at_begin )                                    &
     2609       ntdim_3d(1) = do3d_time_count(1) + CEILING(                                                 &
     2610                     ( end_time - MAX(                                                             &
     2611                         MERGE( skip_time_data_output_av, skip_time_data_output_av + spinup_time,  &
     2612                                data_output_during_spinup ),                                       &
     2613                         simulated_time_at_begin )                                                 &
    27792614                     ) / dt_data_output_av )
    27802615
    2781        ntdim_2d_xy(0) = do2d_xy_time_count(0) + CEILING(                              &
    2782                         ( end_time - MAX(                                             &
    2783                            MERGE(skip_time_do2d_xy, skip_time_do2d_xy + spinup_time,  &
    2784                                  data_output_during_spinup ),                         &
    2785                            simulated_time_at_begin )                                  &
     2616       ntdim_2d_xy(0) = do2d_xy_time_count(0) + CEILING(                                           &
     2617                        ( end_time - MAX(                                                          &
     2618                            MERGE( skip_time_do2d_xy, skip_time_do2d_xy + spinup_time,             &
     2619                                   data_output_during_spinup ),                                    &
     2620                            simulated_time_at_begin )                                              &
    27862621                        ) / dt_do2d_xy )
    27872622
    2788        ntdim_2d_xz(0) = do2d_xz_time_count(0) + CEILING(                              &
    2789                         ( end_time - MAX(                                             &
    2790                          MERGE(skip_time_do2d_xz, skip_time_do2d_xz + spinup_time,    &
    2791                                data_output_during_spinup ),                           &
    2792                          simulated_time_at_begin )                                    &
     2623       ntdim_2d_xz(0) = do2d_xz_time_count(0) + CEILING(                                           &
     2624                        ( end_time - MAX(                                                          &
     2625                            MERGE( skip_time_do2d_xz, skip_time_do2d_xz + spinup_time,             &
     2626                                   data_output_during_spinup ),                                    &
     2627                            simulated_time_at_begin )                                              &
    27932628                        ) / dt_do2d_xz )
    27942629
    2795        ntdim_2d_yz(0) = do2d_yz_time_count(0) + CEILING(                              &
    2796                         ( end_time - MAX(                                             &
    2797                          MERGE(skip_time_do2d_yz, skip_time_do2d_yz + spinup_time,    &
    2798                                data_output_during_spinup ),                           &
    2799                          simulated_time_at_begin )                                    &
     2630       ntdim_2d_yz(0) = do2d_yz_time_count(0) + CEILING(                                           &
     2631                        ( end_time - MAX(                                                          &
     2632                            MERGE( skip_time_do2d_yz, skip_time_do2d_yz + spinup_time,             &
     2633                                   data_output_during_spinup ),                                    &
     2634                            simulated_time_at_begin )                                              &
    28002635                        ) / dt_do2d_yz )
    28012636
     
    28062641       ENDIF
    28072642!
    2808 !--    Please note, for averaged 2D data skip_time_data_output_av is the relavant
    2809 !--    output control parameter.
    2810        ntdim_2d_xy(1) = do2d_xy_time_count(1) + CEILING(                              &
    2811                      ( end_time - MAX( MERGE( skip_time_data_output_av,               &
    2812                                               skip_time_data_output_av + spinup_time, &
    2813                                               data_output_during_spinup ),            &
    2814                                        simulated_time_at_begin )                      &
    2815                      ) / dt_data_output_av )
    2816 
    2817        ntdim_2d_xz(1) = do2d_xz_time_count(1) + CEILING(                              &
    2818                      ( end_time - MAX( MERGE( skip_time_data_output_av,               &
    2819                                               skip_time_data_output_av + spinup_time, &
    2820                                               data_output_during_spinup ),            &
    2821                                        simulated_time_at_begin )                      &
    2822                      ) / dt_data_output_av )
    2823 
    2824        ntdim_2d_yz(1) = do2d_yz_time_count(1) + CEILING(                              &
    2825                      ( end_time - MAX( MERGE( skip_time_data_output_av,               &
    2826                                               skip_time_data_output_av + spinup_time, &
    2827                                               data_output_during_spinup ),            &
    2828                                        simulated_time_at_begin )                      &
    2829                      ) / dt_data_output_av )
     2643!--    Please note, for averaged 2D data skip_time_data_output_av is the relavant output control
     2644!--    parameter.
     2645       ntdim_2d_xy(1) = do2d_xy_time_count(1) + CEILING(                                           &
     2646                        ( end_time - MAX( MERGE( skip_time_data_output_av,                         &
     2647                                                 skip_time_data_output_av + spinup_time,          &
     2648                                                 data_output_during_spinup ),                      &
     2649                                          simulated_time_at_begin )                                &
     2650                        ) / dt_data_output_av )
     2651
     2652       ntdim_2d_xz(1) = do2d_xz_time_count(1) + CEILING(                                           &
     2653                        ( end_time - MAX( MERGE( skip_time_data_output_av,                         &
     2654                                                 skip_time_data_output_av + spinup_time,          &
     2655                                                 data_output_during_spinup ),                      &
     2656                                          simulated_time_at_begin )                                &
     2657                        ) / dt_data_output_av )
     2658
     2659       ntdim_2d_yz(1) = do2d_yz_time_count(1) + CEILING(                                           &
     2660                        ( end_time - MAX( MERGE( skip_time_data_output_av,                         &
     2661                                                 skip_time_data_output_av + spinup_time,          &
     2662                                                 data_output_during_spinup ),                      &
     2663                                          simulated_time_at_begin )                                &
     2664                        ) / dt_data_output_av )
    28302665
    28312666    ENDIF
     
    28392674       ELSE
    28402675          IF ( prandtl_number < 0.0_wp )  THEN
    2841              WRITE( message_string, * )  'prandtl_number = ', prandtl_number,  &
    2842                                          ' < 0.0'
     2676             WRITE( message_string, * )  'prandtl_number = ', prandtl_number, ' < 0.0'
    28432677             CALL message( 'check_parameters', 'PA0122', 1, 2, 0, 6, 0 )
    28442678          ENDIF
     
    28462680
    28472681          IF ( constant_flux_layer )  THEN
    2848              message_string = 'constant_flux_layer is not allowed with fixed ' &
    2849                               // 'value of km'
     2682             message_string = 'constant_flux_layer is not allowed with fixed value of km'
    28502683             CALL message( 'check_parameters', 'PA0123', 1, 2, 0, 6, 0 )
    28512684          ENDIF
     
    28542687
    28552688!
    2856 !-- In case of non-cyclic lateral boundaries and a damping layer for the
    2857 !-- potential temperature, check the width of the damping layer
     2689!-- In case of non-cyclic lateral boundaries and a damping layer for the potential temperature,
     2690!-- check the width of the damping layer
    28582691    IF ( bc_lr /= 'cyclic' ) THEN
    2859        IF ( pt_damping_width < 0.0_wp  .OR.                                    &
    2860             pt_damping_width > REAL( (nx+1) * dx ) )  THEN
     2692       IF ( pt_damping_width < 0.0_wp  .OR.  pt_damping_width > REAL( (nx+1) * dx ) )  THEN
    28612693          message_string = 'pt_damping_width out of range'
    28622694          CALL message( 'check_parameters', 'PA0124', 1, 2, 0, 6, 0 )
     
    28652697
    28662698    IF ( bc_ns /= 'cyclic' )  THEN
    2867        IF ( pt_damping_width < 0.0_wp  .OR.                                    &
    2868             pt_damping_width > REAL( (ny+1) * dy ) )  THEN
     2699       IF ( pt_damping_width < 0.0_wp  .OR.  pt_damping_width > REAL( (ny+1) * dy ) )  THEN
    28692700          message_string = 'pt_damping_width out of range'
    28702701          CALL message( 'check_parameters', 'PA0124', 1, 2, 0, 6, 0 )
     
    28752706!-- Check value range for zeta = z/L
    28762707    IF ( zeta_min >= zeta_max )  THEN
    2877        WRITE( message_string, * )  'zeta_min = ', zeta_min, ' must be less ', &
    2878                                    'than zeta_max = ', zeta_max
     2708       WRITE( message_string, * )  'zeta_min = ', zeta_min, ' must be less ', 'than zeta_max = ', &
     2709              zeta_max
    28792710       CALL message( 'check_parameters', 'PA0125', 1, 2, 0, 6, 0 )
    28802711    ENDIF
     
    28822713!
    28832714!-- Check random generator
    2884     IF ( (random_generator /= 'system-specific'      .AND.                     &
    2885           random_generator /= 'random-parallel'   )  .AND.                     &
     2715    IF ( (random_generator /= 'system-specific'      .AND.                                         &
     2716          random_generator /= 'random-parallel'   )  .AND.                                         &
    28862717          random_generator /= 'numerical-recipes' )  THEN
    2887        message_string = 'unknown random generator: random_generator = "' //    &
     2718       message_string = 'unknown random generator: random_generator = "' //                        &
    28882719                        TRIM( random_generator ) // '"'
    28892720       CALL message( 'check_parameters', 'PA0135', 1, 2, 0, 6, 0 )
     
    29012732       ENDIF
    29022733    ELSEIF ( disturbance_level_b < zu(3) )  THEN
    2903        WRITE( message_string, * )  'disturbance_level_b = ',                   &
    2904                            disturbance_level_b, ' must be >= ', zu(3), '(zu(3))'
     2734       WRITE( message_string, * )  'disturbance_level_b = ', disturbance_level_b, ' must be >= ',  &
     2735              zu(3), '(zu(3))'
    29052736       CALL message( 'check_parameters', 'PA0126', 1, 2, 0, 6, 0 )
    29062737    ELSEIF ( disturbance_level_b > zu(nzt-2) )  THEN
    2907        WRITE( message_string, * )  'disturbance_level_b = ',                   &
    2908                    disturbance_level_b, ' must be <= ', zu(nzt-2), '(zu(nzt-2))'
     2738       WRITE( message_string, * )  'disturbance_level_b = ', disturbance_level_b, ' must be <= ',  &
     2739              zu(nzt-2), '(zu(nzt-2))'
    29092740       CALL message( 'check_parameters', 'PA0127', 1, 2, 0, 6, 0 )
    29102741    ELSE
     
    29262757       ENDIF
    29272758    ELSEIF ( disturbance_level_t > zu(nzt-2) )  THEN
    2928        WRITE( message_string, * )  'disturbance_level_t = ',                   &
    2929                    disturbance_level_t, ' must be <= ', zu(nzt-2), '(zu(nzt-2))'
     2759       WRITE( message_string, * )  'disturbance_level_t = ', disturbance_level_t, ' must be <= ',  &
     2760              zu(nzt-2), '(zu(nzt-2))'
    29302761       CALL message( 'check_parameters', 'PA0128', 1, 2, 0, 6, 0 )
    29312762    ELSEIF ( disturbance_level_t < disturbance_level_b )  THEN
    2932        WRITE( message_string, * )  'disturbance_level_t = ',                   &
    2933                    disturbance_level_t, ' must be >= disturbance_level_b = ',  &
    2934                    disturbance_level_b
     2763       WRITE( message_string, * )  'disturbance_level_t = ', disturbance_level_t,                  &
     2764             ' must be >= disturbance_level_b = ', disturbance_level_b
    29352765       CALL message( 'check_parameters', 'PA0129', 1, 2, 0, 6, 0 )
    29362766    ELSE
     
    29452775!
    29462776!-- Check again whether the levels determined this way are ok.
    2947 !-- Error may occur at automatic determination and too few grid points in
    2948 !-- z-direction.
     2777!-- Error may occur at automatic determination and too few grid points in z-direction.
    29492778    IF ( disturbance_level_ind_t < disturbance_level_ind_b )  THEN
    2950        WRITE( message_string, * )  'disturbance_level_ind_t = ',               &
    2951                 disturbance_level_ind_t, ' must be >= ',                       &
    2952                 'disturbance_level_ind_b = ', disturbance_level_ind_b
     2779       WRITE( message_string, * )  'disturbance_level_ind_t = ', disturbance_level_ind_t,          &
     2780              ' must be >= ', 'disturbance_level_ind_b = ', disturbance_level_ind_b
    29532781       CALL message( 'check_parameters', 'PA0130', 1, 2, 0, 6, 0 )
    29542782    ENDIF
     
    29562784!
    29572785!-- Determine the horizontal index range for random perturbations.
    2958 !-- In case of non-cyclic horizontal boundaries, no perturbations are imposed
    2959 !-- near the inflow and the perturbation area is further limited to ...(1)
    2960 !-- after the initial phase of the flow.
     2786!-- In case of non-cyclic horizontal boundaries, no perturbations are imposed near the inflow and
     2787!-- the perturbation area is further limited to ...(1) after the initial phase of the flow.
    29612788
    29622789    IF ( bc_lr /= 'cyclic' )  THEN
     
    29642791          inflow_disturbance_begin = MIN( 10, nx/2 )
    29652792       ENDIF
    2966        IF ( inflow_disturbance_begin < 0  .OR.  inflow_disturbance_begin > nx )&
    2967        THEN
     2793       IF ( inflow_disturbance_begin < 0  .OR.  inflow_disturbance_begin > nx )  THEN
    29682794          message_string = 'inflow_disturbance_begin out of range'
    29692795          CALL message( 'check_parameters', 'PA0131', 1, 2, 0, 6, 0 )
     
    29722798          inflow_disturbance_end = MIN( 100, 3*nx/4 )
    29732799       ENDIF
    2974        IF ( inflow_disturbance_end < 0  .OR.  inflow_disturbance_end > nx )    &
    2975        THEN
     2800       IF ( inflow_disturbance_end < 0  .OR.  inflow_disturbance_end > nx )  THEN
    29762801          message_string = 'inflow_disturbance_end out of range'
    29772802          CALL message( 'check_parameters', 'PA0132', 1, 2, 0, 6, 0 )
     
    29812806          inflow_disturbance_begin = MIN( 10, ny/2 )
    29822807       ENDIF
    2983        IF ( inflow_disturbance_begin < 0  .OR.  inflow_disturbance_begin > ny )&
    2984        THEN
     2808       IF ( inflow_disturbance_begin < 0  .OR.  inflow_disturbance_begin > ny )  THEN
    29852809          message_string = 'inflow_disturbance_begin out of range'
    29862810          CALL message( 'check_parameters', 'PA0131', 1, 2, 0, 6, 0 )
     
    29892813          inflow_disturbance_end = MIN( 100, 3*ny/4 )
    29902814       ENDIF
    2991        IF ( inflow_disturbance_end < 0  .OR.  inflow_disturbance_end > ny )    &
    2992        THEN
     2815       IF ( inflow_disturbance_end < 0  .OR.  inflow_disturbance_end > ny )  THEN
    29932816          message_string = 'inflow_disturbance_end out of range'
    29942817          CALL message( 'check_parameters', 'PA0132', 1, 2, 0, 6, 0 )
     
    30452868
    30462869!
    3047 !-- A turbulent inflow requires Dirichlet conditions at the respective inflow
    3048 !-- boundary (so far, a turbulent inflow is realized from the left side only)
     2870!-- A turbulent inflow requires Dirichlet conditions at the respective inflow boundary (so far, a
     2871!-- turbulent inflow is realized from the left side only).
    30492872    IF ( turbulent_inflow  .AND.  bc_lr /= 'dirichlet/radiation' )  THEN
    3050        message_string = 'turbulent_inflow = .T. requires a Dirichlet ' //      &
     2873       message_string = 'turbulent_inflow = .T. requires a Dirichlet ' //                          &
    30512874                        'condition at the inflow boundary'
    30522875       CALL message( 'check_parameters', 'PA0133', 1, 2, 0, 6, 0 )
     
    30542877
    30552878!
    3056 !-- Turbulent inflow requires that 3d arrays have been cyclically filled with
    3057 !-- data from prerun in the first main run
    3058     IF ( turbulent_inflow  .AND.  initializing_actions /= 'cyclic_fill'  .AND. &
     2879!-- Turbulent inflow requires that 3d arrays have been cyclically filled with data from prerun in
     2880!-- the first main run
     2881    IF ( turbulent_inflow  .AND.  initializing_actions /= 'cyclic_fill'  .AND.                     &
    30592882         initializing_actions /= 'read_restart_data' )  THEN
    3060        message_string = 'turbulent_inflow = .T. requires ' //                  &
    3061                         'initializing_actions = ''cyclic_fill'' or ' //        &
     2883       message_string = 'turbulent_inflow = .T. requires ' //                                      &
     2884                        'initializing_actions = ''cyclic_fill'' or ' //                            &
    30622885                        'initializing_actions = ''read_restart_data'' '
    30632886       CALL message( 'check_parameters', 'PA0055', 1, 2, 0, 6, 0 )
     
    30712894!--    Calculate the index of the recycling plane
    30722895       IF ( recycling_width <= dx  .OR.  recycling_width >= nx * dx )  THEN
    3073           WRITE( message_string, * )  'illegal value for recycling_width: ',   &
    3074                                       recycling_width
     2896          WRITE( message_string, * )  'illegal value for recycling_width: ', recycling_width
    30752897          CALL message( 'check_parameters', 'PA0134', 1, 2, 0, 6, 0 )
    30762898       ENDIF
     
    30802902!
    30812903!--   Check for correct input of recycling method for thermodynamic quantities
    3082        IF ( TRIM( recycling_method_for_thermodynamic_quantities ) /= 'turbulent_fluctuation' .AND. &
     2904       IF ( TRIM( recycling_method_for_thermodynamic_quantities ) /= 'turbulent_fluctuation'  .AND.&
    30832905            TRIM( recycling_method_for_thermodynamic_quantities ) /= 'absolute_value' )  THEN
    30842906          WRITE( message_string, * )  'unknown recycling method for thermodynamic quantities: ',   &
     
    30922914    IF ( turbulent_outflow )  THEN
    30932915!
    3094 !--    Turbulent outflow requires Dirichlet conditions at the respective inflow
    3095 !--    boundary (so far, a turbulent outflow is realized at the right side only)
     2916!--    Turbulent outflow requires Dirichlet conditions at the respective inflow boundary (so far, a
     2917!--    turbulent outflow is realized at the right side only).
    30962918       IF ( bc_lr /= 'dirichlet/radiation' )  THEN
    3097           message_string = 'turbulent_outflow = .T. requires ' //              &
    3098                            'bc_lr = "dirichlet/radiation"'
     2919          message_string = 'turbulent_outflow = .T. requires bc_lr = "dirichlet/radiation"'
    30992920          CALL message( 'check_parameters', 'PA0038', 1, 2, 0, 6, 0 )
    31002921       ENDIF
    31012922!
    31022923!--    The ouflow-source plane must lay inside the model domain
    3103        IF ( outflow_source_plane < dx  .OR.  &
    3104             outflow_source_plane > nx * dx )  THEN
    3105           WRITE( message_string, * )  'illegal value for outflow_source'//     &
    3106                                       '_plane: ', outflow_source_plane
     2924       IF ( outflow_source_plane < dx  .OR.  outflow_source_plane > nx * dx )  THEN
     2925          WRITE( message_string, * )  'illegal value for outflow_source'// '_plane: ',             &
     2926                 outflow_source_plane
    31072927          CALL message( 'check_parameters', 'PA0145', 1, 2, 0, 6, 0 )
    31082928       ENDIF
     
    31162936          damp_level_ind_1d = nzt + 1
    31172937       ELSEIF ( damp_level_1d < 0.0_wp  .OR.  damp_level_1d > zu(nzt+1) )  THEN
    3118           WRITE( message_string, * )  'damp_level_1d = ', damp_level_1d,       &
    3119                  ' must be >= 0.0 and <= ', zu(nzt+1), '(zu(nzt+1))'
     2938          WRITE( message_string, * )  'damp_level_1d = ', damp_level_1d, ' must be >= 0.0 and <= ',&
     2939                 zu(nzt+1), '(zu(nzt+1))'
    31202940          CALL message( 'check_parameters', 'PA0136', 1, 2, 0, 6, 0 )
    31212941       ELSE
     
    31312951!
    31322952!-- Check some other 1d-model parameters
    3133     IF ( TRIM( mixing_length_1d ) /= 'as_in_3d_model'  .AND.                   &
     2953    IF ( TRIM( mixing_length_1d ) /= 'as_in_3d_model'  .AND.                                       &
    31342954         TRIM( mixing_length_1d ) /= 'blackadar' )  THEN
    3135        message_string = 'mixing_length_1d = "' // TRIM( mixing_length_1d ) //  &
    3136                         '" is unknown'
     2955       message_string = 'mixing_length_1d = "' // TRIM( mixing_length_1d ) // '" is unknown'
    31372956       CALL message( 'check_parameters', 'PA0137', 1, 2, 0, 6, 0 )
    31382957    ENDIF
    3139     IF ( TRIM( dissipation_1d ) /= 'as_in_3d_model'  .AND.                     &
    3140          TRIM( dissipation_1d ) /= 'detering'  .AND.                           &
     2958    IF ( TRIM( dissipation_1d ) /= 'as_in_3d_model'  .AND.                                         &
     2959         TRIM( dissipation_1d ) /= 'detering'        .AND.                                         &
    31412960         TRIM( dissipation_1d ) /= 'prognostic' )  THEN
    3142        message_string = 'dissipation_1d = "' // TRIM( dissipation_1d ) //      &
    3143                         '" is unknown'
     2961       message_string = 'dissipation_1d = "' // TRIM( dissipation_1d ) // '" is unknown'
    31442962       CALL message( 'check_parameters', 'PA0138', 1, 2, 0, 6, 0 )
    31452963    ENDIF
    3146     IF ( TRIM( mixing_length_1d ) /= 'as_in_3d_model'  .AND.                   &
     2964    IF ( TRIM( mixing_length_1d ) /= 'as_in_3d_model'  .AND.                                       &
    31472965         TRIM( dissipation_1d ) == 'as_in_3d_model' )  THEN
    3148        message_string = 'dissipation_1d = "' // TRIM( dissipation_1d ) //      &
     2966       message_string = 'dissipation_1d = "' // TRIM( dissipation_1d ) //                          &
    31492967                        '" requires mixing_length_1d = "as_in_3d_model"'
    31502968       CALL message( 'check_parameters', 'PA0485', 1, 2, 0, 6, 0 )
     
    31522970
    31532971!
    3154 !-- Set time for the next user defined restart (time_restart is the
    3155 !-- internal parameter for steering restart events)
     2972!-- Set time for the next user defined restart (time_restart is the internal parameter for steering
     2973!-- restart events)
    31562974    IF ( restart_time /= 9999999.9_wp )  THEN
    31572975       IF ( restart_time > time_since_reference_point )  THEN
     
    31602978    ELSE
    31612979!
    3162 !--    In case of a restart run, set internal parameter to default (no restart)
    3163 !--    if the NAMELIST-parameter restart_time is omitted
     2980!--    In case of a restart run, set internal parameter to default (no restart) if the
     2981!--    NAMELIST-parameter restart_time is omitted
    31642982       time_restart = 9999999.9_wp
    31652983    ENDIF
     
    31682986!-- Check pressure gradient conditions
    31692987    IF ( dp_external  .AND.  conserve_volume_flow )  THEN
    3170        WRITE( message_string, * )  'Both dp_external and conserve_volume_flo', &
    3171             'w are .TRUE. but one of them must be .FALSE.'
     2988       WRITE( message_string, * )  'Both dp_external and conserve_volume_flo',                     &
     2989              'w are .TRUE. but one of them must be .FALSE.'
    31722990       CALL message( 'check_parameters', 'PA0150', 1, 2, 0, 6, 0 )
    31732991    ENDIF
    31742992    IF ( dp_external )  THEN
    31752993       IF ( dp_level_b < zu(nzb)  .OR.  dp_level_b > zu(nzt) )  THEN
    3176           WRITE( message_string, * )  'dp_level_b = ', dp_level_b, ' is out ', &
    3177                ' of range [zu(nzb), zu(nzt)]'
     2994          WRITE( message_string, * )  'dp_level_b = ', dp_level_b, ' is out ',                     &
     2995                 ' of range [zu(nzb), zu(nzt)]'
    31782996          CALL message( 'check_parameters', 'PA0151', 1, 2, 0, 6, 0 )
    31792997       ENDIF
    31802998       IF ( .NOT. ANY( dpdxy /= 0.0_wp ) )  THEN
    3181           WRITE( message_string, * )  'dp_external is .TRUE. but dpdxy is ze', &
    3182                'ro, i.e. the external pressure gradient will not be applied'
     2999          WRITE( message_string, * )  'dp_external is .TRUE. but dpdxy is ze',                     &
     3000                 'ro, i.e. the external pressure gradient will not be applied'
    31833001          CALL message( 'check_parameters', 'PA0152', 0, 1, 0, 6, 0 )
    31843002       ENDIF
    31853003    ENDIF
    31863004    IF ( ANY( dpdxy /= 0.0_wp )  .AND.  .NOT.  dp_external )  THEN
    3187        WRITE( message_string, * )  'dpdxy is nonzero but dp_external is ',     &
    3188             '.FALSE., i.e. the external pressure gradient & will not be applied'
     3005       WRITE( message_string, * )  'dpdxy is nonzero but dp_external is ',                         &
     3006              '.FALSE., i.e. the external pressure gradient & will not be applied'
    31893007       CALL message( 'check_parameters', 'PA0153', 0, 1, 0, 6, 0 )
    31903008    ENDIF
     
    31943012          conserve_volume_flow_mode = 'initial_profiles'
    31953013
    3196        ELSEIF ( TRIM( conserve_volume_flow_mode ) /= 'initial_profiles' .AND.  &
    3197             TRIM( conserve_volume_flow_mode ) /= 'bulk_velocity' )  THEN
    3198           WRITE( message_string, * )  'unknown conserve_volume_flow_mode: ',   &
    3199                conserve_volume_flow_mode
     3014       ELSEIF ( TRIM( conserve_volume_flow_mode ) /= 'initial_profiles'  .AND.                     &
     3015                TRIM( conserve_volume_flow_mode ) /= 'bulk_velocity' )  THEN
     3016          WRITE( message_string, * )  'unknown conserve_volume_flow_mode: ',                       &
     3017                 conserve_volume_flow_mode
    32003018          CALL message( 'check_parameters', 'PA0154', 1, 2, 0, 6, 0 )
    32013019       ENDIF
    3202        IF ( (bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic')  .AND.                &
    3203           TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
    3204           WRITE( message_string, * )  'non-cyclic boundary conditions ',       &
    3205                'require  conserve_volume_flow_mode = ''initial_profiles'''
     3020       IF ( ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic')  .AND.                                   &
     3021            TRIM( conserve_volume_flow_mode ) == 'bulk_velocity' )  THEN
     3022          WRITE( message_string, * )  'non-cyclic boundary conditions ',                           &
     3023                 'require  conserve_volume_flow_mode = ''initial_profiles'''
    32063024          CALL message( 'check_parameters', 'PA0155', 1, 2, 0, 6, 0 )
    32073025       ENDIF
    32083026    ENDIF
    3209     IF ( ( u_bulk /= 0.0_wp  .OR.  v_bulk /= 0.0_wp )  .AND.                   &
    3210          ( .NOT. conserve_volume_flow  .OR.                                    &
    3211          TRIM( conserve_volume_flow_mode ) /= 'bulk_velocity' ) )  THEN
    3212        WRITE( message_string, * )  'nonzero bulk velocity requires ',          &
    3213             'conserve_volume_flow = .T. and ',                                 &
    3214             'conserve_volume_flow_mode = ''bulk_velocity'''
     3027    IF ( ( u_bulk /= 0.0_wp .OR. v_bulk /= 0.0_wp )  .AND.                                         &
     3028         ( .NOT. conserve_volume_flow .OR. TRIM( conserve_volume_flow_mode ) /= 'bulk_velocity' ) )&
     3029    THEN
     3030       WRITE( message_string, * )  'nonzero bulk velocity requires ',                              &
     3031              'conserve_volume_flow = .T. and ', 'conserve_volume_flow_mode = ''bulk_velocity'''
    32153032       CALL message( 'check_parameters', 'PA0157', 1, 2, 0, 6, 0 )
    32163033    ENDIF
    32173034
    32183035!
    3219 !-- Prevent empty time records in volume, cross-section and masked data in case
    3220 !-- of non-parallel netcdf-output in restart runs
     3036!-- Prevent empty time records in volume, cross-section and masked data in case of non-parallel
     3037!-- netcdf-output in restart runs
    32213038    IF ( netcdf_data_format < 5 )  THEN
    32223039       IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
     
    32323049!
    32333050!-- Check roughness length, which has to be smaller than dz/2
    3234     IF ( ( constant_flux_layer .OR.  &
    3235            INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )       &
    3236          .AND. roughness_length >= 0.5 * dz(1) )  THEN
     3051    IF ( ( constant_flux_layer .OR. INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  &
     3052         .AND.  roughness_length >= 0.5 * dz(1) )  THEN
    32373053       message_string = 'roughness_length must be smaller than dz/2'
    32383054       CALL message( 'check_parameters', 'PA0424', 1, 2, 0, 6, 0 )
     
    32483064!-- Check if topography is read from file in case of complex terrain simulations
    32493065    IF ( complex_terrain  .AND.  TRIM( topography ) /= 'read_from_file' )  THEN
    3250        message_string = 'complex_terrain requires topography' //               &
    3251                         ' = ''read_from_file'''
     3066       message_string = 'complex_terrain requires topography = ''read_from_file'''
    32523067       CALL message( 'check_parameters', 'PA0295', 1, 2, 0, 6, 0 )
    32533068    ENDIF
    32543069
    32553070!
    3256 !-- Check if vertical grid stretching is switched off in case of complex
    3257 !-- terrain simulations
    3258     IF ( complex_terrain  .AND.                                                &
    3259          ANY( dz_stretch_level_start /= -9999999.9_wp ) )  THEN
    3260        message_string = 'Vertical grid stretching is not allowed for ' //      &
    3261                         'complex_terrain = .T.'
     3071!-- Check if vertical grid stretching is switched off in case of complex terrain simulations
     3072    IF ( complex_terrain  .AND.  ANY( dz_stretch_level_start /= -9999999.9_wp ) )  THEN
     3073       message_string = 'Vertical grid stretching is not allowed for complex_terrain = .TRUE.'
    32623074       CALL message( 'check_parameters', 'PA0473', 1, 2, 0, 6, 0 )
    32633075    ENDIF
     
    32673079 CONTAINS
    32683080
    3269 !------------------------------------------------------------------------------!
     3081!--------------------------------------------------------------------------------------------------!
    32703082! Description:
    32713083! ------------
    3272 !> Check the length of data output intervals. In case of parallel NetCDF output
    3273 !> the time levels of the output files need to be fixed. Therefore setting the
    3274 !> output interval to 0.0s (usually used to output each timestep) is not
    3275 !> possible as long as a non-fixed timestep is used.
    3276 !------------------------------------------------------------------------------!
     3084!> Check the length of data output intervals. In case of parallel NetCDF output the time levels of
     3085!> the output files need to be fixed. Therefore setting the output interval to 0.0s (usually used to
     3086!> output each timestep) is not possible as long as a non-fixed timestep is used.
     3087!--------------------------------------------------------------------------------------------------!
    32773088
    32783089    SUBROUTINE check_dt_do( dt_do, dt_do_name )
     
    32863097       IF ( dt_do == 0.0_wp )  THEN
    32873098          IF ( dt_fixed )  THEN
    3288              WRITE( message_string, '(A,F9.4,A)' )  'Output at every '  //     &
    3289                     'timestep is wanted (' // dt_do_name // ' = 0.0).&'//      &
    3290                     'The output interval is set to the fixed timestep dt '//   &
    3291                     '= ', dt, 's.'
     3099             WRITE( message_string, '(A,F9.4,A)' )  'Output at every timestep is wanted (' //      &
     3100                    dt_do_name // ' = 0.0).&'//                                                    &
     3101                    'The output interval is set to the fixed timestep dt '// '= ', dt, 's.'
    32923102             CALL message( 'check_parameters', 'PA0060', 0, 0, 0, 6, 0 )
    32933103             dt_do = dt
    32943104          ELSE
    3295              message_string = dt_do_name // ' = 0.0 while using a ' //         &
    3296                               'variable timestep and parallel netCDF4 ' //     &
    3297                               'is not allowed.'
     3105             message_string = dt_do_name // ' = 0.0 while using a ' //                             &
     3106                              'variable timestep and parallel netCDF4 is not allowed.'
    32983107             CALL message( 'check_parameters', 'PA0081', 1, 2, 0, 6, 0 )
    32993108          ENDIF
     
    33043113
    33053114
    3306 !------------------------------------------------------------------------------!
     3115!--------------------------------------------------------------------------------------------------!
    33073116! Description:
    33083117! ------------
    33093118!> Set the bottom and top boundary conditions for humidity and scalars.
    3310 !------------------------------------------------------------------------------!
     3119!--------------------------------------------------------------------------------------------------!
    33113120
    33123121    SUBROUTINE set_bc_scalars( sq, bc_b, bc_t, ibc_b, ibc_t, err_nr_b, err_nr_t )
     
    33153124       IMPLICIT NONE
    33163125
    3317        CHARACTER (LEN=1)   ::  sq         !< name of scalar quantity
    33183126       CHARACTER (LEN=*)   ::  bc_b       !< bottom boundary condition
    33193127       CHARACTER (LEN=*)   ::  bc_t       !< top boundary condition
    33203128       CHARACTER (LEN=*)   ::  err_nr_b   !< error number if bottom bc is unknown
    33213129       CHARACTER (LEN=*)   ::  err_nr_t   !< error number if top bc is unknown
     3130       CHARACTER (LEN=1)   ::  sq         !< name of scalar quantity
     3131
    33223132
    33233133       INTEGER(iwp)        ::  ibc_b      !< index for bottom boundary condition
     
    33253135
    33263136!
    3327 !--    Set Integer flags and check for possilbe errorneous settings for bottom
    3328 !--    boundary condition
     3137!--    Set Integer flags and check for possilbe errorneous settings for bottom boundary condition
    33293138       IF ( bc_b == 'dirichlet' )  THEN
    33303139          ibc_b = 0
     
    33323141          ibc_b = 1
    33333142       ELSE
    3334           message_string = 'unknown boundary condition: bc_' // TRIM( sq ) // &
    3335                            '_b ="' // TRIM( bc_b ) // '"'
     3143          message_string = 'unknown boundary condition: bc_' // TRIM( sq ) // '_b ="' //          &
     3144                           TRIM( bc_b ) // '"'
    33363145          CALL message( 'check_parameters', err_nr_b, 1, 2, 0, 6, 0 )
    33373146       ENDIF
    33383147!
    3339 !--    Set Integer flags and check for possilbe errorneous settings for top
    3340 !--    boundary condition
     3148!--    Set Integer flags and check for possilbe errorneous settings for top boundary condition
    33413149       IF ( bc_t == 'dirichlet' )  THEN
    33423150          ibc_t = 0
     
    33483156          ibc_t = 3
    33493157       ELSE
    3350           message_string = 'unknown boundary condition: bc_' // TRIM( sq ) // &
    3351                            '_t ="' // TRIM( bc_t ) // '"'
     3158          message_string = 'unknown boundary condition: bc_' // TRIM( sq ) // '_t ="' //          &
     3159                           TRIM( bc_t ) // '"'
    33523160          CALL message( 'check_parameters', err_nr_t, 1, 2, 0, 6, 0 )
    33533161       ENDIF
     
    33583166
    33593167
    3360 !------------------------------------------------------------------------------!
     3168!--------------------------------------------------------------------------------------------------!
    33613169! Description:
    33623170! ------------
    3363 !> Check for consistent settings of bottom boundary conditions for humidity
    3364 !> and scalars.
    3365 !------------------------------------------------------------------------------!
    3366 
    3367     SUBROUTINE check_bc_scalars( sq, bc_b, ibc_b,                      &
    3368                                  err_nr_1, err_nr_2,                   &
    3369                                  constant_flux, surface_initial_change )
     3171!> Check for consistent settings of bottom boundary conditions for humidity and scalars.
     3172!--------------------------------------------------------------------------------------------------!
     3173
     3174    SUBROUTINE check_bc_scalars( sq, bc_b, ibc_b, err_nr_1, err_nr_2, constant_flux,               &
     3175                                 surface_initial_change )
    33703176
    33713177
    33723178       IMPLICIT NONE
    33733179
    3374        CHARACTER (LEN=1)   ::  sq                       !< name of scalar quantity
    33753180       CHARACTER (LEN=*)   ::  bc_b                     !< bottom boundary condition
    33763181       CHARACTER (LEN=*)   ::  err_nr_1                 !< error number of first error
    33773182       CHARACTER (LEN=*)   ::  err_nr_2                 !< error number of second error
     3183       CHARACTER (LEN=1)   ::  sq                       !< name of scalar quantity
     3184
    33783185
    33793186       INTEGER(iwp)        ::  ibc_b                    !< index of bottom boundary condition
     
    33843191
    33853192!
    3386 !--    A given surface value implies Dirichlet boundary condition for
    3387 !--    the respective quantity. In this case specification of a constant flux is
    3388 !--    forbidden. However, an exception is made for large-scale forcing as well
    3389 !--    as land-surface model.
     3193!--    A given surface value implies Dirichlet boundary condition for the respective quantity. In
     3194!--    this case specification of a constant flux is forbidden. However, an exception is made for
     3195!--    large-scale forcing as well as land-surface model.
    33903196       IF ( .NOT. land_surface  .AND.  .NOT. large_scale_forcing )  THEN
    33913197          IF ( ibc_b == 0  .AND.  constant_flux )  THEN
    3392              message_string = 'boundary condition: bc_' // TRIM( sq ) //       &
    3393                               '_b ' // '= "' // TRIM( bc_b ) //                &
    3394                               '" is not allowed with prescribed surface flux'
     3198             message_string = 'boundary condition: bc_' // TRIM( sq ) // '_b = "' //               &
     3199                              TRIM( bc_b ) // '" is not allowed with prescribed surface flux'
    33953200             CALL message( 'check_parameters', err_nr_1, 1, 2, 0, 6, 0 )
    33963201          ENDIF
    33973202       ENDIF
    33983203       IF ( constant_flux  .AND.  surface_initial_change /= 0.0_wp )  THEN
    3399           WRITE( message_string, * )  'a prescribed surface flux is not allo', &
    3400                  'wed with ', sq, '_surface_initial_change (/=0) = ',          &
    3401                  surface_initial_change
     3204          WRITE( message_string, * )  'a prescribed surface flux is not allo', 'wed with ', sq,    &
     3205                '_surface_initial_change (/=0) = ', surface_initial_change
    34023206          CALL message( 'check_parameters', err_nr_2, 1, 2, 0, 6, 0 )
    34033207       ENDIF
Note: See TracChangeset for help on using the changeset viewer.