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/ocean_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! file re-formatted to follow the PALM coding standard
    2731!
     
    572576    IMPLICIT NONE
    573577
    574     CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
    575 
    576 
    577     NAMELIST /ocean_parameters/  bc_sa_t, bottom_salinityflux, salinity, sa_surface,               &
    578                                  sa_vertical_gradient, sa_vertical_gradient_level,                 &
    579                                  stokes_waveheight, stokes_wavelength, surface_cooling_spinup_time,&
    580                                  top_salinityflux, wall_salinityflux, wave_breaking
    581 
    582 !
    583 !-- Try to find the namelist
    584     REWIND ( 11 )
    585     line = ' '
    586     DO WHILE ( INDEX( line, '&ocean_parameters' ) == 0 )
    587        READ ( 11, '(A)', END=12 )  line
    588     ENDDO
    589     BACKSPACE ( 11 )
    590 
    591 !
    592 !-- Read namelist
    593     READ ( 11, ocean_parameters, ERR = 10 )
    594 !
    595 !-- Set switch that enables PALM's ocean mode
    596     ocean_mode = .TRUE.
    597 
    598     GOTO 12
    599 
    600  10 BACKSPACE( 11 )
    601     READ( 11 , '(A)') line
    602     CALL parin_fail_message( 'ocean_parameters', line )
    603 
    604  12 CONTINUE
     578    CHARACTER(LEN=100) ::  line  !< dummy string that contains the current line of the parameter
     579                                 !< file
     580    INTEGER(iwp)  ::  io_status  !< status after reading the namelist file
     581
     582
     583    NAMELIST /ocean_parameters/  bc_sa_t,                                                          &
     584                                 bottom_salinityflux,                                              &
     585                                 salinity,                                                         &
     586                                 sa_surface,                                                       &
     587                                 sa_vertical_gradient,                                             &
     588                                 sa_vertical_gradient_level,                                       &
     589                                 stokes_waveheight,                                                &
     590                                 stokes_wavelength,                                                &
     591                                 surface_cooling_spinup_time,                                      &
     592                                 top_salinityflux,                                                 &
     593                                 wall_salinityflux,                                                &
     594                                 wave_breaking
     595
     596!
     597!-- Move to the beginning of the namelist file and try to find and read the namelist called
     598!-- ocean_parameters.
     599    REWIND( 11 )
     600    READ( 11, ocean_parameters, IOSTAT=io_status )
     601
     602!
     603!-- Action depending on the READ status
     604    IF ( io_status == 0 )  THEN
     605!
     606!--    ocean_parameters namelist was found and read correctly. Set switch that enables PALM's ocean
     607!--    mode.
     608       ocean_mode = .TRUE.
     609
     610    ELSEIF ( io_status > 0 )  THEN
     611!
     612!--    ocean_parameters namelist was found but contained errors. Print an error message including
     613!--    the line that caused the problem.
     614       BACKSPACE( 11 )
     615       READ( 11 , '(A)') line
     616       CALL parin_fail_message( 'ocean_parameters', line )
     617
     618    ENDIF
    605619
    606620 END SUBROUTINE ocean_parin
     621
    607622
    608623!--------------------------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.