Ignore:
Timestamp:
Jan 14, 2021 10:42:28 AM (4 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/gust_mod.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!
     29! 4828 2021-01-05 11:21:41Z Giersch
    2630! Enable 3D data output also with 64-bit precision
    2731!
     
    213217!> Parin for &gust_parameters for gust module
    214218!--------------------------------------------------------------------------------------------------!
    215     SUBROUTINE gust_parin
    216 
    217 
    218        IMPLICIT NONE
    219 
    220        CHARACTER (LEN=80)  ::  line  !< dummy string that contains the current line of the parameter file
    221 
    222        NAMELIST /gust_parameters/                                                                  &
    223           gust_module_enabled
    224 
    225        line = ' '
    226 !
    227 !--    Try to find gust module package
    228        REWIND ( 11 )
    229        line = ' '
    230        DO   WHILE ( INDEX( line, '&gust_parameters' ) == 0 )
    231           READ ( 11, '(A)', END=10 )  line
    232        ENDDO
    233        BACKSPACE ( 11 )
    234 !
    235 !--    Read user-defined namelist
    236        READ ( 11, gust_parameters )
    237 !
    238 !--    Set flag that indicates that the gust module is switched on
     219 SUBROUTINE gust_parin
     220
     221
     222    IMPLICIT NONE
     223
     224    CHARACTER(LEN=100)  ::  line  !< dummy string that contains the current line of the parameter
     225                                  !< file
     226    INTEGER(iwp)  ::  io_status   !< status after reading the namelist file
     227
     228
     229    NAMELIST /gust_parameters/  gust_module_enabled
     230
     231!
     232!-- Move to the beginning of the namelist file and try to find and read the namelist.
     233    REWIND( 11 )
     234    READ( 11, gust_parameters, IOSTAT=io_status )
     235
     236!
     237!-- Action depending on the READ status
     238    IF ( io_status == 0 )  THEN
     239!
     240!--    gust_parameters namelist was found and read correctly. Set flag that indicates that the gust
     241!--    module is switched on.
    239242       gust_module_enabled = .TRUE.
    240243
    241 10     CONTINUE
    242 
    243 
    244     END SUBROUTINE gust_parin
     244    ELSEIF ( io_status > 0 )  THEN
     245!
     246!--    gust_parameters namelist was found, but contained errors. Print an error message including
     247!--    the line that caused the problem.
     248       BACKSPACE( 11 )
     249       READ( 11 , '(A)') line
     250       CALL parin_fail_message( 'gust_parameters', line )
     251
     252    ENDIF
     253
     254 END SUBROUTINE gust_parin
    245255
    246256
Note: See TracChangeset for help on using the changeset viewer.