Ignore:
Timestamp:
Mar 10, 2016 11:01:04 AM (8 years ago)
Author:
maronga
Message:

added support for water and paved surfaced in land surface model / minor changes

File:
1 edited

Legend:

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

    r1787 r1788  
    1919! Current revisions:
    2020! -----------------
    21 !
    22 !
     21! Added check for use of most_method = 'lookup' in combination with water
     22! surface presribed in the land surface model. Added output of z0q.
     23! Syntax layout improved.
     24!
    2325! Former revisions:
    2426! -----------------
     
    397399
    398400       IF ( dt_coupling == 9999999.9_wp )  THEN
    399           message_string = 'dt_coupling is not set but required for coup' // &
     401          message_string = 'dt_coupling is not set but required for coup' //   &
    400402                           'ling mode "' //  TRIM( coupling_mode ) // '"'
    401403          CALL message( 'check_parameters', 'PA0003', 1, 2, 0, 6, 0 )
     
    419421#if ! defined( __check )
    420422       IF ( myid == 0 ) THEN
    421           CALL MPI_SEND( dt_coupling, 1, MPI_REAL, target_id, 11, comm_inter, &
     423          CALL MPI_SEND( dt_coupling, 1, MPI_REAL, target_id, 11, comm_inter,  &
    422424                         ierr )
    423           CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 11, comm_inter, &
     425          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 11, comm_inter,       &
    424426                         status, ierr )
    425427       ENDIF
     
    436438          IF ( myid == 0  ) THEN
    437439             CALL MPI_SEND( dt_max, 1, MPI_REAL, target_id, 19, comm_inter, ierr )
    438              CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 19, comm_inter, &
     440             CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 19, comm_inter,    &
    439441                            status, ierr )
    440442          ENDIF   
     
    451453          CALL MPI_SEND( restart_time, 1, MPI_REAL, target_id, 12, comm_inter, &
    452454                         ierr )
    453           CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 12, comm_inter, &
     455          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 12, comm_inter,       &
    454456                         status, ierr )
    455457       ENDIF
     
    464466#if ! defined( __check )
    465467       IF ( myid == 0 ) THEN
    466           CALL MPI_SEND( dt_restart, 1, MPI_REAL, target_id, 13, comm_inter, &
     468          CALL MPI_SEND( dt_restart, 1, MPI_REAL, target_id, 13, comm_inter,   &
    467469                         ierr )
    468           CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 13, comm_inter, &
     470          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 13, comm_inter,       &
    469471                         status, ierr )
    470472       ENDIF   
     
    483485          CALL MPI_SEND( simulation_time_since_reference, 1, MPI_REAL, target_id, &
    484486                         14, comm_inter, ierr )
    485           CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 14, comm_inter, &
     487          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 14, comm_inter,       &
    486488                         status, ierr )   
    487489       ENDIF
     
    499501       IF ( myid == 0 ) THEN
    500502          CALL MPI_SEND( dx, 1, MPI_REAL, target_id, 15, comm_inter, ierr )
    501           CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 15, comm_inter, &
     503          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 15, comm_inter,       &
    502504                                                             status, ierr )
    503505       ENDIF
     
    508510
    509511          IF ( dx < remote ) THEN
    510              WRITE( message_string, * ) 'coupling mode "', &
    511                    TRIM( coupling_mode ),                  &
     512             WRITE( message_string, * ) 'coupling mode "',                     &
     513                   TRIM( coupling_mode ),                                      &
    512514           '": dx in Atmosphere is not equal to or not larger then dx in ocean'
    513515             CALL message( 'check_parameters', 'PA0009', 1, 2, 0, 6, 0 )
     
    515517
    516518          IF ( (nx_a+1)*dx /= (nx_o+1)*remote )  THEN
    517              WRITE( message_string, * ) 'coupling mode "', &
    518                     TRIM( coupling_mode ), &
     519             WRITE( message_string, * ) 'coupling mode "',                     &
     520                    TRIM( coupling_mode ),                                     &
    519521             '": Domain size in x-direction is not equal in ocean and atmosphere'
    520522             CALL message( 'check_parameters', 'PA0010', 1, 2, 0, 6, 0 )
     
    526528       IF ( myid == 0) THEN
    527529          CALL MPI_SEND( dy, 1, MPI_REAL, target_id, 16, comm_inter, ierr )
    528           CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 16, comm_inter, &
     530          CALL MPI_RECV( remote, 1, MPI_REAL, target_id, 16, comm_inter,       &
    529531                         status, ierr )
    530532       ENDIF
     
    534536
    535537          IF ( dy < remote )  THEN
    536              WRITE( message_string, * ) 'coupling mode "', &
    537                     TRIM( coupling_mode ), &
     538             WRITE( message_string, * ) 'coupling mode "',                     &
     539                    TRIM( coupling_mode ),                                     &
    538540                 '": dy in Atmosphere is not equal to or not larger then dy in ocean'
    539541             CALL message( 'check_parameters', 'PA0011', 1, 2, 0, 6, 0 )
     
    541543
    542544          IF ( (ny_a+1)*dy /= (ny_o+1)*remote )  THEN
    543              WRITE( message_string, * ) 'coupling mode "', &
    544                    TRIM( coupling_mode ), &
     545             WRITE( message_string, * ) 'coupling mode "',                     &
     546                   TRIM( coupling_mode ),                                      &
    545547             '": Domain size in y-direction is not equal in ocean and atmosphere'
    546548             CALL message( 'check_parameters', 'PA0012', 1, 2, 0, 6, 0 )
     
    548550
    549551          IF ( MOD(nx_o+1,nx_a+1) /= 0 )  THEN
    550              WRITE( message_string, * ) 'coupling mode "', &
    551                    TRIM( coupling_mode ), &
     552             WRITE( message_string, * ) 'coupling mode "',                     &
     553                   TRIM( coupling_mode ),                                      &
    552554             '": nx+1 in ocean is not divisible without remainder with nx+1 in', &
    553555             ' atmosphere'
     
    556558
    557559          IF ( MOD(ny_o+1,ny_a+1) /= 0 )  THEN
    558              WRITE( message_string, * ) 'coupling mode "', &
    559                    TRIM( coupling_mode ), &
     560             WRITE( message_string, * ) 'coupling mode "',                     &
     561                   TRIM( coupling_mode ),                                      &
    560562             '": ny+1 in ocean is not divisible without remainder with ny+1 in', &
    561563             ' atmosphere'
     
    565567       ENDIF
    566568#else
    567        WRITE( message_string, * ) 'coupling requires PALM to be called with', &
     569       WRITE( message_string, * ) 'coupling requires PALM to be called with',  &
    568570            ' ''mrun -K parallel'''
    569571       CALL message( 'check_parameters', 'PA0141', 1, 2, 0, 6, 0 )
     
    575577!-- Exchange via intercommunicator
    576578    IF ( coupling_mode == 'atmosphere_to_ocean' .AND. myid == 0 )  THEN
    577        CALL MPI_SEND( humidity, 1, MPI_LOGICAL, target_id, 19, comm_inter, &
     579       CALL MPI_SEND( humidity, 1, MPI_LOGICAL, target_id, 19, comm_inter,     &
    578580                      ierr )
    579581    ELSEIF ( coupling_mode == 'ocean_to_atmosphere' .AND. myid == 0)  THEN
    580        CALL MPI_RECV( humidity_remote, 1, MPI_LOGICAL, target_id, 19, &
     582       CALL MPI_RECV( humidity_remote, 1, MPI_LOGICAL, target_id, 19,          &
    581583                      comm_inter, status, ierr )
    582584    ENDIF
     
    633635
    634636       CASE DEFAULT
    635           message_string = 'illegal value given for loop_optimization: "' // &
     637          message_string = 'illegal value given for loop_optimization: "' //   &
    636638                           TRIM( loop_optimization ) // '"'
    637639          CALL message( 'check_parameters', 'PA0013', 1, 2, 0, 6, 0 )
     
    659661    IF ( topography /= 'flat' )  THEN
    660662       action = ' '
    661        IF ( scalar_advec /= 'pw-scheme' .AND. scalar_advec /= 'ws-scheme'     &
     663       IF ( scalar_advec /= 'pw-scheme' .AND. scalar_advec /= 'ws-scheme'      &
    662664      .AND. scalar_advec /= 'ws-scheme-mono' )  THEN
    663665          WRITE( action, '(A,A)' )  'scalar_advec = ', scalar_advec
    664666       ENDIF
    665        IF ( momentum_advec /= 'pw-scheme' .AND. momentum_advec /= 'ws-scheme' ) &
     667       IF ( momentum_advec /= 'pw-scheme' .AND. momentum_advec /= 'ws-scheme' )&
    666668       THEN
    667669          WRITE( action, '(A,A)' )  'momentum_advec = ', momentum_advec
     
    686688       ENDIF
    687689       IF ( action /= ' ' )  THEN
    688           message_string = 'a non-flat topography does not allow ' // &
     690          message_string = 'a non-flat topography does not allow ' //          &
    689691                           TRIM( action )
    690692          CALL message( 'check_parameters', 'PA0014', 1, 2, 0, 6, 0 )
     
    695697!--    is applicable. If this is not possible, abort.
    696698       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
    697           IF ( TRIM( topography ) /= 'single_building' .AND.  &
    698                TRIM( topography ) /= 'single_street_canyon' .AND.  &
     699          IF ( TRIM( topography ) /= 'single_building' .AND.                   &
     700               TRIM( topography ) /= 'single_street_canyon' .AND.              &
    699701               TRIM( topography ) /= 'read_from_file' )  THEN
    700702!--          The default value is not applicable here, because it is only valid
    701703!--          for the two standard cases 'single_building' and 'read_from_file'
    702704!--          defined in init_grid.
    703              WRITE( message_string, * )  &
    704                   'The value for "topography_grid_convention" ',  &
    705                   'is not set. Its default value is & only valid for ',  &
    706                   '"topography" = ''single_building'', ',  &
    707                   '''single_street_canyon'' & or ''read_from_file''.',  &
     705             WRITE( message_string, * )                                        &
     706                  'The value for "topography_grid_convention" ',               &
     707                  'is not set. Its default value is & only valid for ',        &
     708                  '"topography" = ''single_building'', ',                      &
     709                  '''single_street_canyon'' & or ''read_from_file''.',         &
    708710                  ' & Choose ''cell_edge'' or ''cell_center''.'
    709711             CALL message( 'user_check_parameters', 'PA0239', 1, 2, 0, 6, 0 )
     
    711713!--          The default value is applicable here.
    712714!--          Set convention according to topography.
    713              IF ( TRIM( topography ) == 'single_building' .OR.  &
     715             IF ( TRIM( topography ) == 'single_building' .OR.                 &
    714716                  TRIM( topography ) == 'single_street_canyon' )  THEN
    715717                topography_grid_convention = 'cell_edge'
     
    718720             ENDIF
    719721          ENDIF
    720        ELSEIF ( TRIM( topography_grid_convention ) /= 'cell_edge' .AND.  &
     722       ELSEIF ( TRIM( topography_grid_convention ) /= 'cell_edge' .AND.        &
    721723                TRIM( topography_grid_convention ) /= 'cell_center' )  THEN
    722           WRITE( message_string, * )  &
    723                'The value for "topography_grid_convention" is ', &
     724          WRITE( message_string, * )                                           &
     725               'The value for "topography_grid_convention" is ',               &
    724726               'not recognized. & Choose ''cell_edge'' or ''cell_center''.'
    725727          CALL message( 'user_check_parameters', 'PA0240', 1, 2, 0, 6, 0 )
     
    738740       ENDIF
    739741
    740     ELSEIF ( TRIM( coupling_mode ) == 'uncoupled'  .AND.  &
     742    ELSEIF ( TRIM( coupling_mode ) == 'uncoupled'  .AND.                       &
    741743             TRIM( coupling_char ) == '_O' )  THEN
    742744
     
    744746!--    Check whether an (uncoupled) atmospheric run has been declared as an
    745747!--    ocean run (this setting is done via mrun-option -y)
    746 
    747        message_string = 'ocean = .F. does not allow coupling_char = "' // &
     748       message_string = 'ocean = .F. does not allow coupling_char = "' //      &
    748749                        TRIM( coupling_char ) // '" set by mrun-option "-y"'
    749750       CALL message( 'check_parameters', 'PA0317', 1, 2, 0, 6, 0 )
     
    777778          gamma_mg = 1
    778779       ELSE
    779           message_string = 'unknown multigrid cycle: cycle_mg = "' // &
     780          message_string = 'unknown multigrid cycle: cycle_mg = "' //          &
    780781                           TRIM( cycle_mg ) // '"'
    781782          CALL message( 'check_parameters', 'PA0020', 1, 2, 0, 6, 0 )
     
    783784    ENDIF
    784785
    785     IF ( fft_method /= 'singleton-algorithm'  .AND.  &
    786          fft_method /= 'temperton-algorithm'  .AND.  &
    787          fft_method /= 'fftw'                 .AND.  &
     786    IF ( fft_method /= 'singleton-algorithm'  .AND.                            &
     787         fft_method /= 'temperton-algorithm'  .AND.                            &
     788         fft_method /= 'fftw'                 .AND.                            &
    788789         fft_method /= 'system-specific' )  THEN
    789        message_string = 'unknown fft-algorithm: fft_method = "' // &
     790       message_string = 'unknown fft-algorithm: fft_method = "' //             &
    790791                        TRIM( fft_method ) // '"'
    791792       CALL message( 'check_parameters', 'PA0021', 1, 2, 0, 6, 0 )
    792793    ENDIF
    793794   
    794     IF( momentum_advec == 'ws-scheme' .AND. &
     795    IF( momentum_advec == 'ws-scheme' .AND.                                    &
    795796        .NOT. call_psolver_at_all_substeps  ) THEN
    796         message_string = 'psolver must be called at each RK3 substep when "'//&
     797        message_string = 'psolver must be called at each RK3 substep when "'// &
    797798                      TRIM(momentum_advec) // ' "is used for momentum_advec'
    798799        CALL message( 'check_parameters', 'PA0344', 1, 2, 0, 6, 0 )
     
    802803    IF ( momentum_advec /= 'pw-scheme'  .AND.  momentum_advec /= 'ws-scheme' ) &
    803804    THEN
    804        message_string = 'unknown advection scheme: momentum_advec = "' // &
     805       message_string = 'unknown advection scheme: momentum_advec = "' //      &
    805806                        TRIM( momentum_advec ) // '"'
    806807       CALL message( 'check_parameters', 'PA0022', 1, 2, 0, 6, 0 )
     
    811812                   timestep_scheme == 'runge-kutta-2' ) )                      &
    812813    THEN
    813        message_string = 'momentum_advec or scalar_advec = "' &
     814       message_string = 'momentum_advec or scalar_advec = "'                   &
    814815         // TRIM( momentum_advec ) // '" is not allowed with timestep_scheme = "' // &
    815816         TRIM( timestep_scheme ) // '"'
     
    819820         scalar_advec /= 'ws-scheme-mono' .AND. scalar_advec /= 'bc-scheme' )  &
    820821    THEN
    821        message_string = 'unknown advection scheme: scalar_advec = "' // &
     822       message_string = 'unknown advection scheme: scalar_advec = "' //        &
    822823                        TRIM( scalar_advec ) // '"'
    823824       CALL message( 'check_parameters', 'PA0024', 1, 2, 0, 6, 0 )
     
    825826    IF ( scalar_advec == 'bc-scheme'  .AND.  loop_optimization == 'cache' )    &
    826827    THEN
    827        message_string = 'advection_scheme scalar_advec = "' &
     828       message_string = 'advection_scheme scalar_advec = "'                    &
    828829         // TRIM( scalar_advec ) // '" not implemented for & loop_optimization = "' // &
    829830         TRIM( loop_optimization ) // '"'
     
    851852!-- Set LOGICAL switches to enhance performance
    852853    IF ( momentum_advec == 'ws-scheme' )       ws_scheme_mom = .TRUE.
    853     IF ( scalar_advec   == 'ws-scheme' .OR.                                   &
     854    IF ( scalar_advec   == 'ws-scheme' .OR.                                    &
    854855         scalar_advec   == 'ws-scheme-mono' )  ws_scheme_sca = .TRUE.
    855856    IF ( scalar_advec   == 'ws-scheme-mono' )  monotonic_adjustment = .TRUE.
     
    908909    IF ( collision_kernel(6:9) == 'fast' )  use_kernel_tables = .TRUE.
    909910
    910     IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.  &
     911    IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.            &
    911912         TRIM( initializing_actions ) /= 'cyclic_fill' )  THEN
    912913!
    913914!--    No restart run: several initialising actions are possible
    914915       action = initializing_actions
    915        DO WHILE ( TRIM( action ) /= '' )
     916       DO  WHILE ( TRIM( action ) /= '' )
    916917          position = INDEX( action, ' ' )
    917918          SELECT CASE ( action(1:position-1) )
    918919
    919              CASE ( 'set_constant_profiles', 'set_1d-model_profiles', &
     920             CASE ( 'set_constant_profiles', 'set_1d-model_profiles',          &
    920921                    'by_user', 'initialize_vortex',     'initialize_ptanom' )
    921922                action = action(position+1:)
    922923
    923924             CASE DEFAULT
    924                 message_string = 'initializing_action = "' // &
     925                message_string = 'initializing_action = "' //                  &
    925926                                 TRIM( action ) // '" unkown or not allowed'
    926927                CALL message( 'check_parameters', 'PA0030', 1, 2, 0, 6, 0 )
     
    930931    ENDIF
    931932
    932     IF ( TRIM( initializing_actions ) == 'initialize_vortex' .AND. &
     933    IF ( TRIM( initializing_actions ) == 'initialize_vortex'  .AND.            &
    933934         conserve_volume_flow ) THEN
    934          message_string = 'initializing_actions = "initialize_vortex"' // &
     935         message_string = 'initializing_actions = "initialize_vortex"' //      &
    935936                        ' ist not allowed with conserve_volume_flow = .T.'
    936937       CALL message( 'check_parameters', 'PA0343', 1, 2, 0, 6, 0 )
     
    938939
    939940
    940     IF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0  .AND. &
     941    IF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0  .AND.    &
    941942         INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
    942        message_string = 'initializing_actions = "set_constant_profiles"' // &
    943                         ' and "set_1d-model_profiles" are not allowed ' //  &
     943       message_string = 'initializing_actions = "set_constant_profiles"' //    &
     944                        ' and "set_1d-model_profiles" are not allowed ' //     &
    944945                        'simultaneously'
    945946       CALL message( 'check_parameters', 'PA0031', 1, 2, 0, 6, 0 )
    946947    ENDIF
    947948
    948     IF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0  .AND. &
     949    IF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0  .AND.    &
    949950         INDEX( initializing_actions, 'by_user' ) /= 0 )  THEN
    950        message_string = 'initializing_actions = "set_constant_profiles"' // &
     951       message_string = 'initializing_actions = "set_constant_profiles"' //    &
    951952                        ' and "by_user" are not allowed simultaneously'
    952953       CALL message( 'check_parameters', 'PA0032', 1, 2, 0, 6, 0 )
    953954    ENDIF
    954955
    955     IF ( INDEX( initializing_actions, 'by_user' ) /= 0  .AND. &
     956    IF ( INDEX( initializing_actions, 'by_user' ) /= 0  .AND.                  &
    956957         INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
    957        message_string = 'initializing_actions = "by_user" and ' // &
     958       message_string = 'initializing_actions = "by_user" and ' //             &
    958959                        '"set_1d-model_profiles" are not allowed simultaneously'
    959960       CALL message( 'check_parameters', 'PA0033', 1, 2, 0, 6, 0 )
    960961    ENDIF
    961962
    962     IF ( cloud_physics  .AND.  .NOT. humidity )  THEN
    963        WRITE( message_string, * ) 'cloud_physics = ', cloud_physics, ' is ', &
     963    IF ( cloud_physics  .AND.  .NOT.  humidity )  THEN
     964       WRITE( message_string, * ) 'cloud_physics = ', cloud_physics, ' is ',   &
    964965              'not allowed with humidity = ', humidity
    965966       CALL message( 'check_parameters', 'PA0034', 1, 2, 0, 6, 0 )
     
    967968
    968969    IF ( precipitation  .AND.  .NOT.  cloud_physics )  THEN
    969        WRITE( message_string, * ) 'precipitation = ', precipitation, ' is ', &
     970       WRITE( message_string, * ) 'precipitation = ', precipitation, ' is ',   &
    970971              'not allowed with cloud_physics = ', cloud_physics
    971972       CALL message( 'check_parameters', 'PA0035', 1, 2, 0, 6, 0 )
     
    973974
    974975    IF ( humidity  .AND.  sloping_surface )  THEN
    975        message_string = 'humidity = .TRUE. and sloping_surface = .TRUE. ' // &
     976       message_string = 'humidity = .TRUE. and sloping_surface = .TRUE. ' //   &
    976977                        'are not allowed simultaneously'
    977978       CALL message( 'check_parameters', 'PA0036', 1, 2, 0, 6, 0 )
     
    979980
    980981    IF ( passive_scalar  .AND.  humidity )  THEN
    981        message_string = 'humidity = .TRUE. and passive_scalar = .TRUE. ' // &
     982       message_string = 'humidity = .TRUE. and passive_scalar = .TRUE. ' //    &
    982983                        'is not allowed simultaneously'
    983984       CALL message( 'check_parameters', 'PA0038', 1, 2, 0, 6, 0 )
     
    10321033!--    calculated from the temperature/humidity gradients in the land surface
    10331034!--    model
    1034        IF ( bc_pt_b == 'neumann' .OR. bc_q_b == 'neumann' )  THEN
     1035       IF ( bc_pt_b == 'neumann'  .OR. bc_q_b == 'neumann' )  THEN
    10351036          message_string = 'lsm requires setting of'//                         &
    10361037                           'bc_pt_b = "dirichlet" and '//                      &
     
    10391040       ENDIF
    10401041
    1041        IF ( .NOT. constant_flux_layer )  THEN
     1042       IF (  .NOT. constant_flux_layer )  THEN
    10421043          message_string = 'lsm requires '//                                   &
    10431044                           'constant_flux_layer = .T.'
     
    10461047
    10471048       IF ( topography /= 'flat' )  THEN
    1048           message_string = 'lsm cannot be used ' //  &
     1049          message_string = 'lsm cannot be used ' //                            &
    10491050                           'in combination with  topography /= "flat"'
    10501051          CALL message( 'check_parameters', 'PA0415', 1, 2, 0, 6, 0 )
    10511052       ENDIF
    10521053
     1054       IF ( ( veg_type == 14  .OR.  veg_type == 15 ) .AND.                       &
     1055              most_method == 'lookup' )  THEN
     1056           WRITE( message_string, * ) 'veg_type = ', veg_type, ' is not ',     &
     1057                                      'allowed in combination with ',          &
     1058                                      'most_method = ', most_method
     1059          CALL message( 'check_parameters', 'PA0417', 1, 2, 0, 6, 0 )
     1060       ENDIF
     1061
    10531062       IF ( veg_type == 0 )  THEN
    1054           IF ( SUM(root_fraction) /= 1.0_wp)  THEN
     1063          IF ( SUM( root_fraction ) /= 1.0_wp )  THEN
    10551064             message_string = 'veg_type = 0 (user_defined)'//                  &
    10561065                              'requires setting of root_fraction(0:3)'//       &
     
    10591068          ENDIF
    10601069 
    1061           IF ( min_canopy_resistance == 9999999.9_wp)  THEN
     1070          IF ( min_canopy_resistance == 9999999.9_wp )  THEN
    10621071             message_string = 'veg_type = 0 (user defined)'//                  &
    10631072                              'requires setting of min_canopy_resistance'//    &
     
    10661075          ENDIF
    10671076
    1068           IF ( leaf_area_index == 9999999.9_wp)  THEN
     1077          IF ( leaf_area_index == 9999999.9_wp )  THEN
    10691078             message_string = 'veg_type = 0 (user_defined)'//                  &
    10701079                              'requires setting of leaf_area_index'//          &
     
    10731082          ENDIF
    10741083
    1075           IF ( vegetation_coverage == 9999999.9_wp)  THEN
     1084          IF ( vegetation_coverage == 9999999.9_wp )  THEN
    10761085             message_string = 'veg_type = 0 (user_defined)'//                  &
    10771086                              'requires setting of vegetation_coverage'//      &
     
    10871096          ENDIF
    10881097
    1089           IF ( lambda_surface_stable == 9999999.9_wp)  THEN
     1098          IF ( lambda_surface_stable == 9999999.9_wp )  THEN
    10901099             message_string = 'veg_type = 0 (user_defined)'//                  &
    10911100                              'requires setting of lambda_surface_stable'//    &
     
    10941103          ENDIF
    10951104
    1096           IF ( lambda_surface_unstable == 9999999.9_wp)  THEN
     1105          IF ( lambda_surface_unstable == 9999999.9_wp )  THEN
    10971106             message_string = 'veg_type = 0 (user_defined)'//                  &
    10981107                              'requires setting of lambda_surface_unstable'//  &
     
    11011110          ENDIF
    11021111
    1103           IF ( f_shortwave_incoming == 9999999.9_wp)  THEN
     1112          IF ( f_shortwave_incoming == 9999999.9_wp )  THEN
    11041113             message_string = 'veg_type = 0 (user_defined)'//                  &
    11051114                              'requires setting of f_shortwave_incoming'//     &
     
    11081117          ENDIF
    11091118
    1110           IF ( z0_eb == 9999999.9_wp)  THEN
     1119          IF ( z0_eb == 9999999.9_wp )  THEN
    11111120             message_string = 'veg_type = 0 (user_defined)'//                  &
    11121121                              'requires setting of z0_eb'//                   &
     
    11151124          ENDIF
    11161125
    1117           IF ( z0h_eb == 9999999.9_wp)  THEN
     1126          IF ( z0h_eb == 9999999.9_wp )  THEN
    11181127             message_string = 'veg_type = 0 (user_defined)'//                  &
    11191128                              'requires setting of z0h_eb'//                  &
     
    11271136       IF ( soil_type == 0 )  THEN
    11281137
    1129           IF ( alpha_vangenuchten == 9999999.9_wp)  THEN
     1138          IF ( alpha_vangenuchten == 9999999.9_wp )  THEN
    11301139             message_string = 'soil_type = 0 (user_defined)'//                 &
    11311140                              'requires setting of alpha_vangenuchten'//       &
     
    11341143          ENDIF
    11351144
    1136           IF ( l_vangenuchten == 9999999.9_wp)  THEN
     1145          IF ( l_vangenuchten == 9999999.9_wp )  THEN
    11371146             message_string = 'soil_type = 0 (user_defined)'//                 &
    11381147                              'requires setting of l_vangenuchten'//           &
     
    11411150          ENDIF
    11421151
    1143           IF ( n_vangenuchten == 9999999.9_wp)  THEN
     1152          IF ( n_vangenuchten == 9999999.9_wp )  THEN
    11441153             message_string = 'soil_type = 0 (user_defined)'//                 &
    11451154                              'requires setting of n_vangenuchten'//           &
     
    11481157          ENDIF
    11491158
    1150           IF ( hydraulic_conductivity == 9999999.9_wp)  THEN
     1159          IF ( hydraulic_conductivity == 9999999.9_wp )  THEN
    11511160             message_string = 'soil_type = 0 (user_defined)'//                 &
    11521161                              'requires setting of hydraulic_conductivity'//   &
     
    11551164          ENDIF
    11561165
    1157           IF ( saturation_moisture == 9999999.9_wp)  THEN
     1166          IF ( saturation_moisture == 9999999.9_wp )  THEN
    11581167             message_string = 'soil_type = 0 (user_defined)'//                 &
    11591168                              'requires setting of saturation_moisture'//      &
     
    11621171          ENDIF
    11631172
    1164           IF ( field_capacity == 9999999.9_wp)  THEN
     1173          IF ( field_capacity == 9999999.9_wp )  THEN
    11651174             message_string = 'soil_type = 0 (user_defined)'//                 &
    11661175                              'requires setting of field_capacity'//           &
     
    11691178          ENDIF
    11701179
    1171           IF ( wilting_point == 9999999.9_wp)  THEN
     1180          IF ( wilting_point == 9999999.9_wp )  THEN
    11721181             message_string = 'soil_type = 0 (user_defined)'//                 &
    11731182                              'requires setting of wilting_point'//            &
     
    11761185          ENDIF
    11771186
    1178           IF ( residual_moisture == 9999999.9_wp)  THEN
     1187          IF ( residual_moisture == 9999999.9_wp )  THEN
    11791188             message_string = 'soil_type = 0 (user_defined)'//                 &
    11801189                              'requires setting of residual_moisture'//        &
     
    11851194       ENDIF
    11861195
    1187        IF ( .NOT. radiation )  THEN
     1196       IF (  .NOT. radiation )  THEN
    11881197          message_string = 'lsm requires '//                                   &
    11891198                           'radiation = .T.'
     
    11941203
    11951204    IF ( radiation )  THEN
    1196        IF ( radiation_scheme /= 'constant'  .AND.                              &
    1197             radiation_scheme /= 'clear-sky' .AND.                              &
     1205       IF ( radiation_scheme /= 'constant'   .AND.                             &
     1206            radiation_scheme /= 'clear-sky'  .AND.                             &
    11981207            radiation_scheme /= 'rrtmg' )  THEN
    11991208          message_string = 'unknown radiation_scheme = '//                     &
     
    12151224
    12161225       ENDIF
    1217        IF ( albedo_type == 0 .AND. albedo == 9999999.9_wp .AND.                &
     1226       IF ( albedo_type == 0  .AND.  albedo == 9999999.9_wp  .AND.             &
    12181227            radiation_scheme == 'clear-sky')  THEN
    12191228          message_string = 'radiation_scheme = "clear-sky" in combination' //  &
     
    12221231          CALL message( 'check_parameters', 'PA0410', 1, 2, 0, 6, 0 )
    12231232       ENDIF
    1224        IF ( albedo_type == 0 .AND. radiation_scheme == 'rrtmg' .AND.           &
     1233       IF ( albedo_type == 0  .AND.  radiation_scheme == 'rrtmg'  .AND.        &
    12251234          (    albedo_lw_dif == 9999999.9_wp .OR. albedo_lw_dir == 9999999.9_wp&
    12261235          .OR. albedo_sw_dif == 9999999.9_wp .OR. albedo_sw_dir == 9999999.9_wp&
     
    12351244       ENDIF
    12361245       IF ( topography /= 'flat' )  THEN
    1237           message_string = 'radiation scheme cannot be used ' //  &
     1246          message_string = 'radiation scheme cannot be used ' //               &
    12381247                           'in combination with  topography /= "flat"'
    12391248          CALL message( 'check_parameters', 'PA0414', 1, 2, 0, 6, 0 )
     
    12441253                 loop_optimization == 'vector' )                               &
    12451254         .AND.  cloud_physics  .AND.  icloud_scheme == 0 )  THEN
    1246        message_string = 'cloud_scheme = seifert_beheng requires ' // &
     1255       message_string = 'cloud_scheme = seifert_beheng requires ' //           &
    12471256                        'loop_optimization = "cache" or "vector"'
    12481257       CALL message( 'check_parameters', 'PA0362', 1, 2, 0, 6, 0 )
     
    12701279       gradient = 0.0_wp
    12711280
    1272        IF ( .NOT. ocean )  THEN
     1281       IF (  .NOT. ocean )  THEN
    12731282
    12741283          ug_vertical_gradient_level_ind(1) = 0
    12751284          ug(0) = ug_surface
    12761285          DO  k = 1, nzt+1
    1277              IF ( i < 11 ) THEN
    1278                 IF ( ug_vertical_gradient_level(i) < zu(k)  .AND. &
     1286             IF ( i < 11 )  THEN
     1287                IF ( ug_vertical_gradient_level(i) < zu(k)  .AND.              &
    12791288                     ug_vertical_gradient_level(i) >= 0.0_wp )  THEN
    12801289                   gradient = ug_vertical_gradient(i) / 100.0_wp
     
    12991308          ug(nzt+1) = ug_surface
    13001309          DO  k = nzt, nzb, -1
    1301              IF ( i < 11 ) THEN
    1302                 IF ( ug_vertical_gradient_level(i) > zu(k)  .AND. &
     1310             IF ( i < 11 )  THEN
     1311                IF ( ug_vertical_gradient_level(i) > zu(k)  .AND.              &
    13031312                     ug_vertical_gradient_level(i) <= 0.0_wp )  THEN
    13041313                   gradient = ug_vertical_gradient(i) / 100.0_wp
     
    13341343       gradient = 0.0_wp
    13351344
    1336        IF ( .NOT. ocean )  THEN
     1345       IF (  .NOT. ocean )  THEN
    13371346
    13381347          vg_vertical_gradient_level_ind(1) = 0
    13391348          vg(0) = vg_surface
    13401349          DO  k = 1, nzt+1
    1341              IF ( i < 11 ) THEN
    1342                 IF ( vg_vertical_gradient_level(i) < zu(k)  .AND. &
     1350             IF ( i < 11 )  THEN
     1351                IF ( vg_vertical_gradient_level(i) < zu(k)  .AND.              &
    13431352                     vg_vertical_gradient_level(i) >= 0.0_wp )  THEN
    13441353                   gradient = vg_vertical_gradient(i) / 100.0_wp
     
    13631372          vg(nzt+1) = vg_surface
    13641373          DO  k = nzt, nzb, -1
    1365              IF ( i < 11 ) THEN
    1366                 IF ( vg_vertical_gradient_level(i) > zu(k)  .AND. &
     1374             IF ( i < 11 )  THEN
     1375                IF ( vg_vertical_gradient_level(i) > zu(k)  .AND.              &
    13671376                     vg_vertical_gradient_level(i) <= 0.0_wp )  THEN
    13681377                   gradient = vg_vertical_gradient(i) / 100.0_wp
     
    14151424
    14161425             IF ( kk < 100 )  THEN
    1417                 DO WHILE ( uv_heights(kk+1) <= zu(k) )
     1426                DO  WHILE ( uv_heights(kk+1) <= zu(k) )
    14181427                   kk = kk + 1
    14191428                   IF ( kk == 100 )  EXIT
     
    14211430             ENDIF
    14221431
    1423              IF ( kk < 100 .AND. uv_heights(kk+1) /= 9999999.9_wp )  THEN
     1432             IF ( kk < 100  .AND. uv_heights(kk+1) /= 9999999.9_wp )  THEN
    14241433                u_init(k) = u_profile(kk) + ( zu(k) - uv_heights(kk) ) /       &
    14251434                                       ( uv_heights(kk+1) - uv_heights(kk) ) * &
     
    14441453!
    14451454!--    Compute initial temperature profile using the given temperature gradients
    1446        IF ( .NOT. neutral )  THEN
     1455       IF (  .NOT. neutral )  THEN
    14471456
    14481457          i = 1
    14491458          gradient = 0.0_wp
    14501459
    1451           IF ( .NOT. ocean )  THEN
     1460          IF (  .NOT. ocean )  THEN
    14521461
    14531462             pt_vertical_gradient_level_ind(1) = 0
    14541463             DO  k = 1, nzt+1
    1455                 IF ( i < 11 ) THEN
    1456                    IF ( pt_vertical_gradient_level(i) < zu(k)  .AND. &
     1464                IF ( i < 11 )  THEN
     1465                   IF ( pt_vertical_gradient_level(i) < zu(k)  .AND.           &
    14571466                        pt_vertical_gradient_level(i) >= 0.0_wp )  THEN
    14581467                      gradient = pt_vertical_gradient(i) / 100.0_wp
     
    14761485             pt_vertical_gradient_level_ind(1) = nzt+1
    14771486             DO  k = nzt, 0, -1
    1478                 IF ( i < 11 ) THEN
    1479                    IF ( pt_vertical_gradient_level(i) > zu(k)  .AND. &
     1487                IF ( i < 11 )  THEN
     1488                   IF ( pt_vertical_gradient_level(i) > zu(k)  .AND.           &
    14801489                        pt_vertical_gradient_level(i) <= 0.0_wp )  THEN
    14811490                      gradient = pt_vertical_gradient(i) / 100.0_wp
     
    15331542          q_vertical_gradient_level_ind(1) = 0
    15341543          DO  k = 1, nzt+1
    1535              IF ( i < 11 ) THEN
    1536                 IF ( q_vertical_gradient_level(i) < zu(k)  .AND. &
     1544             IF ( i < 11 )  THEN
     1545                IF ( q_vertical_gradient_level(i) < zu(k)  .AND.               &
    15371546                     q_vertical_gradient_level(i) >= 0.0_wp )  THEN
    15381547                   gradient = q_vertical_gradient(i) / 100.0_wp
     
    15791588          sa_vertical_gradient_level_ind(1) = nzt+1
    15801589          DO  k = nzt, 0, -1
    1581              IF ( i < 11 ) THEN
    1582                 IF ( sa_vertical_gradient_level(i) > zu(k)  .AND. &
     1590             IF ( i < 11 )  THEN
     1591                IF ( sa_vertical_gradient_level(i) > zu(k)  .AND.              &
    15831592                     sa_vertical_gradient_level(i) <= 0.0_wp )  THEN
    15841593                   gradient = sa_vertical_gradient(i) / 100.0_wp
     
    16061615!
    16071616!-- Check if the control parameter use_subsidence_tendencies is used correctly
    1608     IF ( use_subsidence_tendencies  .AND.  .NOT. large_scale_subsidence )  THEN
    1609        message_string = 'The usage of use_subsidence_tendencies ' // &
     1617    IF ( use_subsidence_tendencies  .AND.  .NOT.  large_scale_subsidence )  THEN
     1618       message_string = 'The usage of use_subsidence_tendencies ' //           &
    16101619                            'requires large_scale_subsidence = .T..'
    16111620       CALL message( 'check_parameters', 'PA0396', 1, 2, 0, 6, 0 )
    16121621    ELSEIF ( use_subsidence_tendencies  .AND.  .NOT. large_scale_forcing )  THEN
    1613        message_string = 'The usage of use_subsidence_tendencies ' // &
     1622       message_string = 'The usage of use_subsidence_tendencies ' //           &
    16141623                            'requires large_scale_forcing = .T..'
    16151624       CALL message( 'check_parameters', 'PA0397', 1, 2, 0, 6, 0 )
     
    16191628!-- Initialize large scale subsidence if required
    16201629    If ( large_scale_subsidence )  THEN
    1621        IF ( subs_vertical_gradient_level(1) /= -9999999.9_wp .AND. &
    1622                                      .NOT. large_scale_forcing )  THEN
     1630       IF ( subs_vertical_gradient_level(1) /= -9999999.9_wp  .AND.            &
     1631                                     .NOT.  large_scale_forcing )  THEN
    16231632          CALL init_w_subsidence
    16241633       ENDIF
     
    16271636!--    are read in from file LSF_DATA
    16281637
    1629        IF ( subs_vertical_gradient_level(1) == -9999999.9_wp .AND. &
    1630                                      .NOT. large_scale_forcing )  THEN
    1631           message_string = 'There is no default large scale vertical ' // &
    1632                            'velocity profile set. Specify the subsidence ' // &
    1633                            'velocity profile via subs_vertical_gradient and ' // &
    1634                            'subs_vertical_gradient_level.'
     1638       IF ( subs_vertical_gradient_level(1) == -9999999.9_wp  .AND.            &
     1639            .NOT. large_scale_forcing )  THEN
     1640          message_string = 'There is no default large scale vertical ' //      &
     1641                           'velocity profile set. Specify the subsidence ' //  &
     1642                           'velocity profile via subs_vertical_gradient ' //  &
     1643                           'and subs_vertical_gradient_level.'
    16351644          CALL message( 'check_parameters', 'PA0380', 1, 2, 0, 6, 0 )
    16361645       ENDIF
    16371646    ELSE
    16381647        IF ( subs_vertical_gradient_level(1) /= -9999999.9_wp )  THEN
    1639            message_string = 'Enable usage of large scale subsidence by ' // &
     1648           message_string = 'Enable usage of large scale subsidence by ' //    &
    16401649                            'setting large_scale_subsidence = .T..'
    16411650          CALL message( 'check_parameters', 'PA0381', 1, 2, 0, 6, 0 )
     
    16591668       vpt_reference = pt_reference * ( 1.0_wp + 0.61_wp * q_surface )
    16601669    ELSE
    1661        message_string = 'illegal value for reference_state: "' // &
     1670       message_string = 'illegal value for reference_state: "' //              &
    16621671                        TRIM( reference_state ) // '"'
    16631672       CALL message( 'check_parameters', 'PA0056', 1, 2, 0, 6, 0 )
     
    16861695    IF ( alpha_surface /= 0.0_wp )  THEN
    16871696       IF ( ABS( alpha_surface ) > 90.0_wp )  THEN
    1688           WRITE( message_string, * ) 'ABS( alpha_surface = ', alpha_surface, &
     1697          WRITE( message_string, * ) 'ABS( alpha_surface = ', alpha_surface,   &
    16891698                                     ' ) must be < 90.0'
    16901699          CALL message( 'check_parameters', 'PA0043', 1, 2, 0, 6, 0 )
     
    17161725          ENDIF
    17171726       ELSE
    1718           WRITE( message_string, * ) 'cfl_factor = ', cfl_factor, &
     1727          WRITE( message_string, * ) 'cfl_factor = ', cfl_factor,              &
    17191728                 ' out of range & 0.0 < cfl_factor <= 1.0 is required'
    17201729          CALL message( 'check_parameters', 'PA0045', 1, 2, 0, 6, 0 )
     
    17401749!-- Set wind speed in the Galilei-transformed system
    17411750    IF ( galilei_transformation )  THEN
    1742        IF ( use_ug_for_galilei_tr .AND.                     &
    1743             ug_vertical_gradient_level(1) == 0.0_wp  .AND.  &
    1744             ug_vertical_gradient(1) == 0.0_wp  .AND.        &
    1745             vg_vertical_gradient_level(1) == 0.0_wp  .AND.  &
     1751       IF ( use_ug_for_galilei_tr                    .AND.                     &
     1752            ug_vertical_gradient_level(1) == 0.0_wp  .AND.                     &
     1753            ug_vertical_gradient(1) == 0.0_wp        .AND.                     &
     1754            vg_vertical_gradient_level(1) == 0.0_wp  .AND.                     &
    17461755            vg_vertical_gradient(1) == 0.0_wp )  THEN
    17471756          u_gtrans = ug_surface * 0.6_wp
    17481757          v_gtrans = vg_surface * 0.6_wp
    1749        ELSEIF ( use_ug_for_galilei_tr  .AND.                     &
    1750                 ( ug_vertical_gradient_level(1) /= 0.0_wp  .OR.  &
     1758       ELSEIF ( use_ug_for_galilei_tr  .AND.                                   &
     1759                ( ug_vertical_gradient_level(1) /= 0.0_wp  .OR.                &
    17511760                ug_vertical_gradient(1) /= 0.0_wp ) )  THEN
    1752           message_string = 'baroclinity (ug) not allowed simultaneously' // &
     1761          message_string = 'baroclinity (ug) not allowed simultaneously' //    &
    17531762                           ' with galilei transformation'
    17541763          CALL message( 'check_parameters', 'PA0046', 1, 2, 0, 6, 0 )
    1755        ELSEIF ( use_ug_for_galilei_tr  .AND.                     &
    1756                 ( vg_vertical_gradient_level(1) /= 0.0_wp  .OR.  &
     1764       ELSEIF ( use_ug_for_galilei_tr  .AND.                                   &
     1765                ( vg_vertical_gradient_level(1) /= 0.0_wp  .OR.                &
    17571766                vg_vertical_gradient(1) /= 0.0_wp ) )  THEN
    1758           message_string = 'baroclinity (vg) not allowed simultaneously' // &
     1767          message_string = 'baroclinity (vg) not allowed simultaneously' //    &
    17591768                           ' with galilei transformation'
    17601769          CALL message( 'check_parameters', 'PA0047', 1, 2, 0, 6, 0 )
    17611770       ELSE
    1762           message_string = 'variable translation speed used for galilei-' // &
    1763              'transformation, which may cause & instabilities in stably ' // &
     1771          message_string = 'variable translation speed used for galilei-' //   &
     1772             'transformation, which may cause & instabilities in stably ' //   &
    17641773             'stratified regions'
    17651774          CALL message( 'check_parameters', 'PA0048', 0, 1, 0, 6, 0 )
     
    17821791    IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
    17831792       IF ( psolver(1:9) /= 'multigrid' )  THEN
    1784           message_string = 'non-cyclic lateral boundaries do not allow ' // &
     1793          message_string = 'non-cyclic lateral boundaries do not allow ' //    &
    17851794                           'psolver = "' // TRIM( psolver ) // '"'
    17861795          CALL message( 'check_parameters', 'PA0051', 1, 2, 0, 6, 0 )
    17871796       ENDIF
    1788        IF ( momentum_advec /= 'pw-scheme' .AND.                               &
    1789           ( momentum_advec /= 'ws-scheme' .AND.                               &
    1790             momentum_advec /= 'ws-scheme-mono' )                              &
     1797       IF ( momentum_advec /= 'pw-scheme'  .AND.                               &
     1798          ( momentum_advec /= 'ws-scheme'  .AND.                               &
     1799            momentum_advec /= 'ws-scheme-mono' )                               &
    17911800          )  THEN
    17921801
    1793           message_string = 'non-cyclic lateral boundaries do not allow ' // &
     1802          message_string = 'non-cyclic lateral boundaries do not allow ' //    &
    17941803                           'momentum_advec = "' // TRIM( momentum_advec ) // '"'
    17951804          CALL message( 'check_parameters', 'PA0052', 1, 2, 0, 6, 0 )
    17961805       ENDIF
    1797        IF ( scalar_advec /= 'pw-scheme' .AND.                                  &
    1798           ( scalar_advec /= 'ws-scheme' .AND.                                  &
     1806       IF ( scalar_advec /= 'pw-scheme'  .AND.                                 &
     1807          ( scalar_advec /= 'ws-scheme'  .AND.                                 &
    17991808            scalar_advec /= 'ws-scheme-mono' )                                 &
    18001809          )  THEN
    1801           message_string = 'non-cyclic lateral boundaries do not allow ' // &
     1810          message_string = 'non-cyclic lateral boundaries do not allow ' //    &
    18021811                           'scalar_advec = "' // TRIM( scalar_advec ) // '"'
    18031812          CALL message( 'check_parameters', 'PA0053', 1, 2, 0, 6, 0 )
    18041813       ENDIF
    18051814       IF ( galilei_transformation )  THEN
    1806           message_string = 'non-cyclic lateral boundaries do not allow ' // &
     1815          message_string = 'non-cyclic lateral boundaries do not allow ' //    &
    18071816                           'galilei_transformation = .T.'
    18081817          CALL message( 'check_parameters', 'PA0054', 1, 2, 0, 6, 0 )
     
    18191828          bc_e_b = 'neumann'
    18201829          ibc_e_b = 1
    1821           message_string = 'boundary condition bc_e_b changed to "' // &
     1830          message_string = 'boundary condition bc_e_b changed to "' //         &
    18221831                           TRIM( bc_e_b ) // '"'
    18231832          CALL message( 'check_parameters', 'PA0057', 0, 1, 0, 6, 0 )
    18241833       ENDIF
    18251834    ELSE
    1826        message_string = 'unknown boundary condition: bc_e_b = "' // &
     1835       message_string = 'unknown boundary condition: bc_e_b = "' //            &
    18271836                        TRIM( bc_e_b ) // '"'
    18281837       CALL message( 'check_parameters', 'PA0058', 1, 2, 0, 6, 0 )
     
    18361845       ibc_p_b = 1
    18371846    ELSE
    1838        message_string = 'unknown boundary condition: bc_p_b = "' // &
     1847       message_string = 'unknown boundary condition: bc_p_b = "' //            &
    18391848                        TRIM( bc_p_b ) // '"'
    18401849       CALL message( 'check_parameters', 'PA0059', 1, 2, 0, 6, 0 )
     
    18471856       ibc_p_t = 1
    18481857    ELSE
    1849        message_string = 'unknown boundary condition: bc_p_t = "' // &
     1858       message_string = 'unknown boundary condition: bc_p_t = "' //            &
    18501859                        TRIM( bc_p_t ) // '"'
    18511860       CALL message( 'check_parameters', 'PA0061', 1, 2, 0, 6, 0 )
     
    18621871          ibc_pt_b = 1
    18631872       ELSE
    1864           message_string = 'unknown boundary condition: bc_pt_b = "' // &
     1873          message_string = 'unknown boundary condition: bc_pt_b = "' //        &
    18651874                           TRIM( bc_pt_b ) // '"'
    18661875          CALL message( 'check_parameters', 'PA0062', 1, 2, 0, 6, 0 )
     
    18771886       ibc_pt_t = 3
    18781887    ELSE
    1879        message_string = 'unknown boundary condition: bc_pt_t = "' // &
     1888       message_string = 'unknown boundary condition: bc_pt_t = "' //           &
    18801889                        TRIM( bc_pt_t ) // '"'
    18811890       CALL message( 'check_parameters', 'PA0063', 1, 2, 0, 6, 0 )
     
    18891898          ELSEIF ( ibc_pt_b == 1 )  THEN
    18901899             constant_heatflux = .TRUE.
    1891              IF ( TRIM( initializing_actions ) /= 'read_restart_data' .AND.    &
    1892                   .NOT. land_surface )  THEN
     1900             IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.   &
     1901                  .NOT.  land_surface )  THEN
    18931902                surface_heatflux = shf_surf(1)
    18941903             ELSE
     
    18991908    ELSE
    19001909        constant_heatflux = .TRUE.
    1901         IF ( TRIM( initializing_actions ) /= 'read_restart_data' .AND.         &
    1902              large_scale_forcing .AND. .NOT. land_surface )  THEN
     1910        IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.        &
     1911             large_scale_forcing  .AND.  .NOT. land_surface )  THEN
    19031912           surface_heatflux = shf_surf(1)
    19041913        ENDIF
     
    19091918    IF ( neutral )  THEN
    19101919
    1911        IF ( surface_heatflux /= 0.0_wp  .AND. surface_heatflux /= 9999999.9_wp ) &
     1920       IF ( surface_heatflux /= 0.0_wp  .AND.                                  &
     1921            surface_heatflux /= 9999999.9_wp )  THEN
     1922          message_string = 'heatflux must not be set for pure neutral flow'
     1923          CALL message( 'check_parameters', 'PA0351', 1, 2, 0, 6, 0 )
     1924       ENDIF
     1925
     1926       IF ( top_heatflux /= 0.0_wp  .AND.  top_heatflux /= 9999999.9_wp )      &
    19121927       THEN
    19131928          message_string = 'heatflux must not be set for pure neutral flow'
     
    19151930       ENDIF
    19161931
    1917        IF ( top_heatflux /= 0.0_wp  .AND.  top_heatflux /= 9999999.9_wp ) &
    1918        THEN
    1919           message_string = 'heatflux must not be set for pure neutral flow'
    1920           CALL message( 'check_parameters', 'PA0351', 1, 2, 0, 6, 0 )
    1921        ENDIF
    1922 
    1923     ENDIF
    1924 
    1925     IF ( top_momentumflux_u /= 9999999.9_wp  .AND.  &
     1932    ENDIF
     1933
     1934    IF ( top_momentumflux_u /= 9999999.9_wp  .AND.                             &
    19261935         top_momentumflux_v /= 9999999.9_wp )  THEN
    19271936       constant_top_momentumflux = .TRUE.
    1928     ELSEIF (  .NOT. ( top_momentumflux_u == 9999999.9_wp  .AND.  &
     1937    ELSEIF (  .NOT. ( top_momentumflux_u == 9999999.9_wp  .AND.                &
    19291938           top_momentumflux_v == 9999999.9_wp ) )  THEN
    1930        message_string = 'both, top_momentumflux_u AND top_momentumflux_v ' // &
     1939       message_string = 'both, top_momentumflux_u AND top_momentumflux_v ' //  &
    19311940                        'must be set'
    19321941       CALL message( 'check_parameters', 'PA0064', 1, 2, 0, 6, 0 )
     
    19371946!-- temperature. In this case specification of a constant heat flux is
    19381947!-- forbidden.
    1939     IF ( ibc_pt_b == 0  .AND.   constant_heatflux  .AND. &
     1948    IF ( ibc_pt_b == 0  .AND.  constant_heatflux  .AND.                        &
    19401949         surface_heatflux /= 0.0_wp )  THEN
    19411950       message_string = 'boundary_condition: bc_pt_b = "' // TRIM( bc_pt_b ) //&
     
    19441953    ENDIF
    19451954    IF ( constant_heatflux  .AND.  pt_surface_initial_change /= 0.0_wp )  THEN
    1946        WRITE ( message_string, * )  'constant_heatflux = .TRUE. is not allo', &
    1947                'wed with pt_surface_initial_change (/=0) = ', &
     1955       WRITE ( message_string, * )  'constant_heatflux = .TRUE. is not allo',  &
     1956               'wed with pt_surface_initial_change (/=0) = ',                  &
    19481957               pt_surface_initial_change
    19491958       CALL message( 'check_parameters', 'PA0066', 1, 2, 0, 6, 0 )
     
    19541963!-- temperature. In this case specification of a constant heat flux is
    19551964!-- forbidden.
    1956     IF ( ibc_pt_t == 0  .AND.   constant_top_heatflux  .AND. &
     1965    IF ( ibc_pt_t == 0  .AND.  constant_top_heatflux  .AND.                    &
    19571966         top_heatflux /= 0.0_wp )  THEN
    19581967       message_string = 'boundary_condition: bc_pt_t = "' // TRIM( bc_pt_t ) //&
     
    19691978          ibc_sa_t = 1
    19701979       ELSE
    1971           message_string = 'unknown boundary condition: bc_sa_t = "' // &
     1980          message_string = 'unknown boundary condition: bc_sa_t = "' //        &
    19721981                           TRIM( bc_sa_t ) // '"'
    19731982          CALL message( 'check_parameters', 'PA0068', 1, 2, 0, 6, 0 )
     
    19751984
    19761985       IF ( top_salinityflux == 9999999.9_wp )  constant_top_salinityflux = .FALSE.
    1977        IF ( ibc_sa_t == 1  .AND.   top_salinityflux == 9999999.9_wp )  THEN
    1978           message_string = 'boundary condition: bc_sa_t = "' // &
    1979                            TRIM( bc_sa_t ) // '" requires to set ' // &
     1986       IF ( ibc_sa_t == 1  .AND.  top_salinityflux == 9999999.9_wp )  THEN
     1987          message_string = 'boundary condition: bc_sa_t = "' //                &
     1988                           TRIM( bc_sa_t ) // '" requires to set ' //          &
    19801989                           'top_salinityflux'
    19811990          CALL message( 'check_parameters', 'PA0069', 1, 2, 0, 6, 0 )
     
    19861995!--    salinity. In this case specification of a constant salinity flux is
    19871996!--    forbidden.
    1988        IF ( ibc_sa_t == 0  .AND.   constant_top_salinityflux  .AND. &
     1997       IF ( ibc_sa_t == 0  .AND.  constant_top_salinityflux  .AND.            &
    19891998            top_salinityflux /= 0.0_wp )  THEN
    1990           message_string = 'boundary condition: bc_sa_t = "' // &
    1991                            TRIM( bc_sa_t ) // '" is not allowed with ' // &
     1999          message_string = 'boundary condition: bc_sa_t = "' //                &
     2000                           TRIM( bc_sa_t ) // '" is not allowed with ' //      &
    19922001                           'constant_top_salinityflux = .TRUE.'
    19932002          CALL message( 'check_parameters', 'PA0070', 1, 2, 0, 6, 0 )
     
    20102019          ibc_q_b = 1
    20112020       ELSE
    2012           message_string = 'unknown boundary condition: bc_' // TRIM( sq ) // &
     2021          message_string = 'unknown boundary condition: bc_' // TRIM( sq ) //  &
    20132022                           '_b ="' // TRIM( bc_q_b ) // '"'
    20142023          CALL message( 'check_parameters', 'PA0071', 1, 2, 0, 6, 0 )
     
    20212030          ibc_q_t = 3
    20222031       ELSE
    2023           message_string = 'unknown boundary condition: bc_' // TRIM( sq ) // &
     2032          message_string = 'unknown boundary condition: bc_' // TRIM( sq ) //  &
    20242033                           '_t ="' // TRIM( bc_q_t ) // '"'
    20252034          CALL message( 'check_parameters', 'PA0072', 1, 2, 0, 6, 0 )
     
    20402049       ELSE
    20412050          constant_waterflux = .TRUE.
    2042           IF ( TRIM( initializing_actions ) /= 'read_restart_data' .AND. &
    2043                  large_scale_forcing ) THEN
     2051          IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .AND.      &
     2052               large_scale_forcing ) THEN
    20442053             surface_waterflux = qsws_surf(1)
    20452054          ENDIF
     
    20582067       IF ( constant_waterflux  .AND.  q_surface_initial_change /= 0.0_wp )  THEN
    20592068          WRITE( message_string, * )  'a prescribed surface flux is not allo', &
    2060                  'wed with ', sq, '_surface_initial_change (/=0) = ', &
     2069                 'wed with ', sq, '_surface_initial_change (/=0) = ',          &
    20612070                 q_surface_initial_change
    20622071          CALL message( 'check_parameters', 'PA0074', 1, 2, 0, 6, 0 )
     
    20712080       ibc_uv_b = 1
    20722081       IF ( constant_flux_layer )  THEN
    2073           message_string = 'boundary condition: bc_uv_b = "' // &
     2082          message_string = 'boundary condition: bc_uv_b = "' //                &
    20742083               TRIM( bc_uv_b ) // '" is not allowed with constant_flux_layer'  &
    20752084               // ' = .TRUE.'
     
    20772086       ENDIF
    20782087    ELSE
    2079        message_string = 'unknown boundary condition: bc_uv_b = "' // &
     2088       message_string = 'unknown boundary condition: bc_uv_b = "' //           &
    20802089                        TRIM( bc_uv_b ) // '"'
    20812090       CALL message( 'check_parameters', 'PA0076', 1, 2, 0, 6, 0 )
     
    21062115          ibc_uv_t = 3
    21072116       ELSE
    2108           message_string = 'unknown boundary condition: bc_uv_t = "' // &
     2117          message_string = 'unknown boundary condition: bc_uv_t = "' //        &
    21092118                           TRIM( bc_uv_t ) // '"'
    21102119          CALL message( 'check_parameters', 'PA0077', 1, 2, 0, 6, 0 )
     
    21172126       rayleigh_damping_factor = 0.0_wp
    21182127    ELSE
    2119        IF ( rayleigh_damping_factor < 0.0_wp .OR. rayleigh_damping_factor > 1.0_wp ) &
    2120        THEN
    2121           WRITE( message_string, * )  'rayleigh_damping_factor = ', &
     2128       IF ( rayleigh_damping_factor < 0.0_wp  .OR.                            &
     2129            rayleigh_damping_factor > 1.0_wp )  THEN
     2130          WRITE( message_string, * )  'rayleigh_damping_factor = ',            &
    21222131                              rayleigh_damping_factor, ' out of range [0.0,1.0]'
    21232132          CALL message( 'check_parameters', 'PA0078', 1, 2, 0, 6, 0 )
     
    21262135
    21272136    IF ( rayleigh_damping_height == -1.0_wp )  THEN
    2128        IF ( .NOT. ocean )  THEN
     2137       IF (  .NOT. ocean )  THEN
    21292138          rayleigh_damping_height = 0.66666666666_wp * zu(nzt)
    21302139       ELSE
     
    21322141       ENDIF
    21332142    ELSE
    2134        IF ( .NOT. ocean )  THEN
    2135           IF ( rayleigh_damping_height < 0.0_wp  .OR. &
     2143       IF (  .NOT. ocean )  THEN
     2144          IF ( rayleigh_damping_height < 0.0_wp  .OR.                          &
    21362145               rayleigh_damping_height > zu(nzt) )  THEN
    2137              WRITE( message_string, * )  'rayleigh_damping_height = ', &
     2146             WRITE( message_string, * )  'rayleigh_damping_height = ',         &
    21382147                   rayleigh_damping_height, ' out of range [0.0,', zu(nzt), ']'
    21392148             CALL message( 'check_parameters', 'PA0079', 1, 2, 0, 6, 0 )
    21402149          ENDIF
    21412150       ELSE
    2142           IF ( rayleigh_damping_height > 0.0_wp  .OR. &
     2151          IF ( rayleigh_damping_height > 0.0_wp  .OR.                          &
    21432152               rayleigh_damping_height < zu(nzb) )  THEN
    2144              WRITE( message_string, * )  'rayleigh_damping_height = ', &
     2153             WRITE( message_string, * )  'rayleigh_damping_height = ',         &
    21452154                   rayleigh_damping_height, ' out of range [0.0,', zu(nzb), ']'
    21462155             CALL message( 'check_parameters', 'PA0079', 1, 2, 0, 6, 0 )
     
    21542163!-- be opened (cf. check_open)
    21552164    IF ( statistic_regions > 9  .OR.  statistic_regions < 0 )  THEN
    2156        WRITE ( message_string, * ) 'number of statistic_regions = ', &
     2165       WRITE ( message_string, * ) 'number of statistic_regions = ',           &
    21572166                   statistic_regions+1, ' but only 10 regions are allowed'
    21582167       CALL message( 'check_parameters', 'PA0082', 1, 2, 0, 6, 0 )
    21592168    ENDIF
    2160     IF ( normalizing_region > statistic_regions  .OR. &
     2169    IF ( normalizing_region > statistic_regions  .OR.                          &
    21612170         normalizing_region < 0)  THEN
    2162        WRITE ( message_string, * ) 'normalizing_region = ', &
     2171       WRITE ( message_string, * ) 'normalizing_region = ',                    &
    21632172                normalizing_region, ' must be >= 0 and <= ',statistic_regions, &
    21642173                ' (value of statistic_regions)'
     
    21842193!
    21852194!-- Set the default skip time intervals for data output, if necessary
    2186     IF ( skip_time_dopr    == 9999999.9_wp ) &
     2195    IF ( skip_time_dopr    == 9999999.9_wp )                                   &
    21872196                                       skip_time_dopr    = skip_time_data_output
    2188     IF ( skip_time_dosp    == 9999999.9_wp ) &
     2197    IF ( skip_time_dosp    == 9999999.9_wp )                                   &
    21892198                                       skip_time_dosp    = skip_time_data_output
    2190     IF ( skip_time_do2d_xy == 9999999.9_wp ) &
     2199    IF ( skip_time_do2d_xy == 9999999.9_wp )                                   &
    21912200                                       skip_time_do2d_xy = skip_time_data_output
    2192     IF ( skip_time_do2d_xz == 9999999.9_wp ) &
     2201    IF ( skip_time_do2d_xz == 9999999.9_wp )                                   &
    21932202                                       skip_time_do2d_xz = skip_time_data_output
    2194     IF ( skip_time_do2d_yz == 9999999.9_wp ) &
     2203    IF ( skip_time_do2d_yz == 9999999.9_wp )                                   &
    21952204                                       skip_time_do2d_yz = skip_time_data_output
    2196     IF ( skip_time_do3d    == 9999999.9_wp ) &
     2205    IF ( skip_time_do3d    == 9999999.9_wp )                                   &
    21972206                                       skip_time_do3d    = skip_time_data_output
    2198     IF ( skip_time_data_output_av == 9999999.9_wp ) &
     2207    IF ( skip_time_data_output_av == 9999999.9_wp )                            &
    21992208                                skip_time_data_output_av = skip_time_data_output
    22002209    DO  mid = 1, max_masks
    2201        IF ( skip_time_domask(mid) == 9999999.9_wp ) &
     2210       IF ( skip_time_domask(mid) == 9999999.9_wp )                            &
    22022211                                skip_time_domask(mid)    = skip_time_data_output
    22032212    ENDDO
     
    22072216!-- spectra)
    22082217    IF ( averaging_interval > dt_data_output_av )  THEN
    2209        WRITE( message_string, * )  'averaging_interval = ', &
     2218       WRITE( message_string, * )  'averaging_interval = ',                    &
    22102219             averaging_interval, ' must be <= dt_data_output = ', dt_data_output
    22112220       CALL message( 'check_parameters', 'PA0085', 1, 2, 0, 6, 0 )
     
    22172226
    22182227    IF ( averaging_interval_pr > dt_dopr )  THEN
    2219        WRITE( message_string, * )  'averaging_interval_pr = ', &
     2228       WRITE( message_string, * )  'averaging_interval_pr = ',                 &
    22202229             averaging_interval_pr, ' must be <= dt_dopr = ', dt_dopr
    22212230       CALL message( 'check_parameters', 'PA0086', 1, 2, 0, 6, 0 )
     
    22272236
    22282237    IF ( averaging_interval_sp > dt_dosp )  THEN
    2229        WRITE( message_string, * )  'averaging_interval_sp = ', &
     2238       WRITE( message_string, * )  'averaging_interval_sp = ',                 &
    22302239             averaging_interval_sp, ' must be <= dt_dosp = ', dt_dosp
    22312240       CALL message( 'check_parameters', 'PA0087', 1, 2, 0, 6, 0 )
     
    22522261!-- Check the sample rate for averaging (first for 3d-data, then for profiles)
    22532262    IF ( dt_averaging_input > averaging_interval )  THEN
    2254        WRITE( message_string, * )  'dt_averaging_input = ', &
    2255                 dt_averaging_input, ' must be <= averaging_interval = ', &
     2263       WRITE( message_string, * )  'dt_averaging_input = ',                    &
     2264                dt_averaging_input, ' must be <= averaging_interval = ',       &
    22562265                averaging_interval
    22572266       CALL message( 'check_parameters', 'PA0088', 1, 2, 0, 6, 0 )
     
    22592268
    22602269    IF ( dt_averaging_input_pr > averaging_interval_pr )  THEN
    2261        WRITE( message_string, * )  'dt_averaging_input_pr = ', &
     2270       WRITE( message_string, * )  'dt_averaging_input_pr = ',                 &
    22622271                dt_averaging_input_pr, ' must be <= averaging_interval_pr = ', &
    22632272                averaging_interval_pr
     
    22722281       ELSE
    22732282          IF ( precipitation_amount_interval > dt_do2d_xy )  THEN
    2274              WRITE( message_string, * )  'precipitation_amount_interval = ', &
    2275                  precipitation_amount_interval, ' must not be larger than ', &
     2283             WRITE( message_string, * )  'precipitation_amount_interval = ',   &
     2284                 precipitation_amount_interval, ' must not be larger than ',   &
    22762285                 'dt_do2d_xy = ', dt_do2d_xy
    22772286             CALL message( 'check_parameters', 'PA0090', 1, 2, 0, 6, 0 )
     
    25322541          CASE ( 's', '#s' )
    25332542             IF ( .NOT. passive_scalar )  THEN
    2534                 message_string = 'data_output_pr = ' // &
     2543                message_string = 'data_output_pr = ' //                        &
    25352544                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    25362545                                 'lemented for passive_scalar = .FALSE.'
     
    25732582          CASE ( 'lpt', '#lpt' )
    25742583             IF ( .NOT. cloud_physics ) THEN
    2575                 message_string = 'data_output_pr = ' // &
     2584                message_string = 'data_output_pr = ' //                        &
    25762585                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    25772586                                 'lemented for cloud_physics = .FALSE.'
     
    26162625
    26172626          CASE ( 'w"q"' )
    2618              IF ( .NOT. humidity )  THEN
    2619                 message_string = 'data_output_pr = ' // &
     2627             IF (  .NOT. humidity )  THEN
     2628                message_string = 'data_output_pr = ' //                        &
    26202629                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    26212630                                 'lemented for humidity = .FALSE.'
     
    26282637
    26292638          CASE ( 'w*q*' )
    2630              IF ( .NOT. humidity )  THEN
    2631                 message_string = 'data_output_pr = ' // &
     2639             IF (  .NOT. humidity )  THEN
     2640                message_string = 'data_output_pr = ' //                        &
    26322641                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    26332642                                 'lemented for humidity = .FALSE.'
     
    26402649
    26412650          CASE ( 'wq' )
    2642              IF ( .NOT. humidity )  THEN
    2643                 message_string = 'data_output_pr = ' // &
     2651             IF (  .NOT. humidity )  THEN
     2652                message_string = 'data_output_pr = ' //                        &
    26442653                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    26452654                                 'lemented for humidity = .FALSE.'
     
    26522661
    26532662          CASE ( 'w"s"' )
    2654              IF ( .NOT. passive_scalar ) THEN
    2655                 message_string = 'data_output_pr = ' // &
     2663             IF (  .NOT.  passive_scalar ) THEN
     2664                message_string = 'data_output_pr = ' //                        &
    26562665                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    26572666                                 'lemented for passive_scalar = .FALSE.'
     
    26642673
    26652674          CASE ( 'w*s*' )
    2666              IF ( .NOT. passive_scalar ) THEN
    2667                 message_string = 'data_output_pr = ' // &
     2675             IF (  .NOT.  passive_scalar ) THEN
     2676                message_string = 'data_output_pr = ' //                        &
    26682677                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    26692678                                 'lemented for passive_scalar = .FALSE.'
     
    26762685
    26772686          CASE ( 'ws' )
    2678              IF ( .NOT. passive_scalar ) THEN
    2679                 message_string = 'data_output_pr = ' // &
     2687             IF (  .NOT.  passive_scalar ) THEN
     2688                message_string = 'data_output_pr = ' //                        &
    26802689                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    26812690                                 'lemented for passive_scalar = .FALSE.'
     
    26882697
    26892698          CASE ( 'w"qv"' )
    2690              IF ( humidity  .AND.  .NOT. cloud_physics ) &
    2691              THEN
     2699             IF ( humidity  .AND.  .NOT.  cloud_physics )  THEN
    26922700                dopr_index(i) = 48
    26932701                dopr_unit(i)  = 'kg/kg m/s'
    26942702                hom(:,2,48,:) = SPREAD( zw, 2, statistic_regions+1 )
    2695              ELSEIF( humidity .AND. cloud_physics ) THEN
     2703             ELSEIF ( humidity  .AND.  cloud_physics ) THEN
    26962704                dopr_index(i) = 51
    26972705                dopr_unit(i)  = 'kg/kg m/s'
    26982706                hom(:,2,51,:) = SPREAD( zw, 2, statistic_regions+1 )
    26992707             ELSE
    2700                 message_string = 'data_output_pr = ' // &
     2708                message_string = 'data_output_pr = ' //                        &
    27012709                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    27022710                                 'lemented for cloud_physics = .FALSE. an&' // &
     
    27062714
    27072715          CASE ( 'w*qv*' )
    2708              IF ( humidity  .AND.  .NOT. cloud_physics ) &
     2716             IF ( humidity  .AND.  .NOT. cloud_physics )                       &
    27092717             THEN
    27102718                dopr_index(i) = 49
     
    27162724                hom(:,2,52,:) = SPREAD( zw, 2, statistic_regions+1 )
    27172725             ELSE
    2718                 message_string = 'data_output_pr = ' // &
     2726                message_string = 'data_output_pr = ' //                        &
    27192727                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    27202728                                 'lemented for cloud_physics = .FALSE. an&' // &
     
    27242732
    27252733          CASE ( 'wqv' )
    2726              IF ( humidity  .AND.  .NOT. cloud_physics ) &
    2727              THEN
     2734             IF ( humidity  .AND.  .NOT.  cloud_physics )  THEN
    27282735                dopr_index(i) = 50
    27292736                dopr_unit(i)  = 'kg/kg m/s'
    27302737                hom(:,2,50,:) = SPREAD( zw, 2, statistic_regions+1 )
    2731              ELSEIF( humidity .AND. cloud_physics ) THEN
     2738             ELSEIF ( humidity  .AND.  cloud_physics ) THEN
    27322739                dopr_index(i) = 53
    27332740                dopr_unit(i)  = 'kg/kg m/s'
     
    27422749
    27432750          CASE ( 'ql' )
    2744              IF ( .NOT. cloud_physics  .AND.  .NOT. cloud_droplets )  THEN
     2751             IF (  .NOT.  cloud_physics  .AND.  .NOT. cloud_droplets )  THEN
    27452752                message_string = 'data_output_pr = ' //                        &
    27462753                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    28012808
    28022809          CASE ( 'rho' )
    2803              IF ( .NOT. ocean ) THEN
     2810             IF (  .NOT. ocean ) THEN
    28042811                message_string = 'data_output_pr = ' //                        &
    28052812                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    28192826
    28202827          CASE ( 'w"sa"' )
    2821              IF ( .NOT. ocean ) THEN
     2828             IF (  .NOT. ocean ) THEN
    28222829                message_string = 'data_output_pr = ' //                        &
    28232830                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    28312838
    28322839          CASE ( 'w*sa*' )
    2833              IF ( .NOT. ocean ) THEN
     2840             IF (  .NOT. ocean ) THEN
    28342841                message_string = 'data_output_pr = ' //                        &
    28352842                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    28432850
    28442851          CASE ( 'wsa' )
    2845              IF ( .NOT. ocean ) THEN
     2852             IF (  .NOT. ocean ) THEN
    28462853                message_string = 'data_output_pr = ' //                        &
    28472854                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    28652872
    28662873          CASE ( 'q*2' )
    2867              IF ( .NOT. humidity )  THEN
     2874             IF (  .NOT. humidity )  THEN
    28682875                message_string = 'data_output_pr = ' //                        &
    28692876                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    28772884
    28782885          CASE ( 'prho' )
    2879              IF ( .NOT. ocean ) THEN
     2886             IF (  .NOT. ocean ) THEN
    28802887                message_string = 'data_output_pr = ' //                        &
    28812888                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    28942901
    28952902          CASE ( 'nr' )
    2896              IF ( .NOT. cloud_physics )  THEN
     2903             IF (  .NOT. cloud_physics )  THEN
    28972904                message_string = 'data_output_pr = ' //                        &
    28982905                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    29042911                                 'lemented for cloud_scheme /= seifert_beheng'
    29052912                CALL message( 'check_parameters', 'PA0358', 1, 2, 0, 6, 0 )
    2906              ELSEIF ( .NOT. precipitation )  THEN
     2913             ELSEIF (  .NOT. precipitation )  THEN
    29072914                message_string = 'data_output_pr = ' //                        &
    29082915                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    29162923
    29172924          CASE ( 'qr' )
    2918              IF ( .NOT. cloud_physics )  THEN
     2925             IF (  .NOT. cloud_physics )  THEN
    29192926                message_string = 'data_output_pr = ' //                        &
    29202927                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    29262933                                 'lemented for cloud_scheme /= seifert_beheng'
    29272934                CALL message( 'check_parameters', 'PA0358', 1, 2, 0, 6, 0 )
    2928              ELSEIF ( .NOT. precipitation )  THEN
     2935             ELSEIF (  .NOT. precipitation )  THEN
    29292936                message_string = 'data_output_pr = ' //                        &
    29302937                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    29382945
    29392946          CASE ( 'qc' )
    2940              IF ( .NOT. cloud_physics )  THEN
     2947             IF (  .NOT. cloud_physics )  THEN
    29412948                message_string = 'data_output_pr = ' //                        &
    29422949                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    29552962
    29562963          CASE ( 'prr' )
    2957              IF ( .NOT. cloud_physics )  THEN
     2964             IF (  .NOT. cloud_physics )  THEN
    29582965                message_string = 'data_output_pr = ' //                        &
    29592966                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    29652972                                 'lemented for cloud_scheme /= seifert_beheng'
    29662973                CALL message( 'check_parameters', 'PA0358', 1, 2, 0, 6, 0 )
    2967              ELSEIF ( .NOT. precipitation )  THEN
     2974             ELSEIF (  .NOT. precipitation )  THEN
    29682975                message_string = 'data_output_pr = ' //                        &
    29692976                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    29882995
    29892996          CASE ( 'w_subs' )
    2990              IF ( .NOT. large_scale_subsidence )  THEN
     2997             IF (  .NOT. large_scale_subsidence )  THEN
    29912998                message_string = 'data_output_pr = ' //                        &
    29922999                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    30003007
    30013008          CASE ( 'td_lsa_lpt' )
    3002              IF ( .NOT. large_scale_forcing )  THEN
     3009             IF (  .NOT. large_scale_forcing )  THEN
    30033010                message_string = 'data_output_pr = ' //                        &
    30043011                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    30123019
    30133020          CASE ( 'td_lsa_q' )
    3014              IF ( .NOT. large_scale_forcing )  THEN
     3021             IF (  .NOT. large_scale_forcing )  THEN
    30153022                message_string = 'data_output_pr = ' //                        &
    30163023                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    30243031
    30253032          CASE ( 'td_sub_lpt' )
    3026              IF ( .NOT. large_scale_forcing )  THEN
     3033             IF (  .NOT. large_scale_forcing )  THEN
    30273034                message_string = 'data_output_pr = ' //                        &
    30283035                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    30363043
    30373044          CASE ( 'td_sub_q' )
    3038              IF ( .NOT. large_scale_forcing )  THEN
     3045             IF (  .NOT. large_scale_forcing )  THEN
    30393046                message_string = 'data_output_pr = ' //                        &
    30403047                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    30483055
    30493056          CASE ( 'td_nud_lpt' )
    3050              IF ( .NOT. nudging )  THEN
     3057             IF (  .NOT. nudging )  THEN
    30513058                message_string = 'data_output_pr = ' //                        &
    30523059                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    30603067
    30613068          CASE ( 'td_nud_q' )
    3062              IF ( .NOT. nudging )  THEN
     3069             IF (  .NOT. nudging )  THEN
    30633070                message_string = 'data_output_pr = ' //                        &
    30643071                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    30723079
    30733080          CASE ( 'td_nud_u' )
    3074              IF ( .NOT. nudging )  THEN
     3081             IF (  .NOT. nudging )  THEN
    30753082                message_string = 'data_output_pr = ' //                        &
    30763083                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    30843091
    30853092          CASE ( 'td_nud_v' )
    3086              IF ( .NOT. nudging )  THEN
     3093             IF (  .NOT. nudging )  THEN
    30873094                message_string = 'data_output_pr = ' //                        &
    30883095                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    30963103
    30973104          CASE ( 't_soil', '#t_soil' )
    3098              IF ( .NOT. land_surface )  THEN
     3105             IF (  .NOT. land_surface )  THEN
    30993106                message_string = 'data_output_pr = ' //                        &
    31003107                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    31133120
    31143121          CASE ( 'm_soil', '#m_soil' )
    3115              IF ( .NOT. land_surface )  THEN
     3122             IF (  .NOT. land_surface )  THEN
    31163123                message_string = 'data_output_pr = ' //                        &
    31173124                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
     
    31303137
    31313138          CASE ( 'rad_net' )
    3132              IF ( (.NOT. radiation) .OR. radiation_scheme == 'constant' )  THEN
     3139             IF ( (  .NOT.  radiation )  .OR.  radiation_scheme == 'constant' )&
     3140             THEN
    31333141                message_string = 'data_output_pr = ' //                        &
    31343142                                 TRIM( data_output_pr(i) ) // ' is not ava' // &
     
    31433151
    31443152          CASE ( 'rad_lw_in' )
    3145              IF ( (.NOT. radiation) .OR. radiation_scheme == 'constant' )  THEN
     3153             IF ( (  .NOT.  radiation)  .OR.  radiation_scheme == 'constant' ) &
     3154             THEN
    31463155                message_string = 'data_output_pr = ' //                        &
    31473156                                 TRIM( data_output_pr(i) ) // ' is not ava' // &
     
    31563165
    31573166          CASE ( 'rad_lw_out' )
    3158              IF ( (.NOT. radiation) .OR. radiation_scheme == 'constant' )  THEN
     3167             IF ( (  .NOT. radiation )  .OR.  radiation_scheme == 'constant' ) &
     3168             THEN
    31593169                message_string = 'data_output_pr = ' //                        &
    31603170                                 TRIM( data_output_pr(i) ) // ' is not ava' // &
     
    31693179
    31703180          CASE ( 'rad_sw_in' )
    3171              IF ( (.NOT. radiation) .OR. radiation_scheme == 'constant' )  THEN
     3181             IF ( (  .NOT. radiation )  .OR.  radiation_scheme == 'constant' ) &
     3182             THEN
    31723183                message_string = 'data_output_pr = ' //                        &
    31733184                                 TRIM( data_output_pr(i) ) // ' is not ava' // &
     
    31823193
    31833194          CASE ( 'rad_sw_out')
    3184              IF ( (.NOT. radiation) .OR. radiation_scheme == 'constant' )  THEN
     3195             IF ( (  .NOT.  radiation )  .OR.  radiation_scheme == 'constant' ) &
     3196             THEN
    31853197                message_string = 'data_output_pr = ' //                        &
    31863198                                 TRIM( data_output_pr(i) ) // ' is not ava' // &
     
    31953207
    31963208          CASE ( 'rad_lw_cs_hr' )
    3197              IF ( (.NOT. radiation) .OR. radiation_scheme /= 'rrtmg' )  THEN
     3209             IF ( (  .NOT.  radiation )  .OR.  radiation_scheme /= 'rrtmg' )   &
     3210             THEN
    31983211                message_string = 'data_output_pr = ' //                        &
    31993212                                 TRIM( data_output_pr(i) ) // ' is not ava' // &
     
    32083221
    32093222          CASE ( 'rad_lw_hr' )
    3210              IF ( (.NOT. radiation) .OR. radiation_scheme /= 'rrtmg' )  THEN
     3223             IF ( (  .NOT.  radiation )  .OR.  radiation_scheme /= 'rrtmg' )   &
     3224             THEN
    32113225                message_string = 'data_output_pr = ' //                        &
    32123226                                 TRIM( data_output_pr(i) ) // ' is not ava' // &
     
    32213235
    32223236          CASE ( 'rad_sw_cs_hr' )
    3223              IF ( (.NOT. radiation) .OR. radiation_scheme /= 'rrtmg' )  THEN
     3237             IF ( (  .NOT.  radiation )  .OR.  radiation_scheme /= 'rrtmg' )   &
     3238             THEN
    32243239                message_string = 'data_output_pr = ' //                        &
    32253240                                 TRIM( data_output_pr(i) ) // ' is not ava' // &
     
    32343249
    32353250          CASE ( 'rad_sw_hr' )
    3236              IF ( (.NOT. radiation) .OR. radiation_scheme /= 'rrtmg' )  THEN
     3251             IF ( (  .NOT.  radiation )  .OR.  radiation_scheme /= 'rrtmg' )   &
     3252             THEN
    32373253                message_string = 'data_output_pr = ' //                        &
    32383254                                 TRIM( data_output_pr(i) ) // ' is not ava' // &
     
    33293345
    33303346          CASE ( 'lpt' )
    3331              IF ( .NOT. cloud_physics )  THEN
     3347             IF (  .NOT. cloud_physics )  THEN
    33323348                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    33333349                         'res cloud_physics = .TRUE.'
     
    33373353
    33383354          CASE ( 'm_soil' )
    3339              IF ( .NOT. land_surface )  THEN
     3355             IF (  .NOT. land_surface )  THEN
    33403356                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    33413357                         'land_surface = .TRUE.'
     
    33453361
    33463362          CASE ( 'nr' )
    3347              IF ( .NOT. cloud_physics )  THEN
     3363             IF (  .NOT. cloud_physics )  THEN
    33483364                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    33493365                         'res cloud_physics = .TRUE.'
     
    33573373
    33583374          CASE ( 'pc', 'pr' )
    3359              IF ( .NOT. particle_advection )  THEN
     3375             IF (  .NOT. particle_advection )  THEN
    33603376                message_string = 'output of "' // TRIM( var ) // '" requir' // &
    33613377                   'es a "particles_par"-NAMELIST in the parameter file (PARIN)'
     
    33663382
    33673383          CASE ( 'prr' )
    3368              IF ( .NOT. cloud_physics )  THEN
     3384             IF (  .NOT. cloud_physics )  THEN
    33693385                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    33703386                         'res cloud_physics = .TRUE.'
     
    33743390                         'res cloud_scheme = seifert_beheng'
    33753391                CALL message( 'check_parameters', 'PA0359', 1, 2, 0, 6, 0 )
    3376              ELSEIF ( .NOT. precipitation )  THEN
     3392             ELSEIF (  .NOT. precipitation )  THEN
    33773393                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    33783394                                 'res precipitation = .TRUE.'
     
    33823398
    33833399          CASE ( 'q', 'vpt' )
    3384              IF ( .NOT. humidity )  THEN
     3400             IF (  .NOT. humidity )  THEN
    33853401                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    33863402                                 'res humidity = .TRUE.'
     
    33913407
    33923408          CASE ( 'qc' )
    3393              IF ( .NOT. cloud_physics )  THEN
     3409             IF (  .NOT. cloud_physics )  THEN
    33943410                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    33953411                         'res cloud_physics = .TRUE.'
     
    34033419
    34043420          CASE ( 'ql' )
    3405              IF ( .NOT. ( cloud_physics  .OR.  cloud_droplets ) )  THEN
     3421             IF ( .NOT.  ( cloud_physics  .OR.  cloud_droplets ) )  THEN
    34063422                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    34073423                         'res cloud_physics = .TRUE. or cloud_droplets = .TRUE.'
     
    34113427
    34123428          CASE ( 'ql_c', 'ql_v', 'ql_vp' )
    3413              IF ( .NOT. cloud_droplets )  THEN
     3429             IF (  .NOT. cloud_droplets )  THEN
    34143430                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    34153431                                 'res cloud_droplets = .TRUE.'
     
    34213437
    34223438          CASE ( 'qr' )
    3423              IF ( .NOT. cloud_physics )  THEN
     3439             IF (  .NOT. cloud_physics )  THEN
    34243440                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    34253441                         'res cloud_physics = .TRUE.'
     
    34293445                         'res cloud_scheme = seifert_beheng'
    34303446                CALL message( 'check_parameters', 'PA0359', 1, 2, 0, 6, 0 )
    3431              ELSEIF ( .NOT. precipitation )  THEN
     3447             ELSEIF (  .NOT. precipitation )  THEN
    34323448                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    34333449                                 'res precipitation = .TRUE.'
     
    34373453
    34383454          CASE ( 'qv' )
    3439              IF ( .NOT. cloud_physics )  THEN
     3455             IF (  .NOT. cloud_physics )  THEN
    34403456                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    34413457                                 'res cloud_physics = .TRUE.'
     
    34463462          CASE ( 'rad_lw_in', 'rad_lw_out', 'rad_lw_cs_hr', 'rad_lw_hr',       &
    34473463                 'rad_sw_in', 'rad_sw_out', 'rad_sw_cs_hr', 'rad_sw_hr' )
    3448              IF ( .NOT. radiation .OR. radiation_scheme /= 'rrtmg' )  THEN
     3464             IF (  .NOT.  radiation  .OR. radiation_scheme /= 'rrtmg' )  THEN
    34493465                message_string = '"output of "' // TRIM( var ) // '" requi' // &
    34503466                                 'res radiation = .TRUE. and ' //              &
     
    34553471
    34563472          CASE ( 'rho' )
    3457              IF ( .NOT. ocean )  THEN
     3473             IF (  .NOT. ocean )  THEN
    34583474                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    34593475                                 'res ocean = .TRUE.'
     
    34633479
    34643480          CASE ( 's' )
    3465              IF ( .NOT. passive_scalar )  THEN
     3481             IF (  .NOT. passive_scalar )  THEN
    34663482                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    34673483                                 'res passive_scalar = .TRUE.'
     
    34713487
    34723488          CASE ( 'sa' )
    3473              IF ( .NOT. ocean )  THEN
     3489             IF (  .NOT. ocean )  THEN
    34743490                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    34753491                                 'res ocean = .TRUE.'
     
    34793495
    34803496          CASE ( 't_soil' )
    3481              IF ( .NOT. land_surface )  THEN
     3497             IF (  .NOT. land_surface )  THEN
    34823498                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    34833499                         'land_surface = .TRUE.'
     
    34913507                 'qsws_liq_eb*', 'qsws_soil_eb*', 'qsws_veg_eb*', 'rad_net*',  &
    34923508                 'rrtm_aldif*', 'rrtm_aldir*', 'rrtm_asdif*', 'rrtm_asdir*',   &
    3493                  'r_a*', 'r_s*', 'shf*', 'shf_eb*', 't*', 'u*', 'z0*', 'z0h*' )
     3509                 'r_a*', 'r_s*', 'shf*', 'shf_eb*', 't*', 'u*', 'z0*', 'z0h*', &
     3510                 'z0q*' )
    34943511             IF ( k == 0  .OR.  data_output(i)(ilen-2:ilen) /= '_xy' )  THEN
    34953512                message_string = 'illegal value for data_output: "' //         &
     
    34983515                CALL message( 'check_parameters', 'PA0111', 1, 2, 0, 6, 0 )
    34993516             ENDIF
    3500              IF ( .NOT. radiation .OR. radiation_scheme /= "rrtmg" )  THEN
    3501                 IF ( TRIM( var ) == 'rrtm_aldif*' .OR.                         &
    3502                      TRIM( var ) == 'rrtm_aldir*' .OR.                         &
    3503                      TRIM( var ) == 'rrtm_asdif*' .OR.                         &
     3517             IF (  .NOT.  radiation  .OR. radiation_scheme /= "rrtmg" )  THEN
     3518                IF ( TRIM( var ) == 'rrtm_aldif*'  .OR.                        &
     3519                     TRIM( var ) == 'rrtm_aldir*'  .OR.                        &
     3520                     TRIM( var ) == 'rrtm_asdif*'  .OR.                        &
    35043521                     TRIM( var ) == 'rrtm_asdir*'      )                       &
    35053522                THEN
     
    35113528             ENDIF
    35123529
    3513              IF ( TRIM( var ) == 'c_liq*'  .AND.  .NOT. land_surface )  THEN
     3530             IF ( TRIM( var ) == 'c_liq*'  .AND.  .NOT.  land_surface )  THEN
    35143531                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    35153532                                 'res land_surface = .TRUE.'
    35163533                CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
    35173534             ENDIF
    3518              IF ( TRIM( var ) == 'c_soil*'  .AND.  .NOT. land_surface )  THEN
     3535             IF ( TRIM( var ) == 'c_soil*'  .AND.  .NOT.  land_surface )  THEN
    35193536                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    35203537                                 'res land_surface = .TRUE.'
     
    35263543                CALL message( 'check_parameters', 'PA0401', 1, 2, 0, 6, 0 )
    35273544             ENDIF
    3528              IF ( TRIM( var ) == 'ghf_eb*'  .AND.  .NOT. land_surface )  THEN
     3545             IF ( TRIM( var ) == 'ghf_eb*'  .AND.  .NOT.  land_surface )  THEN
    35293546                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    35303547                                 'res land_surface = .TRUE.'
    35313548                CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
    35323549             ENDIF
    3533              IF ( TRIM( var ) == 'lai*'  .AND.  .NOT. land_surface )  THEN
     3550             IF ( TRIM( var ) == 'lai*'  .AND.  .NOT.  land_surface )  THEN
    35343551                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    35353552                                 'res land_surface = .TRUE.'
     
    35413558                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
    35423559             ENDIF
    3543              IF ( TRIM( var ) == 'm_liq_eb*'  .AND.  .NOT. land_surface )  THEN
     3560             IF ( TRIM( var ) == 'm_liq_eb*'  .AND.  .NOT.  land_surface )  THEN
    35443561                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    35453562                                 'res land_surface = .TRUE.'
     
    35563573                CALL message( 'check_parameters', 'PA0113', 1, 2, 0, 6, 0 )
    35573574             ENDIF
    3558              IF ( TRIM( var ) == 'prr*'  .AND.  .NOT. precipitation )  THEN
     3575             IF ( TRIM( var ) == 'prr*'  .AND.  .NOT.  precipitation )  THEN
    35593576                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    35603577                                 'res precipitation = .TRUE.'
    35613578                CALL message( 'check_parameters', 'PA0112', 1, 2, 0, 6, 0 )
    35623579             ENDIF
    3563              IF ( TRIM( var ) == 'qsws*'  .AND.  .NOT. humidity )  THEN
     3580             IF ( TRIM( var ) == 'qsws*'  .AND.  .NOT.  humidity )  THEN
    35643581                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    35653582                                 'res humidity = .TRUE.'
    35663583                CALL message( 'check_parameters', 'PA0322', 1, 2, 0, 6, 0 )
    35673584             ENDIF
    3568              IF ( TRIM( var ) == 'qsws_eb*'  .AND.  .NOT. land_surface )  THEN
     3585             IF ( TRIM( var ) == 'qsws_eb*'  .AND.  .NOT.  land_surface )  THEN
    35693586                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    35703587                                 'res land_surface = .TRUE.'
    35713588                CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
    35723589             ENDIF
    3573              IF ( TRIM( var ) == 'qsws_liq_eb*'  .AND.  .NOT. land_surface )  &
     3590             IF ( TRIM( var ) == 'qsws_liq_eb*'  .AND.  .NOT. land_surface )   &
    35743591             THEN
    35753592                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
     
    35773594                CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
    35783595             ENDIF
    3579              IF ( TRIM( var ) == 'qsws_soil_eb*'  .AND.  .NOT. land_surface ) &
     3596             IF ( TRIM( var ) == 'qsws_soil_eb*'  .AND.  .NOT.  land_surface ) &
    35803597             THEN
    35813598                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
     
    35833600                CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
    35843601             ENDIF
    3585              IF ( TRIM( var ) == 'qsws_veg_eb*'  .AND.  .NOT. land_surface )  &
     3602             IF ( TRIM( var ) == 'qsws_veg_eb*'  .AND.  .NOT. land_surface )   &
    35863603             THEN
    35873604                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
     
    35893606                CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
    35903607             ENDIF
    3591              IF ( TRIM( var ) == 'r_a*'  .AND.  .NOT. land_surface ) &
     3608             IF ( TRIM( var ) == 'r_a*'  .AND.  .NOT.  land_surface ) &
    35923609             THEN
    35933610                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
     
    35953612                CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
    35963613             ENDIF
    3597              IF ( TRIM( var ) == 'r_s*'  .AND.  .NOT. land_surface ) &
     3614             IF ( TRIM( var ) == 'r_s*'  .AND.  .NOT.  land_surface ) &
    35983615             THEN
    35993616                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
     
    37573774!-- Check mask conditions
    37583775    DO mid = 1, max_masks
    3759        IF ( data_output_masks(mid,1) /= ' ' .OR.                               &
     3776       IF ( data_output_masks(mid,1) /= ' '  .OR.                              &
    37603777            data_output_masks_user(mid,1) /= ' ' ) THEN
    37613778          masks = masks + 1
     
    37633780    ENDDO
    37643781   
    3765     IF ( masks < 0 .OR. masks > max_masks )  THEN
     3782    IF ( masks < 0  .OR. masks > max_masks )  THEN
    37663783       WRITE( message_string, * )  'illegal value: masks must be >= 0 and ',   &
    37673784            '<= ', max_masks, ' (=max_masks)'
     
    39083925!
    39093926!-- Check random generator
    3910     IF ( (random_generator /= 'system-specific'     .AND.                      &
    3911           random_generator /= 'random-parallel'   ) .AND.                      &
     3927    IF ( (random_generator /= 'system-specific'      .AND.                     &
     3928          random_generator /= 'random-parallel'   )  .AND.                     &
    39123929          random_generator /= 'numerical-recipes' )  THEN
    39133930       message_string = 'unknown random generator: random_generator = "' //    &
     
    39193936!-- Determine upper and lower hight level indices for random perturbations
    39203937    IF ( disturbance_level_b == -9999999.9_wp )  THEN
    3921        IF ( ocean ) THEN
     3938       IF ( ocean )  THEN
    39223939          disturbance_level_b     = zu((nzt*2)/3)
    39233940          disturbance_level_ind_b = ( nzt * 2 ) / 3
     
    41824199!
    41834200!-- Check pressure gradient conditions
    4184     IF ( dp_external .AND. conserve_volume_flow )  THEN
     4201    IF ( dp_external  .AND. conserve_volume_flow )  THEN
    41854202       WRITE( message_string, * )  'Both dp_external and conserve_volume_flo', &
    41864203            'w are .TRUE. but one of them must be .FALSE.'
     
    41884205    ENDIF
    41894206    IF ( dp_external )  THEN
    4190        IF ( dp_level_b < zu(nzb) .OR. dp_level_b > zu(nzt) )  THEN
     4207       IF ( dp_level_b < zu(nzb)  .OR. dp_level_b > zu(nzt) )  THEN
    41914208          WRITE( message_string, * )  'dp_level_b = ', dp_level_b, ' is out ', &
    41924209               ' of range'
     
    41994216       ENDIF
    42004217    ENDIF
    4201     IF ( ANY( dpdxy /= 0.0_wp ) .AND. .NOT. dp_external )  THEN
     4218    IF ( ANY( dpdxy /= 0.0_wp )  .AND.  .NOT. dp_external )  THEN
    42024219       WRITE( message_string, * )  'dpdxy is nonzero but dp_external is ',     &
    42034220            '.FALSE., i.e. the external pressure gradient & will not be applied'
     
    42304247       ENDIF
    42314248    ENDIF
    4232     IF ( ( u_bulk /= 0.0_wp .OR. v_bulk /= 0.0_wp ) .AND.                      &
    4233          ( .NOT. conserve_volume_flow .OR.                                     &
     4249    IF ( ( u_bulk /= 0.0_wp  .OR.  v_bulk /= 0.0_wp )  .AND.                   &
     4250         ( .NOT. conserve_volume_flow  .OR.                                    &
    42344251         TRIM( conserve_volume_flow_mode ) /= 'bulk_velocity' ) )  THEN
    42354252       WRITE( message_string, * )  'nonzero bulk velocity requires ',          &
     
    42704287!
    42714288!-- Check nudging and large scale forcing from external file
    4272     IF ( nudging .AND. ( .NOT. large_scale_forcing ) )  THEN
     4289    IF ( nudging  .AND.  (  .NOT. large_scale_forcing ) )  THEN
    42734290       message_string = 'Nudging requires large_scale_forcing = .T.. &'//      &
    42744291                        'Surface fluxes and geostrophic wind should be &'//    &
     
    42774294    ENDIF
    42784295
    4279     IF ( large_scale_forcing .AND. ( bc_lr /= 'cyclic'  .OR.                   &
     4296    IF ( large_scale_forcing  .AND.  ( bc_lr /= 'cyclic'  .OR.                 &
    42804297                                    bc_ns /= 'cyclic' ) )  THEN
    42814298       message_string = 'Non-cyclic lateral boundaries do not allow for &' //  &
     
    42844301     ENDIF
    42854302
    4286     IF ( large_scale_forcing .AND. ( .NOT. humidity ) )  THEN
     4303    IF ( large_scale_forcing  .AND.  (  .NOT. humidity ) )  THEN
    42874304       message_string = 'The usage of large scale forcing from external &'//   &
    42884305                        'file LSF_DATA requires humidity = .T..'
     
    42904307     ENDIF
    42914308
    4292     IF ( large_scale_forcing .AND. topography /= 'flat' )  THEN
     4309    IF ( large_scale_forcing  .AND. topography /= 'flat' )  THEN
    42934310       message_string = 'The usage of large scale forcing from external &'//   &
    42944311                        'file LSF_DATA is not implemented for non-flat topography'
     
    42964313    ENDIF
    42974314
    4298     IF ( large_scale_forcing .AND.  ocean  )  THEN
     4315    IF ( large_scale_forcing  .AND.  ocean  )  THEN
    42994316       message_string = 'The usage of large scale forcing from external &'//   &
    43004317                        'file LSF_DATA is not implemented for ocean runs'
     
    43204337!-- Check for valid setting of most_method
    43214338    IF ( TRIM( most_method ) /= 'circular'  .AND.                              &
    4322          TRIM( most_method ) /= 'newton'  .AND.                                &
     4339         TRIM( most_method ) /= 'newton'    .AND.                              &
    43234340         TRIM( most_method ) /= 'lookup' )  THEN
    4324        message_string = 'most_method = "' // TRIM( most_method ) //      &
     4341       message_string = 'most_method = "' // TRIM( most_method ) //            &
    43254342                        '" is unknown'
    43264343       CALL message( 'check_parameters', 'PA0416', 1, 2, 0, 6, 0 )
     
    43524369       IF ( dt_do == 0.0_wp )  THEN
    43534370          IF ( dt_fixed )  THEN
    4354              WRITE( message_string, '(A,F9.4,A)' )  'Output at every '  //  &
    4355                     'timestep is desired (' // dt_do_name // ' = 0.0).&'//  &
    4356                     'Setting the output interval to the fixed timestep '//  &
     4371             WRITE( message_string, '(A,F9.4,A)' )  'Output at every '  //     &
     4372                    'timestep is desired (' // dt_do_name // ' = 0.0).&'//     &
     4373                    'Setting the output interval to the fixed timestep '//     &
    43574374                    'dt = ', dt, 's.'
    43584375             CALL message( 'check_parameters', 'PA0060', 0, 0, 0, 6, 0 )
    43594376             dt_do = dt
    43604377          ELSE
    4361              message_string = dt_do_name // ' = 0.0 while using a ' //      &
    4362                               'variable timestep and parallel netCDF4 ' //  &
     4378             message_string = dt_do_name // ' = 0.0 while using a ' //         &
     4379                              'variable timestep and parallel netCDF4 ' //     &
    43634380                              'is not allowed.'
    43644381             CALL message( 'check_parameters', 'PA0081', 1, 2, 0, 6, 0 )
Note: See TracChangeset for help on using the changeset viewer.