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

    r4833 r4843  
    2626! -----------------
    2727! $Id$
     28! local namelist parameter added to switch off the module although the respective module namelist
     29! appears in the namelist file
     30!
     31! 4833 2021-01-07 08:57:54Z raasch
    2832! openmp bugfix for time measurements of non advective processes
    2933!
     
    25062510    USE chem_modules
    25072511    USE control_parameters
    2508 
    25092512    USE pegrid
    25102513    USE statistics
    2511 
    25122514
    25132515    CHARACTER(LEN=100) ::  line                        !< dummy string that contains the current
     
    25182520    INTEGER(iwp) ::  io_status                         !< Status after reading the namelist file
    25192521    INTEGER(iwp) ::  max_pr_cs_tmp                     !<
     2522
     2523    LOGICAL ::  switch_off_module = .FALSE.  !< local namelist parameter to switch off the module
     2524                                             !< although the respective module namelist appears in
     2525                                             !< the namelist file
    25202526
    25212527    REAL(wp), DIMENSION(nmaxfixsteps) ::   my_steps    !< List of fixed timesteps   my_step(1) = 0.0
     
    25642570         surface_csflux,                                                                           &
    25652571         surface_csflux_name,                                                                      &
     2572         switch_off_module,                                                                        &
    25662573         time_fac_type
    25672574!
     
    25942601!
    25952602!      chemistry_parameters namelist was found and read correctly. Switch on chemistry model.
    2596        air_chemistry = .TRUE.
     2603       IF ( .NOT. switch_off_module )  air_chemistry = .TRUE.
    25972604
    25982605    ELSEIF ( io_status > 0 )  THEN
Note: See TracChangeset for help on using the changeset viewer.