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

    r4828 r4842  
    2020! Current revisions:
    2121! -----------------
    22 ! 
    23 ! 
     22!
     23!
    2424! Former revisions:
    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!
     30! 4828 2021-01-05 11:21:41Z Giersch
    2731! Bugfix, use time_since_reference_point instead of simulated_time
    28 ! 
     32!
    2933! 4535 2020-05-15 12:07:23Z raasch
    3034! bugfix for restart data format query
    31 ! 
     35!
    3236! 4522 2020-05-06 14:17:05Z suehring
    3337! Modularize user_init_flight in order to provide an explicit interface.
    34 ! 
     38!
    3539! 4497 2020-04-15 10:20:51Z raasch
    3640! file re-formatted to follow the PALM coding standard
     
    3943! 4495 2020-04-13 20:11:20Z raasch
    4044! restart data handling with MPI-IO added
    41 ! 
     45!
    4246! 4360 2020-01-07 11:25:50Z suehring
    4347! Corrected "Former revisions" section
     
    226230 SUBROUTINE flight_parin
    227231
    228     USE control_parameters,                                                                        &
    229         ONLY:  message_string
    230 
    231232    IMPLICIT NONE
    232233
    233     CHARACTER(LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
    234 
    235     NAMELIST /flight_par/ flight_angle,                                                            &
    236                           flight_begin,                                                            &
    237                           flight_end,                                                              &
    238                           flight_level,                                                            &
    239                           leg_mode,                                                                &
    240                           max_elev_change,                                                         &
    241                           rate_of_climb,                                                           &
    242                           speed_agl,                                                               &
    243                           x_end,                                                                   &
    244                           x_start,                                                                 &
    245                           y_end,                                                                   &
    246                           y_start
     234    CHARACTER(LEN=100) ::  line  !< dummy string that contains the current line of the parameter file
     235
     236    INTEGER(iwp) ::  io_status   !< status after reading the namelist file
    247237
    248238
     
    259249                                         y_end,                                                    &
    260250                                         y_start
    261 !
    262 !-- Try to find the namelist flight_par
    263     REWIND ( 11 )
    264     line = ' '
    265     DO  WHILE ( INDEX( line, '&virtual_flight_parameters' ) == 0 )
    266        READ ( 11, '(A)', END = 12 )  line
    267     ENDDO
    268     BACKSPACE ( 11 )
    269 
    270 !
    271 !-- Read namelist
    272     READ ( 11, virtual_flight_parameters, ERR = 10 )
    273 !
    274 !-- Set switch so that virtual flights shall be carried out
    275     virtual_flight = .TRUE.
    276 
    277     GOTO 14
    278 
    279  10    BACKSPACE( 11 )
    280        READ( 11 , '(A)') line
     251
     252!
     253!-- Move to the beginning of the namelist file and try to find and read the namelist.
     254    REWIND( 11 )
     255    READ( 11, virtual_flight_parameters, IOSTAT=io_status )
     256
     257!
     258!-- Action depending on the READ status
     259    IF ( io_status == 0 )  THEN
     260!
     261!--    virtual_flight_parameters namelist was found and read correctly. Set switch that virtual
     262!--    flights are carried out.
     263       virtual_flight = .TRUE.
     264
     265    ELSEIF ( io_status > 0 )  THEN
     266!
     267!--    virtual_flight_parameters namelist was found, but contained errors. Print an error message
     268!--    including the line that caused the problem.
     269       BACKSPACE( 11 )
     270       READ( 11 , '(A)' ) line
    281271       CALL parin_fail_message( 'virtual_flight_parameters', line )
    282 !
    283 !--    Try to find the old namelist
    284  12    REWIND ( 11 )
    285        line = ' '
    286        DO  WHILE ( INDEX( line, '&flight_par' ) == 0 )
    287           READ ( 11, '(A)', END = 14 )  line
    288        ENDDO
    289        BACKSPACE ( 11 )
    290 
    291 !
    292 !-- Read namelist
    293     READ ( 11, flight_par, ERR = 13, END = 14 )
    294 
    295     message_string = 'namelist flight_par is deprecated and will be ' //                           &
    296                      'removed in near future.& Please use namelist ' //                            &
    297                      'virtual_flight_parameters instead'
    298     CALL message( 'flight_parin', 'PA0487', 0, 1, 0, 6, 0 )
    299 !
    300 !-- Set switch so that virtual flights shall be carried out
    301     virtual_flight = .TRUE.
    302 
    303     GOTO 14
    304 
    305  13    BACKSPACE( 11 )
    306        READ( 11 , '(A)') line
    307        CALL parin_fail_message( 'flight_par', line )
    308 
    309  14    CONTINUE
     272
     273    ENDIF
    310274
    311275 END SUBROUTINE flight_parin
     276
    312277
    313278!--------------------------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.