Skip to content
Snippets Groups Projects
Commit 5c036d37 authored by Antoine Cyril David Hoffmann's avatar Antoine Cyril David Hoffmann :seedling:
Browse files

z buffer are now from 1 to 4

+ explanation of the structure
parent 4fa0ed5c
No related branches found
No related tags found
No related merge requests found
...@@ -98,7 +98,6 @@ SUBROUTINE update_ghosts_z_mom ...@@ -98,7 +98,6 @@ SUBROUTINE update_ghosts_z_mom
last = local_nz + ngz/2 last = local_nz + ngz/2
count = local_na*(local_np+ngp)*(local_nj+ngj)*local_nky*local_nkx count = local_na*(local_np+ngp)*(local_nj+ngj)*local_nky*local_nkx
IF (num_procs_z .GT. 1) THEN IF (num_procs_z .GT. 1) THEN
CALL MPI_BARRIER(MPI_COMM_WORLD,ierr)
!!!!!!!!!!! Send ghost to up neighbour !!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!! Send ghost to up neighbour !!!!!!!!!!!!!!!!!!!!!!
! Send the last local moment to fill the -1 neighbour ghost ! Send the last local moment to fill the -1 neighbour ghost
DO ig=1,ngz/2 DO ig=1,ngz/2
...@@ -153,47 +152,54 @@ SUBROUTINE update_ghosts_z_3D(field) ...@@ -153,47 +152,54 @@ SUBROUTINE update_ghosts_z_3D(field)
USE parallel, ONLY: nbr_U,nbr_D,comm0,num_procs_z USE parallel, ONLY: nbr_U,nbr_D,comm0,num_procs_z
USE grid, ONLY: local_nky,local_nkx,local_nz,ngz USE grid, ONLY: local_nky,local_nkx,local_nz,ngz
IMPLICIT NONE IMPLICIT NONE
!! buffer for data exchanges !! buffer for data exchanges, the last dimension is indexing the z ghost cells
COMPLEX(xp),DIMENSION(local_nky,local_nkx,-ngz/2:ngz/2) :: buff_xy_zBC ! Example in the full periodic case
! (down) |x|x|a|b|...|c|d|x|x| (UP) array along z with old ghost cells
! V
! |a|b|c|d| buffer
! 1 2 3 4 buffer indices
! V
! |c|d|a|b|...|c|d|a|b| array along z with update ghost cells
! 3 4 1 2 buffer indices
COMPLEX(xp),DIMENSION(local_nky,local_nkx,ngz) :: buff_xy_zBC
COMPLEX(xp), INTENT(INOUT) :: field(local_nky,local_nkx,local_nz+ngz) COMPLEX(xp), INTENT(INOUT) :: field(local_nky,local_nkx,local_nz+ngz)
INTEGER :: ikxBC_L, ikxBC_R, ikx, iky, first, last, ig, ierr INTEGER :: ikxBC_L, ikxBC_R, ikx, iky, first, last, ig, ierr
first = 1 + ngz/2 first = 1 + ngz/2
last = local_nz + ngz/2 last = local_nz + ngz/2
count = local_nky * local_nkx count = local_nky * local_nkx
IF (num_procs_z .GT. 1) THEN IF (num_procs_z .GT. 1) THEN
CALL MPI_BARRIER(MPI_COMM_WORLD,ierr)
!!!!!!!!!!! Send ghost to up neighbour !!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!! Send ghost to up neighbour !!!!!!!!!!!!!!!!!!!!!!
DO ig = 1,ngz/2 DO ig = 1,ngz/2
CALL mpi_sendrecv( field(:,:,last-(ig-1)), count, mpi_xp_c, nbr_U, 30+ig, & ! Send to Up the last CALL mpi_sendrecv( field(:,:,last-(ig-1)), count, mpi_xp_c, nbr_U, 30+ig, & ! Send to Up the last
buff_xy_zBC(:,:,-ig), count, mpi_xp_c, nbr_D, 30+ig, & ! Receive from Down the first-1 buff_xy_zBC(:,:, ngz-(ig-1)), count, mpi_xp_c, nbr_D, 30+ig, & ! Receive from Down the first-1 (idx 3,4)
comm0, status, ierr) comm0, status, ierr)
ENDDO ENDDO
!!!!!!!!!!! Send ghost to down neighbour !!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!! Send ghost to down neighbour !!!!!!!!!!!!!!!!!!!!!!
DO ig = 1,ngz/2 DO ig = 1,ngz/2
CALL mpi_sendrecv( field(:,:,first+(ig-1)), count, mpi_xp_c, nbr_D, 32+ig, & ! Send to Down the first CALL mpi_sendrecv( field(:,:,first+(ig-1)), count, mpi_xp_c, nbr_D, 32+ig, & ! Send to Down the first
buff_xy_zBC(:,:,ig), count, mpi_xp_c, nbr_U, 32+ig, & ! Recieve from Up the last+1 buff_xy_zBC(:,:,ig), count, mpi_xp_c, nbr_U, 32+ig, & ! Recieve from Up the last+1 (idx 1 2)
comm0, status, ierr) comm0, status, ierr)
ENDDO ENDDO
ELSE ELSE
! no parallelization so just copy last cell into first ghosts and vice versa ! no parallelization so just copy last cell into first ghosts and vice versa
DO ig = 1,ngz/2 DO ig = 1,ngz/2
buff_xy_zBC(:,:,-ig) = field(:,:,last-(ig-1)) buff_xy_zBC(:,:, ngz-(ig-1)) = field(:,:,last -(ig-1))
buff_xy_zBC(:,:, ig) = field(:,:,first+(ig-1)) buff_xy_zBC(:,:, ig) = field(:,:,first+(ig-1))
ENDDO ENDDO
ENDIF ENDIF
DO iky = 1,local_nky DO iky = 1,local_nky
DO ikx = 1,local_nkx DO ikx = 1,local_nkx
ikxBC_L = ikx_zBC_L(iky,ikx); ikxBC_L = ikx_zBC_L(iky,ikx)
IF (ikxBC_L .NE. -99) THEN ! Exchanging the modes that have a periodic pair (a) IF (ikxBC_L .NE. -99) THEN ! Exchanging the modes that have a periodic pair (a)
DO ig = 1,ngz/2 DO ig = 1,ngz/2
field(iky,ikx,first-ig) = pb_phase_L(iky)*buff_xy_zBC(iky,ikxBC_L,-ig) field(iky,ikx,first-ig) = pb_phase_L(iky)*buff_xy_zBC(iky,ikxBC_L,ngz-(ig-1))
ENDDO ENDDO
ELSE ELSE
DO ig = 1,ngz/2 DO ig = 1,ngz/2
field(iky,ikx,first-ig) = 0._xp field(iky,ikx,first-ig) = 0._xp
ENDDO ENDDO
ENDIF ENDIF
ikxBC_R = ikx_zBC_R(iky,ikx); ikxBC_R = ikx_zBC_R(iky,ikx)
IF (ikxBC_R .NE. -99) THEN ! Exchanging the modes that have a periodic pair (a) IF (ikxBC_R .NE. -99) THEN ! Exchanging the modes that have a periodic pair (a)
! last+1 gets first ! last+1 gets first
DO ig = 1,ngz/2 DO ig = 1,ngz/2
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment