Ignore:
Timestamp:
Jan 14, 2021 10:42:28 AM (3 years ago)
Author:
raasch
Message:

reading of namelist file and actions in case of namelist errors revised so that statement labels and goto statements are not required any more, deprecated namelists removed

File:
1 edited

Legend:

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

    r4828 r4842  
    2424! -----------------
    2525! $Id$
     26! reading of namelist file and actions in case of namelist errors revised so that statement labels
     27! and goto statements are not required any more,
     28! deprecated namelists removed
     29!
     30! 4828 2021-01-05 11:21:41Z Giersch
    2631! file re-formatted to follow the PALM coding standard
    2732!
     
    162167    IMPLICIT NONE
    163168
    164     CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
     169    CHARACTER(LEN=100) ::  line  !< dummy string that contains the current line of the parameter
     170                                 !< file
    165171
    166172    INTEGER(iwp) ::  global_id      !< process id with respect to MPI_COMM_WORLD
    167173    INTEGER(iwp) ::  global_procs   !< # of procs with respect to MPI_COMM_WORLD
    168174    INTEGER(iwp) ::  i              !<
    169     INTEGER(iwp) ::  ioerr          !< error flag for open/read/write
    170 
    171     NAMELIST /inipar/  alpha_surface,                                                              &
    172                        approximation,                                                              &
    173                        bc_e_b,                                                                     &
    174                        bc_lr,                                                                      &
    175                        bc_ns,                                                                      &
    176                        bc_p_b,                                                                     &
    177                        bc_p_t,                                                                     &
    178                        bc_pt_b,                                                                    &
    179                        bc_pt_t,                                                                    &
    180                        bc_q_b,                                                                     &
    181                        bc_q_t,                                                                     &
    182                        bc_s_b,                                                                     &
    183                        bc_s_t,                                                                     &
    184                        bc_uv_b,                                                                    &
    185                        bc_uv_t,                                                                    &
    186                        building_height,                                                            &
    187                        building_length_x,                                                          &
    188                        building_length_y,                                                          &
    189                        building_wall_left,                                                         &
    190                        building_wall_south,                                                        &
    191                        calc_soil_moisture_during_spinup,                                           &
    192                        call_psolver_at_all_substeps,                                               &
    193                        canyon_height,                                                              &
    194                        canyon_wall_left,                                                           &
    195                        canyon_wall_south,                                                          &
    196                        canyon_width_x,                                                             &
    197                        canyon_width_y,                                                             &
    198                        cfl_factor,                                                                 &
    199                        check_realistic_q,                                                          &
    200                        cloud_droplets,                                                             &
    201                        collective_wait,                                                            &
    202                        complex_terrain,                                                            &
    203                        conserve_volume_flow,                                                       &
    204                        conserve_volume_flow_mode,                                                  &
    205                        constant_flux_layer,                                                        &
    206                        coupling_start_time,                                                        &
    207                        cycle_mg,                                                                   &
    208                        damp_level_1d,                                                              &
    209                        data_output_during_spinup,                                                  &
    210                        dissipation_1d,                                                             &
    211                        dp_external,                                                                &
    212                        dp_level_b,                                                                 &
    213                        dp_smooth,                                                                  &
    214                        dpdxy,                                                                      &
    215                        dt,                                                                         &
    216                        dt_pr_1d,                                                                   &
    217                        dt_run_control_1d,                                                          &
    218                        dt_spinup,                                                                  &
    219                        dx,                                                                         &
    220                        dy,                                                                         &
    221                        dz,                                                                         &
    222                        dz_max,                                                                     &
    223                        dz_stretch_factor,                                                          &
    224                        dz_stretch_level,                                                           &
    225                        dz_stretch_level_end,                                                       &
    226                        dz_stretch_level_start,                                                     &
    227                        e_init,                                                                     &
    228                        e_min,                                                                      &
    229                        end_time_1d,                                                                &
    230                        ensemble_member_nr,                                                         &
    231                        fft_method,                                                                 &
    232                        flux_input_mode,                                                            &
    233                        flux_output_mode,                                                           &
    234                        galilei_transformation,                                                     &
    235                        humidity,                                                                   &
    236                        inflow_damping_height,                                                      &
    237                        inflow_damping_width,                                                       &
    238                        inflow_disturbance_begin,                                                   &
    239                        inflow_disturbance_end,                                                     &
    240                        initializing_actions,                                                       &
    241                        km_constant,                                                                &
    242                        large_scale_forcing,                                                        &
    243                        large_scale_subsidence,                                                     &
    244                        latitude,                                                                   &
    245                        longitude,                                                                  &
    246                        loop_optimization,                                                          &
    247                        lsf_exception,                                                              &
    248                        masking_method,                                                             &
    249                        mg_cycles,                                                                  &
    250                        mg_switch_to_pe0_level,                                                     &
    251                        mixing_length_1d,                                                           &
    252                        momentum_advec,                                                             &
    253                        monotonic_limiter_z,                                                        &
    254                        netcdf_precision,                                                           &
    255                        neutral,                                                                    &
    256                        ngsrb,                                                                      &
    257                        nsor,                                                                       &
    258                        nsor_ini,                                                                   &
    259                        nudging,                                                                    &
    260                        nx,                                                                         &
    261                        ny,                                                                         &
    262                        nz,                                                                         &
    263                        ocean_mode,                                                                 &
    264                        omega,                                                                      &
    265                        omega_sor,                                                                  &
    266                        origin_date_time,                                                           &
    267                        outflow_source_plane,                                                       &
    268                        passive_scalar,                                                             &
    269                        prandtl_number,                                                             &
    270                        psolver,                                                                    &
    271                        pt_damping_factor,                                                          &
    272                        pt_damping_width,                                                           &
    273                        pt_reference,                                                               &
    274                        pt_surface,                                                                 &
    275                        pt_surface_heating_rate,                                                    &
    276                        pt_surface_initial_change,                                                  &
    277                        pt_vertical_gradient,                                                       &
    278                        pt_vertical_gradient_level,                                                 &
    279                        q_surface,                                                                  &
    280                        q_surface_initial_change,                                                   &
    281                        q_vertical_gradient,                                                        &
    282                        q_vertical_gradient_level,                                                  &
    283                        random_generator,                                                           &
    284                        random_heatflux,                                                            &
    285                        rans_const_c,                                                               &
    286                        rans_const_sigma,                                                           &
    287                        rayleigh_damping_factor,                                                    &
    288                        rayleigh_damping_height,                                                    &
    289                        recycling_method_for_thermodynamic_quantities,                              &
    290                        recycling_width,                                                            &
    291                        reference_state,                                                            &
    292                        residual_limit,                                                             &
    293                        rotation_angle,                                                             &
    294                        roughness_length,                                                           &
    295                        scalar_advec,                                                               &
    296                        scalar_rayleigh_damping,                                                    &
    297                        spinup_time,                                                                &
    298                        spinup_pt_amplitude,                                                        &
    299                        spinup_pt_mean,                                                             &
    300                        statistic_regions,                                                          &
    301                        subs_vertical_gradient,                                                     &
    302                        subs_vertical_gradient_level,                                               &
    303                        surface_heatflux,                                                           &
    304                        surface_pressure,                                                           &
    305                        surface_scalarflux,                                                         &
    306                        surface_waterflux,                                                          &
    307                        s_surface,                                                                  &
    308                        s_surface_initial_change,                                                   &
    309                        s_vertical_gradient,                                                        &
    310                        s_vertical_gradient_level,                                                  &
    311                        timestep_scheme,                                                            &
    312                        topography,                                                                 &
    313                        topography_grid_convention,                                                 &
    314                        top_heatflux,                                                               &
    315                        top_momentumflux_u,                                                         &
    316                        top_momentumflux_v,                                                         &
    317                        top_scalarflux,                                                             &
    318                        transpose_compute_overlap,                                                  &
    319                        tunnel_height,                                                              &
    320                        tunnel_length,                                                              &
    321                        tunnel_wall_depth,                                                          &
    322                        tunnel_width_x,                                                             &
    323                        tunnel_width_y,                                                             &
    324                        turbulence_closure,                                                         &
    325                        turbulent_inflow,                                                           &
    326                        turbulent_outflow,                                                          &
    327                        u_bulk,                                                                     &
    328                        u_profile,                                                                  &
    329                        ug_surface,                                                                 &
    330                        ug_vertical_gradient,                                                       &
    331                        ug_vertical_gradient_level,                                                 &
    332                        use_cmax,                                                                   &
    333                        use_fixed_date,                                                             &
    334                        use_fixed_time,                                                             &
    335                        use_free_convection_scaling,                                                &
    336                        use_ug_for_galilei_tr,                                                      &
    337                        use_subsidence_tendencies,                                                  &
    338                        use_surface_fluxes,                                                         &
    339                        use_top_fluxes,                                                             &
    340                        use_upstream_for_tke,                                                       &
    341                        uv_heights,                                                                 &
    342                        v_bulk,                                                                     &
    343                        v_profile,                                                                  &
    344                        vdi_checks,                                                                 &
    345                        vg_surface,                                                                 &
    346                        vg_vertical_gradient,                                                       &
    347                        vg_vertical_gradient_level,                                                 &
    348                        wall_adjustment,                                                            &
    349                        wall_heatflux,                                                              &
    350                        wall_humidityflux,                                                          &
    351                        wall_scalarflux,                                                            &
    352                        y_shift,                                                                    &
    353                        zeta_max,                                                                   &
    354                        zeta_min,                                                                   &
    355                        z0h_factor
     175    INTEGER(iwp) ::  io_status      !< status after reading the namelist files
     176
    356177
    357178    NAMELIST /initialization_parameters/  alpha_surface,                                           &
     
    541362                                          z0h_factor
    542363
    543     NAMELIST /d3par/  averaging_interval,                                                          &
    544                       averaging_interval_pr,                                                       &
    545                       cpu_log_barrierwait,                                                         &
    546                       create_disturbances,                                                         &
    547                       cross_profiles,                                                              &
    548                       data_output,                                                                 &
    549                       data_output_2d_on_each_pe,                                                   &
    550                       data_output_masks,                                                           &
    551                       data_output_pr,                                                              &
    552                       debug_output,                                                                &
    553                       debug_output_timestep,                                                       &
    554                       disturbance_amplitude,                                                       &
    555                       disturbance_energy_limit,                                                    &
    556                       disturbance_level_b,                                                         &
    557                       disturbance_level_t,                                                         &
    558                       do2d_at_begin,                                                               &
    559                       do3d_at_begin,                                                               &
    560                       dt,                                                                          &
    561                       dt_averaging_input,                                                          &
    562                       dt_averaging_input_pr,                                                       &
    563                       dt_coupling,                                                                 &
    564                       dt_data_output,                                                              &
    565                       dt_data_output_av,                                                           &
    566                       dt_disturb,                                                                  &
    567                       dt_domask,                                                                   &
    568                       dt_dopr,                                                                     &
    569                       dt_dopr_listing,                                                             &
    570                       dt_dots,                                                                     &
    571                       dt_do2d_xy,                                                                  &
    572                       dt_do2d_xz,                                                                  &
    573                       dt_do2d_yz,                                                                  &
    574                       dt_do3d,                                                                     &
    575                       dt_max,                                                                      &
    576                       dt_restart,                                                                  &
    577                       dt_run_control,                                                              &
    578                       end_time,                                                                    &
    579                       force_print_header,                                                          &
    580                       mask_k_over_surface,                                                         &
    581                       mask_scale_x,                                                                &
    582                       mask_scale_y,                                                                &
    583                       mask_scale_z,                                                                &
    584                       mask_x,                                                                      &
    585                       mask_y,                                                                      &
    586                       mask_z,                                                                      &
    587                       mask_x_loop,                                                                 &
    588                       mask_y_loop,                                                                 &
    589                       mask_z_loop,                                                                 &
    590                       netcdf_data_format,                                                          &
    591                       netcdf_deflate,                                                              &
    592                       normalizing_region,                                                          &
    593                       npex,                                                                        &
    594                       npey,                                                                        &
    595                       nz_do3d,                                                                     &
    596                       profile_columns,                                                             &
    597                       profile_rows,                                                                &
    598                       restart_time,                                                                &
    599                       section_xy,                                                                  &
    600                       section_xz,                                                                  &
    601                       section_yz,                                                                  &
    602                       skip_time_data_output,                                                       &
    603                       skip_time_data_output_av,                                                    &
    604                       skip_time_dopr,                                                              &
    605                       skip_time_do2d_xy,                                                           &
    606                       skip_time_do2d_xz,                                                           &
    607                       skip_time_do2d_yz,                                                           &
    608                       skip_time_do3d,                                                              &
    609                       skip_time_domask,                                                            &
    610                       synchronous_exchange,                                                        &
    611                       termination_time_needed
    612 
    613364    NAMELIST /runtime_parameters/  averaging_interval,                                             &
    614365                                   averaging_interval_pr,                                          &
     
    699450    CALL location_message( 'reading environment parameters from ENVPAR', 'start' )
    700451
    701     OPEN( 90, FILE='ENVPAR', STATUS='OLD', FORM='FORMATTED', IOSTAT=ioerr )
    702 
    703     IF ( ioerr /= 0 )  THEN
     452    OPEN( 90, FILE='ENVPAR', STATUS='OLD', FORM='FORMATTED', IOSTAT=io_status )
     453
     454    IF ( io_status /= 0 )  THEN
    704455       message_string = 'local file ENVPAR not found' //                                           &
    705456                        '&some variables for steering may not be properly set'
    706457       CALL message( 'parin', 'PA0276', 0, 1, 0, 6, 0 )
    707458    ELSE
    708        READ( 90, envpar, IOSTAT=ioerr )
    709        IF ( ioerr < 0 )  THEN
     459       READ( 90, envpar, IOSTAT=io_status )
     460       IF ( io_status < 0 )  THEN
    710461          message_string = 'no envpar-NAMELIST found in local file '  //                           &
    711                            'ENVPAR& or some variables for steering may '  //   &
    712                            'not be properly set'
     462                           'ENVPAR& or some variables for steering may not be properly set'
    713463          CALL message( 'parin', 'PA0278', 0, 1, 0, 6, 0 )
    714        ELSEIF ( ioerr > 0 )  THEN
     464       ELSEIF ( io_status > 0 )  THEN
    715465          message_string = 'errors in local file ENVPAR' //                                        &
    716466                           '&some variables for steering may not be properly set'
     
    730480!
    731481!-- Read the control parameters for initialization.
    732 !-- The namelist "inipar" must be provided in the NAMELIST-file.
    733     READ ( 11, initialization_parameters, ERR=10, END=11 )
    734     GOTO 14
    735 
    736  10 BACKSPACE( 11 )
    737     READ( 11 , '(A)') line
    738     CALL parin_fail_message( 'initialization_parameters', line )
    739 
    740  11 REWIND ( 11 )
    741     READ( 11, inipar, ERR=12, END=13 )
    742 
    743     message_string = 'namelist inipar is deprecated and will be ' //                               &
    744                      'removed in near future. & Please use namelist ' //                           &
    745                      'initialization_parameters instead'
    746     CALL message( 'parin', 'PA0017', 0, 1, 0, 6, 0 )
    747 
    748     GOTO 14
    749 
    750  12 BACKSPACE( 11 )
    751     READ( 11 , '(A)') line
    752     CALL parin_fail_message( 'inipar', line )
    753 
    754  13 message_string = 'no initialization_parameters-namelist found'
    755     CALL message( 'parin', 'PA0272', 1, 2, 0, 6, 0 )
    756 
     482!-- The namelist "initialisation_parameters" must be provided in the NAMELIST-file.
     483    READ( 11, initialization_parameters, IOSTAT=io_status )
     484
     485!
     486!-- Action depending on the READ status
     487    IF ( io_status > 0 )  THEN
     488!
     489!--    initialisation_parameters namelist was found but countained errors. Print an error message
     490!-     including the line that caused the problem.
     491       BACKSPACE( 11 )
     492       READ( 11 , '(A)' ) line
     493       CALL parin_fail_message( 'initialization_parameters', line )
     494
     495    ELSEIF ( io_status < 0 )  THEN
     496!
     497!--    initialisation_parametes namelist was not found. Return a message.
     498       message_string = 'no initialization_parameters-namelist found'
     499       CALL message( 'parin', 'PA0272', 1, 2, 0, 6, 0 )
     500
     501    ENDIF
    757502!
    758503!-- Try to read runtime parameters given by the user for this run (namelist "runtime_parameters").
    759504!-- The namelist "runtime_parmeters" can be omitted. In that case default values are used for the
    760505!-- parameters.
    761  14 line = ' '
    762 
    763506    REWIND( 11 )
    764     line = ' '
    765     DO WHILE ( INDEX( line, '&runtime_parameters' ) == 0 )
    766        READ( 11, '(A)', END=16 )  line
    767     ENDDO
    768     BACKSPACE( 11 )
    769 
    770 !
    771 !-- Read namelist
    772     READ( 11, runtime_parameters, ERR = 15 )
    773     GOTO 18
    774 
    775  15 BACKSPACE( 11 )
    776     READ( 11 , '(A)') line
    777     CALL parin_fail_message( 'runtime_parameters', line )
    778 
    779  16 REWIND( 11 )
    780     line = ' '
    781     DO WHILE ( INDEX( line, '&d3par' ) == 0 )
    782        READ( 11, '(A)', END=18 )  line
    783     ENDDO
    784     BACKSPACE ( 11 )
    785 
    786 !
    787 !-- Read namelist
    788     READ( 11, d3par, ERR = 17, END = 18 )
    789 
    790     message_string = 'namelist d3par is deprecated and will be ' //                                &
    791                      'removed in near future. &Please use namelist ' //                            &
    792                      'runtime_parameters instead'
    793     CALL message( 'parin', 'PA0487', 0, 1, 0, 6, 0 )
    794 
    795     GOTO 18
    796 
    797  17 BACKSPACE( 11 )
    798     READ( 11 , '(A)') line
    799     CALL parin_fail_message( 'd3par', line )
    800 
    801  18 CONTINUE
     507    READ( 11, runtime_parameters, IOSTAT=io_status )
     508
     509    IF ( io_status > 0 )  THEN
     510!
     511!--    Namelist runtime_parameters was found but contained errors. Print an error message including
     512!--    the line that caused the problem.
     513       BACKSPACE( 11 )
     514       READ( 11 , '(A)') line
     515       CALL parin_fail_message( 'runtime_parameters', line )
     516
     517    ENDIF
    802518
    803519!
Note: See TracChangeset for help on using the changeset viewer.