Ignore:
Timestamp:
May 28, 2018 7:55:41 AM (6 years ago)
Author:
Giersch
Message:

Code adjusted according to coding standards, renamed namelists, error messages revised until PA0347, output CASE 108 disabled

File:
1 edited

Legend:

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

    r3035 r3045  
    2525! -----------------
    2626! $Id$
     27! Error messages revised
     28!
     29! 3035 2018-05-24 09:35:20Z schwenkel
    2730! Add option to initialize warm air bubble close to surface
    28 ! 
     31!
    2932! 3034 2018-05-24 08:41:20Z raasch
    3033! bugfix: check that initializing_actions has been set
    31 ! 
     34!
    3235! 2980 2018-04-17 15:19:27Z suehring
    3336! Further improvement for spinup checks.
     
    751754!
    752755!-- Check the coupling mode
    753 !> @todo Check if any queries for other coupling modes (e.g. precursor_ocean) are missing
    754     IF ( coupling_mode /= 'uncoupled'            .AND.  &
    755          coupling_mode /= 'vnested_crse'         .AND.  &
    756          coupling_mode /= 'vnested_fine'         .AND.  &
    757          coupling_mode /= 'atmosphere_to_ocean'  .AND.  &
     756    IF ( coupling_mode /= 'uncoupled'            .AND.                         &
     757         coupling_mode /= 'precursor_atmos'      .AND.                         &
     758         coupling_mode /= 'precursor_ocean'      .AND.                         &
     759         coupling_mode /= 'vnested_crse'         .AND.                         &
     760         coupling_mode /= 'vnested_fine'         .AND.                         &
     761         coupling_mode /= 'atmosphere_to_ocean'  .AND.                         &
    758762         coupling_mode /= 'ocean_to_atmosphere' )  THEN
    759763       message_string = 'illegal coupling mode: ' // TRIM( coupling_mode )
     
    764768!-- Check if humidity is set to TRUE in case of the atmospheric run (for coupled runs)
    765769    IF ( coupling_mode == 'atmosphere_to_ocean' .AND. .NOT. humidity) THEN
    766        message_string = ' Humidity has to be set to .T. in the _p3d file for ' //      &
    767                         'coupled runs between ocean and atmosphere.'
     770       message_string = ' Humidity has to be set to .T. in the _p3d file ' //  &
     771                        'for coupled runs between ocean and atmosphere.'
    768772       CALL message( 'check_parameters', 'PA0476', 1, 2, 0, 6, 0 )
    769773    ENDIF
     
    771775!
    772776!-- Check dt_coupling, restart_time, dt_restart, end_time, dx, dy, nx and ny
    773     IF ( coupling_mode /= 'uncoupled'  .AND.                                   &
    774          coupling_mode(1:8) /= 'vnested_' )  THEN
     777    IF ( coupling_mode /= 'uncoupled'       .AND.                              &
     778         coupling_mode(1:8) /= 'vnested_'   .AND.                              &
     779         coupling_mode /= 'precursor_atmos' .AND.                              &
     780         coupling_mode /= 'precursor_ocean' )  THEN
    775781
    776782       IF ( dt_coupling == 9999999.9_wp )  THEN
     
    914920             WRITE( message_string, * ) 'coupling mode "',                     &
    915921                   TRIM( coupling_mode ),                                      &
    916              '": nx+1 in ocean is not divisible by nx+1 in', &
     922             '": nx+1 in ocean is not divisible by nx+1 in',                   &
    917923             ' atmosphere without remainder'
    918924             CALL message( 'check_parameters', 'PA0339', 1, 2, 0, 6, 0 )
     
    10541060!
    10551061!-- Check approximation
    1056     IF ( TRIM( approximation ) /= 'boussinesq'   .AND.   &
     1062    IF ( TRIM( approximation ) /= 'boussinesq'   .AND.                         &
    10571063         TRIM( approximation ) /= 'anelastic' )  THEN
    1058        message_string = 'unknown approximation: approximation = "' //    &
     1064       message_string = 'unknown approximation: approximation = "' //          &
    10591065                        TRIM( approximation ) // '"'
    10601066       CALL message( 'check_parameters', 'PA0446', 1, 2, 0, 6, 0 )
     
    10631069!
    10641070!-- Check approximation requirements
    1065     IF ( TRIM( approximation ) == 'anelastic'   .AND.   &
     1071    IF ( TRIM( approximation ) == 'anelastic'   .AND.                          &
    10661072         TRIM( momentum_advec ) /= 'ws-scheme' )  THEN
    1067        message_string = 'Anelastic approximation requires: ' //                &
     1073       message_string = 'Anelastic approximation requires ' //                 &
    10681074                        'momentum_advec = "ws-scheme"'
    10691075       CALL message( 'check_parameters', 'PA0447', 1, 2, 0, 6, 0 )
    10701076    ENDIF
    1071     IF ( TRIM( approximation ) == 'anelastic'   .AND.   &
     1077    IF ( TRIM( approximation ) == 'anelastic'   .AND.                          &
    10721078         TRIM( psolver ) == 'multigrid' )  THEN
    1073        message_string = 'Anelastic approximation currently only supports: ' // &
    1074                         'psolver = "poisfft", ' // &
    1075                         'psolver = "sor" and ' // &
     1079       message_string = 'Anelastic approximation currently only supports ' // &
     1080                        'psolver = "poisfft", ' //                             &
     1081                        'psolver = "sor" and ' //                              &
    10761082                        'psolver = "multigrid_noopt"'
    10771083       CALL message( 'check_parameters', 'PA0448', 1, 2, 0, 6, 0 )
    10781084    ENDIF
    1079     IF ( TRIM( approximation ) == 'anelastic'   .AND.   &
     1085    IF ( TRIM( approximation ) == 'anelastic'   .AND.                          &
    10801086         conserve_volume_flow )  THEN
    1081        message_string = 'Anelastic approximation is not allowed with:' //      &
     1087       message_string = 'Anelastic approximation is not allowed with ' //      &
    10821088                        'conserve_volume_flow = .TRUE.'
    10831089       CALL message( 'check_parameters', 'PA0449', 1, 2, 0, 6, 0 )
     
    10861092!
    10871093!-- Check flux input mode
    1088     IF ( TRIM( flux_input_mode ) /= 'dynamic'    .AND.   &
    1089          TRIM( flux_input_mode ) /= 'kinematic'  .AND.   &
     1094    IF ( TRIM( flux_input_mode ) /= 'dynamic'    .AND.                         &
     1095         TRIM( flux_input_mode ) /= 'kinematic'  .AND.                         &
    10901096         TRIM( flux_input_mode ) /= 'approximation-specific' )  THEN
    10911097       message_string = 'unknown flux input mode: flux_input_mode = "' //      &
     
    11041110!
    11051111!-- Check flux output mode
    1106     IF ( TRIM( flux_output_mode ) /= 'dynamic'    .AND.   &
    1107          TRIM( flux_output_mode ) /= 'kinematic'  .AND.   &
     1112    IF ( TRIM( flux_output_mode ) /= 'dynamic'    .AND.                        &
     1113         TRIM( flux_output_mode ) /= 'kinematic'  .AND.                        &
    11081114         TRIM( flux_output_mode ) /= 'approximation-specific' )  THEN
    11091115       message_string = 'unknown flux output mode: flux_output_mode = "' //    &
     
    12481254!
    12491255!-- Advection schemes:
    1250     IF ( momentum_advec /= 'pw-scheme'  .AND.  momentum_advec /= 'ws-scheme' ) &
     1256    IF ( momentum_advec /= 'pw-scheme'  .AND.                                  & 
     1257         momentum_advec /= 'ws-scheme'  .AND.                                  &
     1258         momentum_advec /= 'up-scheme' )                                       &
    12511259    THEN
    12521260       message_string = 'unknown advection scheme: momentum_advec = "' //      &
     
    12591267    THEN
    12601268       message_string = 'momentum_advec or scalar_advec = "'                   &
    1261          // TRIM( momentum_advec ) // '" is not allowed with timestep_scheme = "' // &
    1262          TRIM( timestep_scheme ) // '"'
     1269         // TRIM( momentum_advec ) // '" is not allowed with ' //              &
     1270         'timestep_scheme = "' // TRIM( timestep_scheme ) // '"'
    12631271       CALL message( 'check_parameters', 'PA0023', 1, 2, 0, 6, 0 )
    12641272    ENDIF
    12651273    IF ( scalar_advec /= 'pw-scheme'  .AND.  scalar_advec /= 'ws-scheme' .AND. &
    1266          scalar_advec /= 'bc-scheme' )                                         &
     1274         scalar_advec /= 'bc-scheme' .AND. scalar_advec /= 'up-scheme' )       &
    12671275    THEN
    12681276       message_string = 'unknown advection scheme: scalar_advec = "' //        &
     
    12731281    THEN
    12741282       message_string = 'advection_scheme scalar_advec = "'                    &
    1275          // TRIM( scalar_advec ) // '" not implemented for & loop_optimization = "' // &
    1276          TRIM( loop_optimization ) // '"'
     1283         // TRIM( scalar_advec ) // '" not implemented for ' //                &
     1284         'loop_optimization = "' // TRIM( loop_optimization ) // '"'
    12771285       CALL message( 'check_parameters', 'PA0026', 1, 2, 0, 6, 0 )
    12781286    ENDIF
     
    13251333!-- Check for proper settings for microphysics
    13261334    IF ( cloud_physics  .AND.  cloud_droplets )  THEN
    1327        message_string = 'cloud_physics = .TRUE. is not allowed with ' //  &
     1335       message_string = 'cloud_physics = .TRUE. is not allowed with ' //       &
    13281336                        'cloud_droplets = .TRUE.'
    13291337       CALL message( 'check_parameters', 'PA0442', 1, 2, 0, 6, 0 )
     
    13551363    IF ( TRIM( initializing_actions ) == '' )  THEN
    13561364       message_string = 'no value specified for initializing_actions'
    1357        CALL message( 'check_parameters', 'PA0017', 1, 2, 0, 6, 0 )
     1365       CALL message( 'check_parameters', 'PA0149', 1, 2, 0, 6, 0 )
    13581366    ENDIF
    13591367
     
    13731381
    13741382             CASE DEFAULT
    1375                 message_string = 'initializing_actions = "' //                 &
     1383                message_string = 'initializing_action = "' //                  &
    13761384                                 TRIM( action ) // '" unknown or not allowed'
    13771385                CALL message( 'check_parameters', 'PA0030', 1, 2, 0, 6, 0 )
     
    14721480    IF ( large_scale_forcing  .OR.  nudging )  CALL lsf_nudging_check_parameters
    14731481
    1474 
    1475 
    1476     IF ( .NOT. ( loop_optimization == 'cache'  .OR.                            &
    1477                  loop_optimization == 'vector' )                               &
    1478          .AND.  cloud_physics  .AND.  microphysics_seifert )  THEN
    1479        message_string = 'cloud_scheme = seifert_beheng requires ' //           &
    1480                         'loop_optimization = "cache" or "vector"'
    1481        CALL message( 'check_parameters', 'PA0362', 1, 2, 0, 6, 0 )
    1482     ENDIF
    1483 
    14841482!
    14851483!-- In case of no model continuation run, check initialising parameters and
     
    18251823!-- Check time step and cfl_factor
    18261824    IF ( dt /= -1.0_wp )  THEN
    1827        IF ( dt <= 0.0_wp  .AND.  dt /= -1.0_wp )  THEN
     1825       IF ( dt <= 0.0_wp )  THEN
    18281826          WRITE( message_string, * ) 'dt = ', dt , ' <= 0.0'
    18291827          CALL message( 'check_parameters', 'PA0044', 1, 2, 0, 6, 0 )
     
    18441842       ELSE
    18451843          WRITE( message_string, * ) 'cfl_factor = ', cfl_factor,              &
    1846                  ' out of range & 0.0 < cfl_factor <= 1.0 is required'
     1844                 ' out of range 0.0 < cfl_factor <= 1.0 is required'
    18471845          CALL message( 'check_parameters', 'PA0045', 1, 2, 0, 6, 0 )
    18481846       ENDIF
     
    18871885          CALL message( 'check_parameters', 'PA0047', 1, 2, 0, 6, 0 )
    18881886       ELSE
    1889           message_string = 'variable translation speed used for galilei-' //   &
    1890              'transformation, which may cause & instabilities in stably ' //   &
     1887          message_string = 'variable translation speed used for Galilei-' //   &
     1888             'transformation, which may cause instabilities in stably ' //     &
    18911889             'stratified regions'
    18921890          CALL message( 'check_parameters', 'PA0048', 0, 1, 0, 6, 0 )
     
    20642062         surface_heatflux /= 0.0_wp )  THEN
    20652063       message_string = 'boundary_condition: bc_pt_b = "' // TRIM( bc_pt_b ) //&
    2066                         '& is not allowed with constant_heatflux = .TRUE.'
     2064                        'is not allowed with constant_heatflux = .TRUE.'
    20672065       CALL message( 'check_parameters', 'PA0065', 1, 2, 0, 6, 0 )
    20682066    ENDIF
     
    21542152    IF ( passive_scalar )  THEN
    21552153
    2156        IF ( ANY( wall_scalarflux /= 0.0_wp )  .AND.                        &
     2154       IF ( ANY( wall_scalarflux /= 0.0_wp )  .AND.                            &
    21572155            surface_scalarflux == 9999999.9_wp )  THEN
    2158           message_string = 'wall_scalarflux additionally requires ' //     &
     2156          message_string = 'wall_scalarflux additionally requires ' //         &
    21592157                           'setting of surface_scalarflux'
    21602158          CALL message( 'check_parameters', 'PA0445', 1, 2, 0, 6, 0 )
     
    23262324    IF ( averaging_interval > dt_data_output_av )  THEN
    23272325       WRITE( message_string, * )  'averaging_interval = ',                    &
    2328              averaging_interval, ' must be <= dt_data_output = ', dt_data_output
     2326             averaging_interval, ' must be <= dt_data_output_av = ',           &
     2327             dt_data_output_av
    23292328       CALL message( 'check_parameters', 'PA0085', 1, 2, 0, 6, 0 )
    23302329    ENDIF
     
    25492548          CASE ( 'sa', '#sa' )
    25502549             IF ( .NOT. ocean )  THEN
    2551                 message_string = 'data_output_pr = ' // &
     2550                message_string = 'data_output_pr = ' //                        &
    25522551                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    25532552                                 'lemented for ocean = .FALSE.'
     
    26222621          CASE ( 'q', '#q' )
    26232622             IF ( .NOT. humidity )  THEN
    2624                 message_string = 'data_output_pr = ' // &
     2623                message_string = 'data_output_pr = ' //                        &
    26252624                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    26262625                                 'lemented for humidity = .FALSE.'
     
    28072806                message_string = 'data_output_pr = ' //                        &
    28082807                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    2809                                  'lemented for cloud_physics = .FALSE. an&' // &
     2808                                 'lemented for cloud_physics = .FALSE. an' // &
    28102809                                 'd humidity = .FALSE.'
    28112810                CALL message( 'check_parameters', 'PA0095', 1, 2, 0, 6, 0 )
     
    28252824                message_string = 'data_output_pr = ' //                        &
    28262825                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    2827                                  'lemented for cloud_physics = .FALSE. an&' // &
     2826                                 'lemented for cloud_physics = .FALSE. an' // &
    28282827                                 'd humidity = .FALSE.'
    28292828                CALL message( 'check_parameters', 'PA0095', 1, 2, 0, 6, 0 )
     
    28422841                message_string = 'data_output_pr = ' //                        &
    28432842                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    2844                                  'lemented for cloud_physics = .FALSE. an&' // &
     2843                                 'lemented for cloud_physics = .FALSE. an' // &
    28452844                                 'd humidity = .FALSE.'
    28462845                CALL message( 'check_parameters', 'PA0095', 1, 2, 0, 6, 0 )
     
    28512850                message_string = 'data_output_pr = ' //                        &
    28522851                                 TRIM( data_output_pr(i) ) // ' is not imp' // &
    2853                                  'lemented for cloud_physics = .FALSE. or' // &
    2854                                  '&cloud_droplets = .FALSE.'
     2852                                 'lemented for cloud_physics = .FALSE. and' // &
     2853                                 'cloud_droplets = .FALSE.'
    28552854                CALL message( 'check_parameters', 'PA0096', 1, 2, 0, 6, 0 )
    28562855             ELSE
     
    32493248             ELSEIF ( .NOT.  microphysics_morrison )  THEN
    32503249                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
    3251                          'res = microphysics morrison '
     3250                         'res = morrison '
    32523251                CALL message( 'check_parameters', 'PA0359', 1, 2, 0, 6, 0 )
    32533252             ENDIF
     
    32693268             IF (  .NOT.  particle_advection )  THEN
    32703269                message_string = 'output of "' // TRIM( var ) // '" requir' // &
    3271                    'es a "particle_parameters"-NAMELIST in the parameter file (PARIN)'
     3270                   'es a "particle_parameters"-NAMELIST in the parameter ' //  &
     3271                   'file (PARIN)'
    32723272                CALL message( 'check_parameters', 'PA0104', 1, 2, 0, 6, 0 )
    32733273             ENDIF
     
    32813281                CALL message( 'check_parameters', 'PA0108', 1, 2, 0, 6, 0 )
    32823282             ELSEIF ( microphysics_sat_adjust )  THEN
    3283                 message_string = 'output of "' // TRIM( var ) // '" is ' //  &
     3283                message_string = 'output of "' // TRIM( var ) // '" is ' //    &
    32843284                         'not available for cloud_scheme = saturation_adjust'
    32853285                CALL message( 'check_parameters', 'PA0423', 1, 2, 0, 6, 0 )
     
    33783378             IF ( k == 0  .OR.  data_output(i)(ilen-2:ilen) /= '_xy' )  THEN
    33793379                message_string = 'illegal value for data_output: "' //         &
    3380                                  TRIM( var ) // '" & only 2d-horizontal ' //   &
     3380                                 TRIM( var ) // '" only 2d-horizontal ' //     &
    33813381                                 'cross sections are allowed for this value'
    33823382                CALL message( 'check_parameters', 'PA0111', 1, 2, 0, 6, 0 )
     
    34113411             ENDIF
    34123412
    3413           IF ( TRIM( var ) == 'ghf*'  .AND.  .NOT.  land_surface )  THEN
    3414              message_string = 'output of "' // TRIM( var ) // '" requi' //     &
    3415                               'res land_surface = .TRUE.'
    3416              CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
    3417           ENDIF
     3413             IF ( TRIM( var ) == 'ghf*'  .AND.  .NOT.  land_surface )  THEN
     3414                message_string = 'output of "' // TRIM( var ) // '" requi' //  &
     3415                                 'res land_surface = .TRUE.'
     3416                CALL message( 'check_parameters', 'PA0404', 1, 2, 0, 6, 0 )
     3417             ENDIF
    34183418
    34193419             IF ( ( TRIM( var ) == 'r_a*' .OR.  TRIM( var ) == 'ghf*' )        &
     
    35583558       WRITE( message_string, * )  'output of averaged quantity "',            &
    35593559                                   TRIM( doav(1) ), '_av" requires to set a ', &
    3560                                    'non-zero & averaging interval'
     3560                                   'non-zero averaging interval'
    35613561       CALL message( 'check_parameters', 'PA0323', 1, 2, 0, 6, 0 )
    35623562    ENDIF
     
    35793579    section(:,2) = section_xz
    35803580    section(:,3) = section_yz
    3581 
    3582 !
    3583 !-- Upper plot limit for 2D vertical sections
    3584     IF ( z_max_do2d == -1.0_wp )  z_max_do2d = zu(nzt)
    3585     IF ( z_max_do2d < zu(nzb+1)  .OR.  z_max_do2d > zu(nzt) )  THEN
    3586        WRITE( message_string, * )  'z_max_do2d = ', z_max_do2d,                &
    3587                     ' must be >= ', zu(nzb+1), '(zu(nzb+1)) and <= ', zu(nzt), &
    3588                     ' (zu(nzt))'
    3589        CALL message( 'check_parameters', 'PA0116', 1, 2, 0, 6, 0 )
    3590     ENDIF
    35913581
    35923582!
     
    36473637                           '5 (parallel netCDF 4) and ' //                     &
    36483638                           '6 (parallel netCDF 4 Classic model) '//            &
    3649                            '&are currently not supported (not yet tested) ' // &
    3650                            'for masked data.&Using respective non-parallel' // &
     3639                           ' are currently not supported (not yet tested) ' // &
     3640                           'for masked data. Using respective non-parallel' // &
    36513641                           ' output for masked data.'
    36523642          CALL message( 'check_parameters', 'PA0383', 0, 0, 0, 6, 0 )
     
    36633653#else
    36643654       message_string = 'netCDF: netCDF4 format requested but no ' //          &
    3665                         'cpp-directive __netcdf4 given & switch '  //          &
     3655                        'cpp-directive __netcdf4 given  switch '  //           &
    36663656                        'back to 64-bit offset format'
    36673657       CALL message( 'check_parameters', 'PA0171', 0, 1, 0, 6, 0 )
     
    36743664#else
    36753665       message_string = 'netCDF: netCDF4 parallel output requested but no ' // &
    3676                         'cpp-directive __netcdf4_parallel given & switch '  // &
     3666                        'cpp-directive __netcdf4_parallel given, switch '   // &
    36773667                        'back to netCDF4 non-parallel output'
    36783668       CALL message( 'check_parameters', 'PA0099', 0, 1, 0, 6, 0 )
     
    38653855    IF ( disturbance_level_ind_t < disturbance_level_ind_b )  THEN
    38663856       WRITE( message_string, * )  'disturbance_level_ind_t = ',               &
    3867                 disturbance_level_ind_t, ' must be >= disturbance_level_ind_b = ', &
    3868                 disturbance_level_ind_b
     3857                disturbance_level_ind_t, ' must be >= ',                      &
     3858                'disturbance_level_ind_b = ', disturbance_level_ind_b
    38693859       CALL message( 'check_parameters', 'PA0130', 1, 2, 0, 6, 0 )
    38703860    ENDIF
     
    39843974    IF ( turbulent_inflow )  THEN
    39853975       IF ( recycling_width <= dx  .OR.  recycling_width >= nx * dx )  THEN
    3986           WRITE( message_string, * )  'illegal value for recycling_width:', &
    3987                                       ' ', recycling_width
     3976          WRITE( message_string, * )  'illegal value for recycling_width: ',  &
     3977                                      recycling_width
    39883978          CALL message( 'check_parameters', 'PA0134', 1, 2, 0, 6, 0 )
    39893979       ENDIF
     
    40874077       IF ( dp_level_b < zu(nzb)  .OR.  dp_level_b > zu(nzt) )  THEN
    40884078          WRITE( message_string, * )  'dp_level_b = ', dp_level_b, ' is out ', &
    4089                ' of range'
     4079               ' of range [zu(nzb), zu(nzt)]'
    40904080          CALL message( 'check_parameters', 'PA0151', 1, 2, 0, 6, 0 )
    40914081       ENDIF
    40924082       IF ( .NOT. ANY( dpdxy /= 0.0_wp ) )  THEN
    40934083          WRITE( message_string, * )  'dp_external is .TRUE. but dpdxy is ze', &
    4094                'ro, i.e. the external pressure gradient & will not be applied'
     4084               'ro, i.e. the external pressure gradient will not be applied'
    40954085          CALL message( 'check_parameters', 'PA0152', 0, 1, 0, 6, 0 )
    40964086       ENDIF
     
    41474137       IF ( particle_dvrpsize /= 'absw' )  THEN
    41484138          message_string = 'illegal value for parameter particle_dvrpsize:' // &
    4149                            ' ' // TRIM( particle_color)
     4139                           ' ' // TRIM( particle_dvrpsize)
    41504140          CALL message( 'check_parameters', 'PA0314', 1, 2, 0, 6, 0 )
    41514141       ELSE
     
    41834173!-- Check roughness length, which has to be smaller than dz/2
    41844174    IF ( ( constant_flux_layer .OR.  &
    4185            INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 ) &
     4175           INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )       &
    41864176         .AND. roughness_length >= 0.5 * dz )  THEN
    41874177       message_string = 'roughness_length must be smaller than dz/2'
     
    42374227          IF ( dt_fixed )  THEN
    42384228             WRITE( message_string, '(A,F9.4,A)' )  'Output at every '  //     &
    4239                     'timestep is wanted (' // dt_do_name // ' = 0.0).&'//      &
    4240                     'Setting the output interval to the fixed timestep '//     &
    4241                     'dt = ', dt, 's.'
     4229                    'timestep is wanted (' // dt_do_name // ' = 0.0). '//      &
     4230                    'The output interval is set to the fixed timestep dt '//   &
     4231                    '= ', dt, 's.'
    42424232             CALL message( 'check_parameters', 'PA0060', 0, 0, 0, 6, 0 )
    42434233             dt_do = dt
Note: See TracChangeset for help on using the changeset viewer.