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

    r4834 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!
     29! 4834 2021-01-07 10:28:00Z raasch
    2630! file re-formatted to follow the PALM coding standard
    2731!
     
    24482452 SUBROUTINE nesting_offl_parin
    24492453
    2450     CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
    2451 
    2452 
    2453     NAMELIST /nesting_offl_parameters/   nesting_offline
    2454 
    2455     line = ' '
    2456 
    2457 !
    2458 !-- Try to find stg package
    2459     REWIND ( 11 )
    2460     line = ' '
    2461     DO WHILE ( INDEX( line, '&nesting_offl_parameters' ) == 0 )
    2462        READ ( 11, '(A)', END=20 )  line
    2463     ENDDO
    2464     BACKSPACE ( 11 )
    2465 
    2466 !
    2467 !-- Read namelist
    2468     READ ( 11, nesting_offl_parameters, ERR = 10, END = 20 )
    2469 
    2470     GOTO 20
    2471 
    2472 10    BACKSPACE( 11 )
    2473     READ( 11 , '(A)') line
    2474     CALL parin_fail_message( 'nesting_offl_parameters', line )
    2475 
    2476 20    CONTINUE
    2477 
     2454    CHARACTER(LEN=100) ::  line  !< dummy string that contains the current line of the parameter file
     2455    INTEGER(iwp) ::  io_status   !< status after reading the namelist file
     2456
     2457
     2458    NAMELIST /nesting_offl_parameters/  nesting_offline
     2459
     2460!
     2461!-- Move to the beginning of the namelist file and try to find and read the namelist.
     2462    REWIND( 11 )
     2463    READ( 11, nesting_offl_parameters, IOSTAT=io_status )
     2464
     2465!
     2466!-- Action depending on the READ status
     2467    IF ( io_status > 0 )  THEN
     2468!
     2469!--    nesting_offl_parameters namelist was found but contained errors. Print an error message
     2470!--    including the line that caused the problem.
     2471       BACKSPACE( 11 )
     2472       READ( 11 , '(A)' ) line
     2473       CALL parin_fail_message( 'nesting_offl_parameters', line )
     2474
     2475    ENDIF
    24782476
    24792477 END SUBROUTINE nesting_offl_parin
     2478
    24802479
    24812480!--------------------------------------------------------------------------------------------------!
     
    25002499
    25012500 END SUBROUTINE nesting_offl_header
     2501
    25022502
    25032503!--------------------------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.