Ignore:
Timestamp:
Jan 31, 2018 10:44:42 AM (6 years ago)
Author:
Giersch
Message:

Skipping of module related restart data changed + adapting synthetic turbulence generator to current restart procedure

File:
1 edited

Legend:

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

    r2716 r2776  
    2525! -----------------
    2626! $Id$
     27! Variable synthetic_turbulence_generator use_synthetic_turbulence_generator has
     28! been abbreviated + syn_turb_gen_prerun flag is used to define if module
     29! related parameters were outputted as restart data
     30!
     31! 2716 2017-12-29 16:35:59Z kanani
    2732! Corrected "Former revisions" section
    2833!
     
    8388    USE control_parameters,                                                    &
    8489        ONLY:  initializing_actions, message_string,                           &
    85                synthetic_turbulence_generator
     90               syn_turb_gen, syn_turb_gen_prerun
    8691
    8792    USE cpulog,                                                                &
     
    104109    IMPLICIT NONE
    105110
    106     LOGICAL :: velocity_seed_initialized = .FALSE.           !< true after first call of stg_main
    107     LOGICAL :: use_synthetic_turbulence_generator = .FALSE.  !< switch to use synthetic turbulence generator
     111    LOGICAL :: velocity_seed_initialized = .FALSE.  !< true after first call of stg_main
     112    LOGICAL :: use_syn_turb_gen = .FALSE.           !< switch to use synthetic turbulence generator
    108113
    109114    INTEGER(iwp) :: stg_type_yz        !< MPI type for full z range
     
    221226!
    222227!-- Public variables
    223     PUBLIC  use_synthetic_turbulence_generator
     228    PUBLIC  use_syn_turb_gen
    224229
    225230
     
    241246    IMPLICIT NONE
    242247
    243     IF ( use_synthetic_turbulence_generator )  THEN
     248    IF ( use_syn_turb_gen )  THEN
    244249
    245250       IF ( INDEX( initializing_actions, 'set_constant_profiles' ) == 0  .AND. &
     
    288293!-- Write synthetic turbulence generator Header
    289294    WRITE( io, 1 )
    290     IF ( use_synthetic_turbulence_generator )  THEN
     295    IF ( use_syn_turb_gen )  THEN
    291296       WRITE( io, 2 )
    292297    ELSE
     
    665670
    666671
    667     NAMELIST /stg_par/   use_synthetic_turbulence_generator
     672    NAMELIST /stg_par/   use_syn_turb_gen
    668673
    669674    line = ' '
     
    685690!-- Set flag that indicates that the synthetic turbulence generator is switched
    686691!-- on
    687     synthetic_turbulence_generator = .TRUE.
     692    syn_turb_gen = .TRUE.
    688693
    689694    IF ( TRIM( initializing_actions ) == 'read_restart_data' ) THEN
     
    738743       SELECT CASE ( TRIM( variable_chr ) )
    739744
    740           CASE ( 'use_synthetic_turbulence_generator ' )
    741              READ ( 13 )  use_synthetic_turbulence_generator
     745          CASE ( 'use_syn_turb_gen' )
     746             READ ( 13 )  use_syn_turb_gen
    742747          CASE ( 'mc_factor' )
    743748             READ ( 13 )  mc_factor
     749          CASE ( 'syn_turb_gen_prerun' )
     750             READ ( 13 )  syn_turb_gen_prerun
    744751
    745752       END SELECT
     
    762769    IMPLICIT NONE
    763770
    764     WRITE ( 14 )  'use_synthetic_turbulence_generator '
    765     WRITE ( 14 )  use_synthetic_turbulence_generator
    766     WRITE ( 14 )  'mc_factor           '
     771    syn_turb_gen_prerun = .TRUE.
     772
     773    WRITE ( 14 )  'use_syn_turb_gen              '
     774    WRITE ( 14 )  use_syn_turb_gen
     775    WRITE ( 14 )  'mc_factor                     '
    767776    WRITE ( 14 )  mc_factor
    768 
    769     WRITE ( 14 )  '*** end stg module ***            '
     777    WRITE ( 14 )  'syn_turb_gen_prerun           '
     778    WRITE ( 14 )  syn_turb_gen_prerun
     779
     780    WRITE ( 14 )  '*** end stg module ***        '
    770781
    771782END SUBROUTINE stg_write_restart_data
Note: See TracChangeset for help on using the changeset viewer.