Ignore:
Timestamp:
Nov 22, 2019 12:09:09 PM (4 years ago)
Author:
oliver.maas
Message:

Deleted parameter recycling_yshift. y-shift in case of non-cyclic boundary conditions and turbulent_inflow = .TRUE. is now steered by parameter y_shift, that is also used in case of cyclic boundary conditions.

File:
1 edited

Legend:

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

    r4297 r4301  
    2525! -----------------
    2626! $Id$
     27! use y_shift instead of old parameter recycling_yshift
     28!
     29! 4297 2019-11-21 10:37:50Z oliver.maas
    2730! changed recycling_yshift so that the y-shift can be a multiple of PE
    2831! instead of y-shift of a half domain width
     
    5558       
    5659    USE control_parameters,                                                    &
    57         ONLY:  humidity, passive_scalar, recycling_plane, recycling_yshift,    &
     60        ONLY:  humidity, passive_scalar, recycling_plane, y_shift,    &
    5861               recycling_method_for_thermodynamic_quantities
    5962       
     
    8790       inflow_dist        !< turbulence signal of vars, added at inflow boundary
    8891    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,7,nbgp) ::                         &
    89        local_inflow_dist  !< auxiliary variable for inflow_dist, used for yshift
     92       local_inflow_dist  !< auxiliary variable for inflow_dist, used for y-shift
    9093   
    9194    CALL cpu_log( log_point(40), 'inflow_turbulence', 'start' )
     
    245248!-- y-shift for inflow_dist
    246249!-- Shift inflow_dist in positive y direction by a number of
    247 !-- PEs equal to recycling_yshift
    248     IF ( ( recycling_yshift /= 0 ) .AND. myidx == id_inflow ) THEN
     250!-- PEs equal to y_shift
     251    IF ( ( y_shift /= 0 ) .AND. myidx == id_inflow ) THEN
    249252
    250253!
    251254!--    Calculate the ID of the PE which sends data to this PE (prev) and of the
    252255!--    PE which receives data from this PE (next).
    253        prev = MODULO(myidy - recycling_yshift , pdims(2))
    254        next = MODULO(myidy + recycling_yshift , pdims(2))
     256       prev = MODULO(myidy - y_shift , pdims(2))
     257       next = MODULO(myidy + y_shift , pdims(2))
    255258       
    256259       local_inflow_dist = 0.0_wp
Note: See TracChangeset for help on using the changeset viewer.