Ignore:
Timestamp:
Jan 21, 2021 3:51:51 PM (3 years ago)
Author:
gronemeier
Message:

bugfix: removed syn_turb_gen from restart files, replaced use_syn_turb_gen by syn_turb_gen

File:
1 edited

Legend:

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

    r4843 r4848  
    2525! -----------------
    2626! $Id$
     27! replaced use_syn_turb_gen by syn_turb_gen
     28!
     29! 4843 2021-01-15 15:22:11Z raasch
    2730! local namelist parameter added to switch off the module although the respective module namelist
    2831! appears in the namelist file
     
    365368    LOGICAL ::  parametrize_inflow_turbulence = .FALSE.  !< flag indicating that inflow turbulence is either read from file
    366369                                                         !< (.FALSE.) or if it parametrized
    367     LOGICAL ::  use_syn_turb_gen              = .FALSE.  !< switch to use synthetic turbulence generator
    368370    LOGICAL ::  velocity_seed_initialized     = .FALSE.  !< true after first call of stg_main
    369371
     
    519521            parametrize_inflow_turbulence,                                                         &
    520522            time_stg_adjust,                                                                       &
    521             time_stg_call,                                                                         &
    522             use_syn_turb_gen
     523            time_stg_call
    523524
    524525
     
    533534 SUBROUTINE stg_check_parameters
    534535
    535     IF ( .NOT. use_syn_turb_gen  .AND.  .NOT. rans_mode  .AND.                                     &
     536    IF ( .NOT. syn_turb_gen  .AND.  .NOT. rans_mode  .AND.                                     &
    536537          nesting_offline )  THEN
    537538       message_string = 'Synthetic turbulence generator is required ' //                           &
     
    540541    ENDIF
    541542
    542     IF ( .NOT. use_syn_turb_gen  .AND.  child_domain                                               &
     543    IF ( .NOT. syn_turb_gen  .AND.  child_domain                                               &
    543544         .AND. rans_mode_parent  .AND.  .NOT. rans_mode )  THEN
    544545       message_string = 'Synthetic turbulence generator is required when nesting is applied ' //   &
     
    547548    ENDIF
    548549
    549     IF ( use_syn_turb_gen )  THEN
     550    IF ( syn_turb_gen )  THEN
    550551
    551552       IF ( child_domain  .AND.  .NOT. rans_mode  .AND.  .NOT. rans_mode_parent )  THEN
     
    613614!
    614615!-- Write synthetic turbulence generator Header
    615     WRITE( io, 1 )
    616     IF ( use_syn_turb_gen )  THEN
    617        WRITE( io, 2 )
    618     ELSE
    619        WRITE( io, 3 )
    620     ENDIF
    621 
    622     IF ( parametrize_inflow_turbulence )  THEN
    623        WRITE( io, 4 ) dt_stg_adjust
    624     ELSE
    625        WRITE( io, 5 )
     616    IF ( syn_turb_gen )  THEN
     617       WRITE( io, 1 )
     618       IF ( parametrize_inflow_turbulence )  THEN
     619          WRITE( io, 4 ) dt_stg_adjust
     620       ELSE
     621          WRITE( io, 5 )
     622       ENDIF
    626623    ENDIF
    627624
    6286251   FORMAT (//' Synthetic turbulence generator information:'/                                      &
    629626              ' ------------------------------------------'/)
    630 2   FORMAT ('    synthetic turbulence generator is switched on')
    631 3   FORMAT ('    synthetic turbulence generator is switched off')
    6326274   FORMAT ('    imposed turbulence statistics are parametrized and ajdusted to boundary-layer development each ', F8.2, ' s' )
    6336285   FORMAT ('    imposed turbulence is read from file' )
     
    12281223                        dt_stg_adjust,                                                             &
    12291224                        dt_stg_call,                                                               &
    1230                         switch_off_module,                                                         &
    1231                         use_syn_turb_gen
     1225                        switch_off_module
    12321226
    12331227
     
    12781272          READ ( 13 )  time_stg_call
    12791273
    1280        CASE ( 'use_syn_turb_gen' )
    1281           READ ( 13 )  use_syn_turb_gen
    1282 
    12831274       CASE DEFAULT
    12841275
     
    13001291    CALL rrd_mpi_io( 'time_stg_adjust', time_stg_adjust )
    13011292    CALL rrd_mpi_io( 'time_stg_call', time_stg_call )
    1302     CALL rrd_mpi_io( 'use_syn_turb_gen', use_syn_turb_gen )
    13031293
    13041294 END SUBROUTINE stg_rrd_global_mpi
     
    13201310       WRITE ( 14 )  time_stg_call
    13211311
    1322        CALL wrd_write_string( 'use_syn_turb_gen' )
    1323        WRITE ( 14 )  use_syn_turb_gen
    1324 
    13251312    ELSEIF ( restart_data_format_output(1:3) == 'mpi' )  THEN
    13261313
    13271314       CALL wrd_mpi_io( 'time_stg_adjust', time_stg_adjust )
    13281315       CALL wrd_mpi_io( 'time_stg_call', time_stg_call )
    1329        CALL wrd_mpi_io( 'use_syn_turb_gen', use_syn_turb_gen )
    13301316
    13311317    ENDIF
Note: See TracChangeset for help on using the changeset viewer.