Ignore:
Timestamp:
Mar 27, 2018 3:52:42 PM (6 years ago)
Author:
suehring
Message:

Nesting in RANS-LES and RANS-RANS mode enabled; synthetic turbulence generator at all lateral boundaries in nesting or non-cyclic forcing mode; revised Inifor initialization in nesting mode

File:
1 edited

Legend:

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

    r2918 r2938  
    2525! -----------------
    2626! $Id$
     27! Further todo's
     28!
     29! 2936 2018-03-27 14:49:27Z suehring
    2730! - defined l_grid only within this module
    2831! - Moved l_wall definition from modules.f90
     
    6972!>       add OpenMP directives whereever possible
    7073!>       remove debug output variables (dummy1, dummy2, dummy3)
     74!> @todo Move initialization of wall-mixing length from init_grid
     75!> @todo Check for random disturbances
    7176!> @note <Enter notes on the module>
    7277!> @bug  TKE-e closure still crashes due to too small dt
     
    284289
    285290    USE control_parameters,                                                    &
    286         ONLY:  message_string, neutral, turbulent_inflow, turbulent_outflow
     291        ONLY:  message_string, nest_domain, neutral, turbulent_inflow,         &
     292               turbulent_outflow
    287293
    288294    IMPLICIT NONE
     
    302308             rans_tke_e = .TRUE.
    303309
    304              IF ( INDEX( initializing_actions, 'set_1d-model_profiles' )       &
    305                   == 0 )  THEN
     310             IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) == 0  &
     311                  .AND.  .NOT.  nest_domain )  THEN
    306312                message_string = 'Initializing without 1D model while ' //     &
    307313                                 'using TKE-e closure&' //                     &
     
    826832        ONLY:  use_sgs_for_particles, wang_kernel
    827833
     834    USE pmc_interface,                                                         &
     835        ONLY:  nested_run
     836
    828837    IMPLICIT NONE
    829838
     
    847856    ALLOCATE( e_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    848857#endif
    849 
     858!
     859!-- Allocate arrays required for dissipation.
     860!-- Please note, if it is a nested run, arrays need to be allocated even if
     861!-- they do not necessarily need to be transferred, which is attributed to
     862!-- the design of the model coupler which allocates memory for each variable.
    850863    IF ( rans_tke_e  .OR.  use_sgs_for_particles  .OR.  wang_kernel  .OR.      &
    851          collision_turbulence )  THEN
     864         collision_turbulence  .OR.  nested_run )  THEN
    852865#if defined( __nopointer )
    853866       ALLOCATE( diss(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     
    858871#else
    859872       ALLOCATE( diss_1(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    860        IF ( rans_tke_e )  THEN
     873       IF ( rans_tke_e  .OR.  nested_run )  THEN
    861874          ALLOCATE( diss_2(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    862875          ALLOCATE( diss_3(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     
    871884
    872885    IF ( rans_tke_e  .OR.  use_sgs_for_particles  .OR.     &
    873          wang_kernel  .OR.  collision_turbulence )  THEN
     886         wang_kernel  .OR.  collision_turbulence  .OR.  nested_run )  THEN
    874887       diss => diss_1
    875        IF ( rans_tke_e )  THEN
     888       IF ( rans_tke_e  .OR.  nested_run )  THEN
    876889       diss_p => diss_2; tdiss_m => diss_3
    877890       ENDIF
Note: See TracChangeset for help on using the changeset viewer.