/[MITgcm]/MITgcm_contrib/cg2d_bench/exch.F
ViewVC logotype

Diff of /MITgcm_contrib/cg2d_bench/exch.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.1 by ce107, Fri May 12 21:58:05 2006 UTC revision 1.2 by ce107, Fri May 12 22:22:11 2006 UTC
# Line 1  Line 1 
1    C       $Id$    
2        SUBROUTINE EXCH_XY_R8( arr )        SUBROUTINE EXCH_XY_R8( arr )
3    
4  C     == Global variables ==  C     == Global variables ==
# Line 7  C     == Global variables == Line 8  C     == Global variables ==
8    
9  #ifdef ALLOW_MPI  #ifdef ALLOW_MPI
10  #include "mpif.h"  #include "mpif.h"
11    #include "MPI_INFO.h"
12  #endif  #endif
13    
 #include "MPI_INFO.h"  
14  #include "JAM_INFO.h"  #include "JAM_INFO.h"
15    
16  C     == Routine arguments ==  C     == Routine arguments ==
17        Real*8 arr(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        Real arr(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
18    
19  C     == Local variables ==  C     == Local variables ==
20        INTEGER I, J        INTEGER I, J
21        INTEGER northProc, southProc        INTEGER northProc, southProc
22    #ifdef DECOMP2D
23          INTEGER eastProc, westProc
24    #endif
25        INTEGER farProc1, farProc2        INTEGER farProc1, farProc2
26        INTEGER toPid, fromPid        INTEGER toPid, fromPid
27        INTEGER rc        INTEGER rc
# Line 25  C     == Local variables == Line 29  C     == Local variables ==
29        INTEGER myFourWayRank, exchangePhase        INTEGER myFourWayRank, exchangePhase
30    
31  #ifdef ALLOW_MPI  #ifdef ALLOW_MPI
32          INTEGER mpiReq(8)
33          INTEGER mpiStat(MPI_STATUS_SIZE,8)
34        INTEGER mpiStatus(MPI_STATUS_SIZE)        INTEGER mpiStatus(MPI_STATUS_SIZE)
35  #endif  #endif
36    
37    #ifndef DECOMP2D
38  C     East-west halo update (without corners)  C     East-west halo update (without corners)
39        DO J=1,sNy        DO J=1,sNy
40         DO I=1,OLx         DO I=1,OLx
# Line 35  C     East-west halo update (without cor Line 42  C     East-west halo update (without cor
42          arr(sNx+I,J)     = arr(1+I-1  ,J)          arr(sNx+I,J)     = arr(1+I-1  ,J)
43         ENDDO         ENDDO
44        ENDDO        ENDDO
45      #endif
46    
47  C     Phase 1 pairing  C     Phase 1 pairing
48  C     | 0 |  ---> | 1 |  C     | 0 |  ---> | 1 |
49  C     | 0 |  <--- | 1 |  C     | 0 |  <--- | 1 |
# Line 50  C     etc ... Line 58  C     etc ...
58  C      C    
59    
60  #ifdef USE_MPI_EXCH  #ifdef USE_MPI_EXCH
61    #ifdef DECOMP2D
62    C     East-West exchanges
63    #ifdef USE_SNDRCV
64    C     Send West, receive from East
65          CALL MPI_Sendrecv(arr(1,1), 1, ewslice, mpi_westId, 100,
66         $     arr(sNx+1,1), 1, ewslice, mpi_eastId, 100, comm_use,
67         $     mpiStatus, rc)
68    C     Send East, receive from West
69          CALL MPI_Sendrecv(arr(sNx-OLx+1,1), 1, ewslice, mpi_eastId, 200,
70         $     arr(1-OLx,1), 1, ewslice, mpi_westId, 200, comm_use,
71         $     mpiStatus,rc)
72    
73    C     North-South exchanges
74          
75    C     Send South, receive from North
76          CALL MPI_Sendrecv(arr(1,1), 1, nsslice, mpi_southId, 300,
77         $     arr(1,sNy+1), 1, nsslice, mpi_northId, 300, comm_use,
78         $     mpiStatus, rc)
79    C     Send North, receive from South
80          CALL MPI_Sendrecv(arr(1,sNy-OLy+1), 1, nsslice, mpi_northId, 400,
81         $     arr(1,1-OLy), 1, nsslice, mpi_southId, 400, comm_use,
82         $     mpiStatus,rc)
83    #else
84    C     Send West, receive from East
85          CALL MPI_Isend(arr(1,1), 1, ewslice, mpi_westId, 100,
86         $     comm_use, mpiReq(1), rc)
87          CALL MPI_Irecv(arr(sNx+1,1), 1, ewslice, mpi_eastId, 100,
88         $     comm_use, mpiReq(2), rc)
89    C     Send East, receive from West
90          CALL MPI_Isend(arr(sNx-OLx+1,1), 1, ewslice, mpi_eastId, 200,
91         $     comm_use, mpiReq(3), rc)
92          CALL MPI_Irecv(arr(1-OLx,1), 1, ewslice, mpi_westId, 200,
93         $     comm_use, mpiReq(4),rc)
94    
95    C     North-South exchanges
96          
97    C     Send South, receive from North
98          CALL MPI_Isend(arr(1,1), 1, nsslice, mpi_southId, 300,
99         $     comm_use, mpiReq(5), rc)
100          CALL MPI_Irecv(arr(1,sNy+1), 1, nsslice, mpi_northId, 300,
101         $     comm_use, mpiReq(6), rc)
102    C     Send North, receive from South
103          CALL MPI_Isend(arr(1,sNy-OLy+1), 1, nsslice, mpi_northId, 400,
104         $     comm_use, mpiReq(7), rc)
105          CALL MPI_Irecv(arr(1,1-OLy), 1, nsslice, mpi_southId, 400,
106         $     comm_use, mpiReq(8),rc)
107    
108          CALL MPI_Waitall(8, mpiReq, mpiStat, rc)
109    
110    #endif
111    
112    #else
113  C     North-south halo update (without corners)  C     North-south halo update (without corners)
114  C     Put my edges into a buffers  C     Put my edges into a buffers
115        IF ( MOD(myProcId,2) .EQ. 0 ) THEN        IF ( MOD(myProcId,2) .EQ. 0 ) THEN
# Line 76  C     Exchange the buffers Line 136  C     Exchange the buffers
136        ENDIF        ENDIF
137  C     Even-odd pairs  C     Even-odd pairs
138        IF ( farProc1 .NE. myProcId ) THEN        IF ( farProc1 .NE. myProcId ) THEN
139         CALL MPI_Sendrecv_replace(exchBuf1,sNx,MPI_DOUBLE_PRECISION,         CALL MPI_Sendrecv_replace(exchBuf1,sNx,_MPI_TYPE_REAL,
140       &                           farProc1,0,       &                           farProc1,0,
141       &                           farProc1,MPI_ANY_TAG,       &                           farProc1,MPI_ANY_TAG,
142       &                           MPI_COMM_WORLD,mpiStatus,       &                           comm_use,mpiStatus,
143       &                           rc)       &                           rc)
144        ENDIF        ENDIF
145  C     Odd-even pairs  C     Odd-even pairs
146        IF ( farProc2 .NE. myProcId ) THEN        IF ( farProc2 .NE. myProcId ) THEN
147         CALL MPI_Sendrecv_replace(exchBuf2,sNx,MPI_DOUBLE_PRECISION,         CALL MPI_Sendrecv_replace(exchBuf2,sNx,_MPI_TYPE_REAL,
148       &                           farProc2,0,       &                           farProc2,0,
149       &                           farProc2,MPI_ANY_TAG,       &                           farProc2,MPI_ANY_TAG,
150       &                           MPI_COMM_WORLD,mpiStatus,       &                           comm_use,mpiStatus,
151       &                           rc)       &                           rc)
152        ENDIF        ENDIF
153  #endif  #endif
154    #endif
155    
156  #ifdef USE_JAM_EXCH  #ifdef USE_JAM_EXCH
157    
# Line 106  C      recvBuf2  = &arr(I,0    ) Line 167  C      recvBuf2  = &arr(I,0    )
167         farProc1 = northProc         farProc1 = northProc
168         farProc2 = southProc         farProc2 = southProc
169         IF ( farProc1 .NE. myProcId ) THEN         IF ( farProc1 .NE. myProcId ) THEN
170          CALL JAM_EXCHANGE(farProc1,arr(I,sNy),arr(I,sNy+1),sNx*8,jam_exchKey)            CALL JAM_EXCHANGE(farProc1,arr(I,sNy),arr(I,sNy+1),sNx*8
171         $         ,jam_exchKey)
172          jam_exchKey = jam_exchKey+1          jam_exchKey = jam_exchKey+1
173         ENDIF         ENDIF
174    
# Line 150  C      recvBuf2  = &arr(I,sNy+1) Line 212  C      recvBuf2  = &arr(I,sNy+1)
212     21  CONTINUE     21  CONTINUE
213    
214         IF ( farProc2 .NE. myProcId ) THEN         IF ( farProc2 .NE. myProcId ) THEN
215          CALL JAM_EXCHANGE(farProc2,arr(I,sNy),arr(I,sNy+1),sNx*8,jam_exchKey)            CALL JAM_EXCHANGE(farProc2,arr(I,sNy),arr(I,sNy+1),sNx*8
216         $         ,jam_exchKey)
217          jam_exchKey = jam_exchKey+1          jam_exchKey = jam_exchKey+1
218         ENDIF         ENDIF
219    
# Line 159  C      recvBuf2  = &arr(I,sNy+1) Line 222  C      recvBuf2  = &arr(I,sNy+1)
222        ENDIF        ENDIF
223  #endif  #endif
224    
225  #ifdef USE_MPI_EXCH  #if defined(USE_MPI_EXCH) && !defined(DECOMP2D)
226  C     Fill overlap regions from the buffers  C     Fill overlap regions from the buffers
227        IF ( MOD(myProcId,2) .EQ. 0 ) THEN        IF ( MOD(myProcId,2) .EQ. 0 ) THEN
228         DO I=1,sNx         DO I=1,sNx

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.2

  ViewVC Help
Powered by ViewVC 1.1.22