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/spectra_mod.f90

    r4828 r4842  
    2525! -----------------
    2626! $Id$
     27! reading of namelist file and actions in case of namelist errors revised so that statement labels
     28! and goto statements are not required any more,
     29! deprecated namelist removed
     30!
     31! 4828 2021-01-05 11:21:41Z Giersch
    2732! support for MPI Fortran77 interface (mpif.h) removed
    2833!
     
    146151
    147152    USE control_parameters,                                                                        &
    148         ONLY:  dt_data_output,                                                                     &
    149                message_string
     153        ONLY:  dt_data_output
    150154
    151155    IMPLICIT NONE
    152156
    153     CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
    154 
    155     NAMELIST /spectra_par/  averaging_interval_sp,                                                 &
    156                             comp_spectra_level,                                                    &
    157                             data_output_sp,                                                        &
    158                             dt_dosp,                                                               &
    159                             skip_time_dosp,                                                        &
    160                             spectra_direction
     157    CHARACTER(LEN=100) ::  line  !< dummy string that contains the current line of the parameter file
     158
     159    INTEGER(iwp) ::  io_status   !< status after reading the namelist file
     160
    161161
    162162    NAMELIST /spectra_parameters/                                                                  &
     
    168168                            spectra_direction
    169169!
    170 !-- Position the namelist-file at the beginning (it was already opened in parin), search for the
    171 !-- namelist-group of the package and position the file at this line.
    172     line = ' '
    173 
    174 !
    175 !-- Try to find the spectra package
    176     REWIND ( 11 )
    177     line = ' '
    178     DO WHILE ( INDEX( line, '&spectra_parameters' ) == 0 )
    179        READ ( 11, '(A)', END=12 )  line
    180     ENDDO
    181     BACKSPACE ( 11 )
    182 
    183 !
    184 !-- Read namelist
    185     READ ( 11, spectra_parameters, ERR = 10 )
    186 
    187 !
    188 !-- Default setting of dt_dosp here (instead of check_parameters), because its current value is
    189 !-- needed in init_pegrid
    190     IF ( dt_dosp == 9999999.9_wp )  dt_dosp = dt_data_output
    191 
    192 !
    193 !-- Set general switch that spectra shall be calculated
    194     calculate_spectra = .TRUE.
    195 
    196     GOTO 14
    197 
    198  10 BACKSPACE( 11 )
    199     READ( 11 , '(A)') line
    200     CALL parin_fail_message( 'spectra_parameters', line )
    201 !
    202 !-- Try to find the old namelist
    203  12 REWIND ( 11 )
    204     line = ' '
    205     DO WHILE ( INDEX( line, '&spectra_par' ) == 0 )
    206        READ ( 11, '(A)', END=14 )  line
    207     ENDDO
    208     BACKSPACE ( 11 )
    209 
    210 !
    211 !-- Read namelist
    212     READ ( 11, spectra_par, ERR = 13, END = 14 )
    213 
    214 
    215     message_string = 'namelist spectra_par is deprecated and will be removed in near future.' //   &
    216                      ' Please use namelist spectra_parameters instead'
    217     CALL message( 'spectra_parin', 'PA0487', 0, 1, 0, 6, 0 )
    218 !
    219 !-- Default setting of dt_dosp here (instead of check_parameters), because its current value is
    220 !-- needed in init_pegrid
    221     IF ( dt_dosp == 9999999.9_wp )  dt_dosp = dt_data_output
    222 
    223 !
    224 !-- Set general switch that spectra shall be calculated
    225     calculate_spectra = .TRUE.
    226 
    227     GOTO 14
    228 
    229  13 BACKSPACE( 11 )
    230     READ( 11 , '(A)') line
    231     CALL parin_fail_message( 'spectra_par', line )
    232 
    233 
    234  14 CONTINUE
     170!-- Position the namelist-file at the beginning (it was already opened in parin), and try to read
     171!-- the namelist.
     172    REWIND( 11 )
     173    READ( 11, spectra_parameters, IOSTAT=io_status )
     174
     175!
     176!-- Action depending on the READ status
     177    IF ( io_status == 0 )  THEN
     178!
     179!--    spectra_parameters namelist was found and read correctly.
     180!--    Default setting of dt_dosp here (instead of check_parameters), because its current value is
     181!--    needed in init_pegrid.
     182       IF ( dt_dosp == 9999999.9_wp )  dt_dosp = dt_data_output
     183!
     184!--    Set general switch that spectra shall be calculated.
     185       calculate_spectra = .TRUE.
     186
     187    ELSEIF ( io_status > 0 )  THEN
     188!
     189!--    spectra_parameters namelist was found but contained errors. Print an error message including
     190!--    the line that caused the problem.
     191       BACKSPACE( 11 )
     192       READ( 11 , '(A)' ) line
     193       CALL parin_fail_message( 'spectra_parameters', line )
     194
     195    ENDIF
    235196
    236197 END SUBROUTINE spectra_parin
Note: See TracChangeset for help on using the changeset viewer.