Ignore:
Timestamp:
May 5, 2008 2:09:05 PM (16 years ago)
Author:
raasch
Message:

bugfixes for turbulent inflow in init_pegrid, inflow_turbulence, and init_3d_model

File:
1 edited

Legend:

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

    r151 r163  
    4848    USE control_parameters
    4949    USE fft_xy
     50    USE grid_variables
    5051    USE indices
    5152    USE pegrid
     
    5859    IMPLICIT NONE
    5960
    60     INTEGER ::  gathered_size, i, id_inflow_l, ind(5), j, k,                &
     61    INTEGER ::  gathered_size, i, id_inflow_l, id_recycling_l, ind(5), j, k, &
    6162                maximum_grid_level_l, mg_switch_to_pe0_level_l, mg_levels_x, &
    6263                mg_levels_y, mg_levels_z, nnx_y, nnx_z, nny_x, nny_z, nnz_x, &
     
    922923!-- Broadcast the id of the inflow PE
    923924    IF ( inflow_l )  THEN
    924        id_inflow_l = myid
     925       id_inflow_l = myidx
    925926    ELSE
    926927       id_inflow_l = 0
    927928    ENDIF
    928929    CALL MPI_ALLREDUCE( id_inflow_l, id_inflow, 1, MPI_INTEGER, MPI_SUM, &
     930                        comm1dx, ierr )
     931
     932!
     933!-- Broadcast the id of the recycling plane
     934!-- WARNING: needs to be adjusted in case of inflows other than from left side!
     935    IF ( ( recycling_width / dx ) >= nxl  .AND.  ( recycling_width / dx ) <= nxr ) &
     936    THEN
     937       id_recycling_l = myidx
     938    ELSE
     939       id_recycling_l = 0
     940    ENDIF
     941    CALL MPI_ALLREDUCE( id_recycling_l, id_recycling, 1, MPI_INTEGER, MPI_SUM, &
    929942                        comm1dx, ierr )
    930943
Note: See TracChangeset for help on using the changeset viewer.