Ignore:
Timestamp:
Jan 15, 2021 3:22:11 PM (3 years ago)
Author:
raasch
Message:

local namelist parameter added to switch off the module although the respective module namelist appears in the namelist file, further copyright updates

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/dynamics_mod.f90

    r4842 r4843  
    2424! -----------------
    2525! $Id$
     26! local namelist parameter added to switch off the module although the respective module namelist
     27! appears in the namelist file
     28!
     29! 4842 2021-01-14 10:42:28Z raasch
    2630! reading of namelist file and actions in case of namelist errors revised so that statement labels
    2731! and goto statements are not required any more
     
    339343 SUBROUTINE dynamics_parin
    340344
    341 
    342345    CHARACTER(LEN=100)  ::  line  !< dummy string that contains the current line of the parameter
    343346                                  !< file
    344347    INTEGER(iwp)  ::  io_status   !< status after reading the namelist file
    345348
     349    LOGICAL ::  switch_off_module = .FALSE.  !< local namelist parameter to switch off the module
     350                                             !< although the respective module namelist appears in
     351                                             !< the namelist file
    346352   
    347     NAMELIST /dynamics_parameters/  dynamics_module_enabled
    348 
    349 !
    350 !-- Set default module switch to true.
     353    NAMELIST /dynamics_parameters/  switch_off_module
     354
     355
     356!
     357!-- For the time beeing (unless the dynamics module is further developed), set default module
     358!-- switch to true.
    351359    dynamics_module_enabled = .TRUE.
    352360
     361!
    353362!-- Move to the beginning of the namelist file and try to find and read the namelist.
    354363    REWIND( 11 )
     
    357366!
    358367!-- Action depending on the READ status
    359     IF ( io_status > 0 )  THEN
     368    IF ( io_status == 0 )  THEN
     369!
     370!--    dynamics_parameters namelist was found and read correctly.
     371       IF ( .NOT. switch_off_module )  dynamics_module_enabled = .TRUE.
     372
     373    ELSEIF ( io_status > 0 )  THEN
    360374!
    361375!--    dynamics_parameters namelist was found, but contained errors. Print an error message
Note: See TracChangeset for help on using the changeset viewer.