Ignore:
Timestamp:
Mar 7, 2008 1:42:18 PM (16 years ago)
Author:
raasch
Message:

preliminary update for the turbulence recycling method

File:
1 edited

Legend:

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

    r145 r151  
    44! Actual revisions:
    55! -----------------
    6 ! Collect on PE0 horizontal index bounds from all other PEs
     6! Collect on PE0 horizontal index bounds from all other PEs,
     7! broadcast the id of the inflow PE (using the respective communicator)
    78! TEST OUTPUT (TO BE REMOVED) logging mpi2 ierr values
    89!
     
    5758    IMPLICIT NONE
    5859
    59     INTEGER ::  gathered_size, i, ind(5), j, k, maximum_grid_level_l,     &
    60                 mg_switch_to_pe0_level_l, mg_levels_x, mg_levels_y,      &
    61                 mg_levels_z, nnx_y, nnx_z, nny_x, nny_z, nnz_x, nnz_y,    &
    62                 numproc_sqr, nx_total, nxl_l, nxr_l, nyn_l, nys_l, nzb_l, &
    63                 nzt_l, omp_get_num_threads, subdomain_size
     60    INTEGER ::  gathered_size, i, id_inflow_l, ind(5), j, k,                 &
     61                maximum_grid_level_l, mg_switch_to_pe0_level_l, mg_levels_x, &
     62                mg_levels_y, mg_levels_z, nnx_y, nnx_z, nny_x, nny_z, nnz_x, &
     63                nnz_y, numproc_sqr, nx_total, nxl_l, nxr_l, nyn_l, nys_l,    &
     64                nzb_l, nzt_l, omp_get_num_threads, subdomain_size
    6465
    6566    INTEGER, DIMENSION(:), ALLOCATABLE ::  ind_all, nxlf, nxrf, nynf, nysf
     
    918919    ENDIF
    919920
     921!
     922!-- Broadcast the id of the inflow PE
     923    IF ( inflow_l )  THEN
     924       id_inflow_l = myid
     925    ELSE
     926       id_inflow_l = 0
     927    ENDIF
     928    CALL MPI_ALLREDUCE( id_inflow_l, id_inflow, 1, MPI_INTEGER, MPI_SUM, &
     929                        comm1dx, ierr )
     930
    920931#else
    921932    IF ( bc_lr == 'dirichlet/radiation' )  THEN
Note: See TracChangeset for help on using the changeset viewer.