Changeset 1677 for palm


Ignore:
Timestamp:
Oct 2, 2015 1:25:23 PM (8 years ago)
Author:
boeske
Message:

Bugfix concerning wall_flags at PE boundaries, added new subroutine exchange_horiz_int

Location:
palm/trunk/SOURCE
Files:
4 edited

Legend:

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

    r1570 r1677  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Added new routine for exchange of three-dimensional integer arrays
    2323!
    2424! Former revisions:
     
    285285#endif
    286286 END SUBROUTINE exchange_horiz
     287
     288
     289 SUBROUTINE exchange_horiz_int( ar, nbgp_local)
     290
     291    USE control_parameters,                                                    &
     292        ONLY:  bc_lr, bc_lr_cyc, bc_ns, bc_ns_cyc
     293                       
     294    USE indices,                                                               &
     295        ONLY:  nxl, nxr, nyn, nys, nzb, nzt
     296       
     297    USE kinds
     298   
     299    USE pegrid
     300
     301    IMPLICIT NONE
     302
     303
     304    INTEGER(iwp) ::  nbgp_local  !: number of ghost points
     305   
     306    INTEGER(iwp), DIMENSION(nzb:nzt+1,nys-nbgp_local:nyn+nbgp_local,           &
     307                        nxl-nbgp_local:nxr+nbgp_local) ::  ar  !: treated array
     308
     309#if ! defined( __check )
     310
     311#if defined( __parallel )
     312    IF ( pdims(1) == 1 )  THEN
     313!
     314!--    One-dimensional decomposition along y, boundary values can be exchanged
     315!--    within the PE memory
     316       IF ( bc_lr_cyc )  THEN
     317          ar(:,:,nxl-nbgp_local:nxl-1) = ar(:,:,nxr-nbgp_local+1:nxr)
     318          ar(:,:,nxr+1:nxr+nbgp_local) = ar(:,:,nxl:nxl+nbgp_local-1)
     319       ENDIF
     320    ELSE
     321!
     322!--    Send left boundary, receive right one (synchronous)
     323       CALL MPI_SENDRECV(                                                      &
     324           ar(nzb,nys-nbgp_local,nxl),   1, type_yz_int, pleft,  0,            &
     325           ar(nzb,nys-nbgp_local,nxr+1), 1, type_yz_int, pright, 0,            &
     326           comm2d, status, ierr )
     327!
     328!--    Send right boundary, receive left one (synchronous)
     329       CALL MPI_SENDRECV(                                                      &
     330           ar(nzb,nys-nbgp_local,nxr+1-nbgp_local), 1, type_yz_int, pright, 1, &
     331           ar(nzb,nys-nbgp_local,nxl-nbgp_local),   1, type_yz_int, pleft,  1, &
     332           comm2d, status, ierr )
     333    ENDIF
     334
     335
     336    IF ( pdims(2) == 1 )  THEN
     337!
     338!--    One-dimensional decomposition along x, boundary values can be exchanged
     339!--    within the PE memory
     340       IF ( bc_ns_cyc )  THEN
     341          ar(:,nys-nbgp_local:nys-1,:) = ar(:,nyn-nbgp_local+1:nyn,:)
     342          ar(:,nyn+1:nyn+nbgp_local,:) = ar(:,nys:nys+nbgp_local-1,:)
     343       ENDIF
     344
     345    ELSE
     346
     347!
     348!--    Send front boundary, receive rear one (synchronous)
     349       CALL MPI_SENDRECV(                                                      &
     350           ar(nzb,nys,nxl-nbgp_local),   1, type_xz_int, psouth, 0,            &
     351           ar(nzb,nyn+1,nxl-nbgp_local), 1, type_xz_int, pnorth, 0,            &
     352           comm2d, status, ierr )
     353!
     354!--    Send rear boundary, receive front one (synchronous)
     355       CALL MPI_SENDRECV( ar(nzb,nyn-nbgp_local+1,nxl-nbgp_local), 1,          &
     356                          type_xz_int, pnorth, 1,                              &
     357                          ar(nzb,nys-nbgp_local,nxl-nbgp_local),   1,          &
     358                          type_xz_int, psouth, 1,                              &
     359                          comm2d, status, ierr )
     360
     361    ENDIF
     362
     363#else
     364
     365    IF ( bc_lr == 'cyclic' )  THEN
     366       ar(:,:,nxl-nbgp_local:nxl-1) = ar(:,:,nxr-nbgp_local+1:nxr)
     367       ar(:,:,nxr+1:nxr+nbgp_local) = ar(:,:,nxl:nxl+nbgp_local-1)
     368    ENDIF
     369
     370    IF ( bc_ns == 'cyclic' )  THEN
     371       ar(:,nys-nbgp_local:nys-1,:) = ar(:,nyn-nbgp_local+1:nyn,:)
     372       ar(:,nyn+1:nyn+nbgp_local,:) = ar(:,nys:nys+nbgp_local-1,:)
     373    ENDIF
     374
     375#endif
     376#endif
     377
     378
     379 END SUBROUTINE exchange_horiz_int
  • palm/trunk/SOURCE/init_grid.f90

    r1676 r1677  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Bugfix: Ghost points are included in wall_flags_0 and wall_flags_00
    2323!
    2424! Former revisions:
     
    717717!-- In case of non-cyclic lateral boundaries, the order of the advection
    718718!-- scheme have to be reduced up to nzt (required at the lateral boundaries).
    719     nzb_max = MAXVAL( nzb_local )
     719    nzb_max = MAXVAL( nzb_local ) + 1
    720720    IF ( inflow_l .OR. outflow_l .OR. inflow_r .OR. outflow_r .OR.             &
    721721         inflow_n .OR. outflow_n .OR. inflow_s .OR. outflow_s )  THEN
     
    11881188!
    11891189!-- Allocate flags needed for masking walls.
    1190     ALLOCATE( wall_flags_0(nzb:nzt,nys:nyn,nxl:nxr), &
    1191               wall_flags_00(nzb:nzt,nys:nyn,nxl:nxr) )
     1190    ALLOCATE( wall_flags_0(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                    &
     1191              wall_flags_00(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    11921192    wall_flags_0  = 0
    11931193    wall_flags_00 = 0
     
    14531453!
    14541454!--             w component - z-direction
    1455 !--             WS1 (33), WS3 (34), WS5 (35)
     1455!--             WS1 (33), WS3 (34)IF ( inflow_l .OR. outflow_l )  THEN, WS5 (35)
    14561456                flag_set = .FALSE.
    14571457                IF ( k == nzb_w_inner(j,i) .OR. k == nzb_w_inner(j,i) + 1      &
     
    14791479
    14801480!
     1481!-- Exchange 3D integer wall_flags.
     1482    IF ( momentum_advec == 'ws-scheme' .OR. scalar_advec == 'ws-scheme'     &
     1483    .OR. scalar_advec == 'ws-scheme-mono' )  THEN 
     1484!
     1485!--    Exchange ghost points for advection flags
     1486       CALL exchange_horiz_int( wall_flags_0,  nbgp )
     1487       CALL exchange_horiz_int( wall_flags_00, nbgp )
     1488!
     1489!--    Set boundary flags at inflow and outflow boundary in case of
     1490!--    non-cyclic boundary conditions.
     1491       IF ( inflow_l .OR. outflow_l )  THEN
     1492          wall_flags_0(:,:,nxl-1)  = wall_flags_0(:,:,nxl)
     1493          wall_flags_00(:,:,nxl-1) = wall_flags_00(:,:,nxl)
     1494       ENDIF
     1495
     1496       IF ( inflow_r .OR. outflow_r )  THEN
     1497          wall_flags_0(:,:,nxr+1)  = wall_flags_0(:,:,nxr)
     1498          wall_flags_00(:,:,nxr+1) = wall_flags_00(:,:,nxr)
     1499       ENDIF
     1500
     1501       IF ( inflow_n .OR. outflow_n )  THEN
     1502          wall_flags_0(:,nyn+1,:)  = wall_flags_0(:,nyn,:)
     1503          wall_flags_00(:,nyn+1,:) = wall_flags_00(:,nyn,:)
     1504       ENDIF
     1505
     1506       IF ( inflow_s .OR. outflow_s )  THEN
     1507          wall_flags_0(:,nys-1,:)  = wall_flags_0(:,nys,:)
     1508          wall_flags_00(:,nys-1,:) = wall_flags_00(:,nys,:)
     1509       ENDIF
     1510
     1511    ENDIF
     1512
     1513!
    14811514!-- In case of topography: limit near-wall mixing length l_wall further:
    14821515!-- Go through all points of the subdomain one by one and look for the closest
  • palm/trunk/SOURCE/init_pegrid.f90

    r1576 r1677  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! New MPI-data types for exchange of 3D integer arrays.
    2323!
    2424! Former revisions:
     
    10351035
    10361036    ENDIF
     1037!
     1038!-- Define data types for exchange of 3D Integer arrays.
     1039    ngp_yz_int = (nzt - nzb + 2) * (nyn - nys + 1 + 2 * nbgp)
     1040
     1041    CALL MPI_TYPE_VECTOR( nxr-nxl+1+2*nbgp, nbgp*(nzt-nzb+2), ngp_yz_int, &
     1042                          MPI_INTEGER, type_xz_int, ierr )
     1043    CALL MPI_TYPE_COMMIT( type_xz_int, ierr )
     1044
     1045    CALL MPI_TYPE_VECTOR( nbgp, ngp_yz_int, ngp_yz_int, MPI_INTEGER, type_yz_int, &
     1046                          ierr )
     1047    CALL MPI_TYPE_COMMIT( type_yz_int, ierr )
     1048
    10371049#endif
    10381050
  • palm/trunk/SOURCE/modules.f90

    r1667 r1677  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! +ngp_yz_int, type_xz_int, type_yz_int
    2323!
    2424! Former revisions:
     
    13151315#endif
    13161316
    1317 
     1317    INTEGER(iwp) :: ngp_yz_int, type_xz_int, type_yz_int
    13181318    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ngp_xz, ngp_yz, type_xz, type_yz
    13191319
Note: See TracChangeset for help on using the changeset viewer.