/[MITgcm]/MITgcm/eesupp/src/exch_rx_recv_get_y.template
ViewVC logotype

Diff of /MITgcm/eesupp/src/exch_rx_recv_get_y.template

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

revision 1.1 by adcroft, Tue May 29 14:06:38 2001 UTC revision 1.14 by jmc, Mon May 17 02:28:06 2010 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3  #include "CPP_EEOPTIONS.h"  #include "CPP_EEOPTIONS.h"
4    #undef EXCH_USE_SPINNING
5    
6    CBOP
7    C     !ROUTINE: EXCH_RX_RECV_GET_Y
8    
9    C     !INTERFACE:
10        SUBROUTINE EXCH_RX_RECV_GET_Y( array,        SUBROUTINE EXCH_RX_RECV_GET_Y( array,
11       I            myOLw, myOLe, myOLs, myOLn, myNz,       I            myOLw, myOLe, myOLs, myOLn, myNz,
12       I            exchWidthX, exchWidthY,       I            exchWidthX, exchWidthY,
13       I            theSimulationMode, theCornerMode, myThid )       I            theSimulationMode, theCornerMode, myThid )
 C     /==========================================================\  
 C     | SUBROUTINE RECV_GET_Y                                    |  
 C     | o "Send" or "put" Y edges for RX array.                  |  
 C     |==========================================================|  
 C     | Routine that invokes actual message passing send or      |  
 C     | direct "put" of data to update X faces of an XY[R] array.|  
 C     \==========================================================/  
14        IMPLICIT NONE        IMPLICIT NONE
15    
16    C     !DESCRIPTION:
17    C     *==========================================================*
18    C     | SUBROUTINE RECV_GET_Y
19    C     | o "Send" or "put" Y edges for RX array.
20    C     *==========================================================*
21    C     | Routine that invokes actual message passing send or
22    C     | direct "put" of data to update X faces of an XY[R] array.
23    C     *==========================================================*
24    
25    C     !USES:
26  C     == Global variables ==  C     == Global variables ==
27  #include "SIZE.h"  #include "SIZE.h"
28  #include "EEPARAMS.h"  #include "EEPARAMS.h"
29  #include "EESUPPORT.h"  #include "EESUPPORT.h"
30  #include "EXCH.h"  #include "EXCH.h"
31    
32    C     !INPUT/OUTPUT PARAMETERS:
33  C     == Routine arguments ==  C     == Routine arguments ==
34  C     array - Array with edges to exchange.  C     array :: Array with edges to exchange.
35  C     myOLw - West, East, North and South overlap region sizes.  C     myOLw :: West, East, North and South overlap region sizes.
36  C     myOLe  C     myOLe
37  C     myOLn  C     myOLn
38  C     myOLs  C     myOLs
39  C     exchWidthX - Width of data region exchanged.  C     exchWidthX :: Width of data region exchanged.
40  C     exchWidthY  C     exchWidthY
41  C     theSimulationMode - Forward or reverse mode exchange ( provides  C     theSimulationMode :: Forward or reverse mode exchange ( provides
42  C                         support for adjoint integration of code. )  C                          support for adjoint integration of code. )
43  C     theCornerMode     - Flag indicating whether corner updates are  C     theCornerMode     :: Flag indicating whether corner updates are
44  C                         needed.  C                          needed.
45  C     myThid            - Thread number of this instance of S/R EXCH...  C     myThid            :: Thread number of this instance of S/R EXCH...
46  C     eBl               - Edge buffer level  C     eBl               :: Edge buffer level
47        INTEGER myOLw        INTEGER myOLw
48        INTEGER myOLe        INTEGER myOLe
49        INTEGER myOLs        INTEGER myOLs
# Line 48  C     eBl               - Edge buffer le Line 57  C     eBl               - Edge buffer le
57        INTEGER theSimulationMode        INTEGER theSimulationMode
58        INTEGER theCornerMode        INTEGER theCornerMode
59        INTEGER myThid        INTEGER myThid
 CEndOfInterface  
60    
61    C     !LOCAL VARIABLES:
62  C     == Local variables ==  C     == Local variables ==
63  C     I, J, K, iMin, iMax, iB    - Loop counters and extents  C     i, j, k, iMin, iMax, iB    :: Loop counters and extents
64  C     bi, bj  C     bi, bj
65  C     biS, bjS                   - South tile indices  C     biS, bjS                   :: South tile indices
66  C     biN, bjN                   - North tile indices  C     biN, bjN                   :: North tile indices
67  C     eBl                        - Current exchange buffer level  C     eBl                        :: Current exchange buffer level
68  C     theProc, theTag, theType,  - Variables used in message building  C     theProc, theTag, theType,  :: Variables used in message building
69  C     theSize  C     theSize
70  C     southCommMode              - Working variables holding type  C     southCommMode              :: Working variables holding type
71  C     northCommMode                of communication a particular  C     northCommMode                 of communication a particular
72  C                                  tile face uses.  C                                   tile face uses.
73  C     spinCount                  - Exchange statistics counter  C     spinCount                  :: Exchange statistics counter
74        INTEGER I, J, K, iMin, iMax, jMin, jMax, iB, iB0  C     mpiStatus                  :: MPI error code
75          INTEGER i, j, k, iMin, iMax, jMin, jMax, iB, iB0
76        INTEGER bi, bj, biS, bjS, biN, bjN        INTEGER bi, bj, biS, bjS, biN, bjN
77        INTEGER eBl        INTEGER eBl
78        INTEGER southCommMode        INTEGER southCommMode
79        INTEGER northCommMode        INTEGER northCommMode
80    #ifdef EXCH_USE_SPINNING
81        INTEGER spinCount        INTEGER spinCount
82    #endif
83  #ifdef ALLOW_USE_MPI  #ifdef ALLOW_USE_MPI
84        INTEGER theProc, theTag, theType, theSize        INTEGER theProc, theTag, theType, theSize, pReqI
85        INTEGER mpiStatus(MPI_STATUS_SIZE,4), mpiRc        INTEGER mpiStatus(MPI_STATUS_SIZE,4), mpiRc
86  #endif  #endif
87    CEOP
88    
89    C--   Under a "put" scenario we
 C--   Under a "put" scenario we  
90  C--     i. set completetion signal for buffer we put into.  C--     i. set completetion signal for buffer we put into.
91  C--    ii. wait for completetion signal indicating data has been put in  C--    ii. wait for completetion signal indicating data has been put in
92  C--        our buffer.  C--        our buffer.
93  C--   Under a messaging mode we "receive" the message.  C--   Under a messaging mode we "receive" the message.
94  C--   Under a "get" scenario we  C--   Under a "get" scenario we
# Line 84  C--     i. Check that the data is ready. Line 96  C--     i. Check that the data is ready.
96  C--    ii. Read the data.  C--    ii. Read the data.
97  C--   iii. Set data read flag + memory sync.  C--   iii. Set data read flag + memory sync.
98    
   
       DO bj=myByLo(myThid),myByHi(myThid)  
        DO bi=myBxLo(myThid),myBxHi(myThid)  
         ebL = exchangeBufLevel(1,bi,bj)  
         southCommMode  = _tileCommModeS(bi,bj)  
         northCommMode  = _tileCommModeN(bi,bj)  
         biN =  _tileBiN(bi,bj)  
         bjN =  _tileBjN(bi,bj)  
         biS =  _tileBiS(bi,bj)  
         bjS =  _tileBjS(bi,bj)  
         IF ( southCommMode .EQ. COMM_MSG ) THEN  
99  #ifdef ALLOW_USE_MPI  #ifdef ALLOW_USE_MPI
100  #ifndef ALWAYS_USE_MPI  #ifndef ALWAYS_USE_MPI
101           IF ( usingMPI ) THEN        IF ( usingMPI ) THEN
102  #endif  #endif
103    C--   Receive buffer data: Only Master Thread do proc communication
104          _BEGIN_MASTER(myThid)
105    
106          DO bj=1,nSy
107           DO bi=1,nSx
108            eBl = exchangeBufLevel(1,bi,bj)
109            southCommMode = _tileCommModeS(bi,bj)
110            northCommMode = _tileCommModeN(bi,bj)
111            biN = _tileBiN(bi,bj)
112            bjN = _tileBjN(bi,bj)
113            biS = _tileBiS(bi,bj)
114            bjS = _tileBjS(bi,bj)
115            theType = _MPI_TYPE_RX
116            theSize = sNx*exchWidthY*myNz
117            IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS ) THEN
118              theSize = (sNx+2*exchWidthX)*exchWidthY*myNz
119            ENDIF
120    
121            IF ( southCommMode .EQ. COMM_MSG ) THEN
122           theProc = tilePidS(bi,bj)           theProc = tilePidS(bi,bj)
123           theTag  = _tileTagRecvS(bi,bj)           theTag  = _tileTagRecvS(bi,bj)
124           theType = MPI_DOUBLE_PRECISION  # ifndef ALLOW_AUTODIFF_OPENAD_AMPI
125           theSize = sNx*exchWidthY*myNz           CALL MPI_Recv( southRecvBuf_RX(1,eBl,bi,bj), theSize,
126           IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS )       &                  theType, theProc, theTag, MPI_COMM_MODEL,
      &    theSize = (sNx+2*exchWidthX)*exchWidthY*myNz  
          CALL MPI_Recv( southRecvBuf_RX(1,eBl,bi,bj), theSize, theType,  
      &                  theProc, theTag, MPI_COMM_MODEL,  
127       &                  mpiStatus, mpiRc )       &                  mpiStatus, mpiRc )
128  #ifndef ALWAYS_USE_MPI  # else
129          ENDIF                           pReqI=exchNReqsY(1,bi,bj)+1
130  #endif           CALL ampi_recv_RX(
131  #endif /* ALLOW_USE_MPI */       &        southRecvBuf_RX(1,eBl,bi,bj) ,
132         &        theSize ,
133         &        theType ,
134         &        theProc ,
135         &        theTag ,
136         &        MPI_COMM_MODEL ,
137         &        exchReqIdY(pReqI,1,bi,bj),
138         &        exchNReqsY(1,bi,bj),
139         &        mpiStatus ,
140         &        mpiRc )
141    # endif /* ALLOW_AUTODIFF_OPENAD_AMPI */
142             southRecvAck(eBl,bi,bj) = 1
143          ENDIF          ENDIF
144    
145          IF ( northCommMode .EQ. COMM_MSG ) THEN          IF ( northCommMode .EQ. COMM_MSG ) THEN
 #ifdef ALLOW_USE_MPI  
 #ifndef ALWAYS_USE_MPI  
          IF ( usingMPI ) THEN  
 #endif  
146           theProc = tilePidN(bi,bj)           theProc = tilePidN(bi,bj)
147           theTag  = _tileTagRecvN(bi,bj)           theTag  = _tileTagRecvN(bi,bj)
148           theType = MPI_DOUBLE_PRECISION  # ifndef ALLOW_AUTODIFF_OPENAD_AMPI
149           theSize = sNx*exchWidthY*myNz           CALL MPI_Recv( northRecvBuf_RX(1,eBl,bi,bj), theSize,
150           IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS )       &                  theType, theProc, theTag, MPI_COMM_MODEL,
      &    theSize = (sNx+2*exchWidthX)*exchWidthY*myNz  
          CALL MPI_Recv( northRecvBuf_RX(1,eBl,bi,bj), theSize, theType,  
      &                  theProc, theTag, MPI_COMM_MODEL,  
151       &                  mpiStatus, mpiRc )       &                  mpiStatus, mpiRc )
152  #ifndef ALWAYS_USE_MPI  # else
153          ENDIF                           pReqI=exchNReqsY(1,bi,bj)+1
154  #endif           CALL ampi_recv_RX(
155  #endif /* ALLOW_USE_MPI */       &        northRecvBuf_RX(1,eBl,bi,bj) ,
156         &        theSize ,
157         &        theType ,
158         &        theProc ,
159         &        theTag ,
160         &        MPI_COMM_MODEL ,
161         &        exchReqIdY(pReqI,1,bi,bj),
162         &        exchNReqsY(1,bi,bj),
163         &        mpiStatus ,
164         &        mpiRc )
165    # endif /* ALLOW_AUTODIFF_OPENAD_AMPI */
166             northRecvAck(eBl,bi,bj) = 1
167          ENDIF          ENDIF
168         ENDDO         ENDDO
169        ENDDO        ENDDO
170    
171  C--   Wait for buffers I am going read to be ready.  C--   Processes wait for buffers I am going to read to be ready.
172          IF ( .NOT.exchUsesBarrier  ) THEN
173           DO bj=1,nSy
174            DO bi=1,nSx
175             IF ( exchNReqsY(1,bi,bj) .GT. 0 ) THEN
176    # ifndef ALLOW_AUTODIFF_OPENAD_AMPI
177              CALL MPI_Waitall( exchNReqsY(1,bi,bj), exchReqIdY(1,1,bi,bj),
178         &                      mpiStatus, mpiRC )
179    # else
180              CALL ampi_waitall(
181         &         exchNReqsY(1,bi,bj),
182         &         exchReqIdY(1,1,bi,bj),
183         &         mpiStatus,
184         &         mpiRC )
185    # endif /* ALLOW_AUTODIFF_OPENAD_AMPI */
186             ENDIF
187    C        Clear outstanding requests counter
188             exchNReqsY(1,bi,bj) = 0
189            ENDDO
190           ENDDO
191          ENDIF
192    
193          _END_MASTER(myThid)
194    C--   need to sync threads after master has received data ;
195    C     (done after mpi waitall in case waitall is really needed)
196          _BARRIER
197    
198    #ifndef ALWAYS_USE_MPI
199          ENDIF
200    #endif
201    #endif /* ALLOW_USE_MPI */
202    
203    C--   Threads wait for buffers I am going to read to be ready.
204    C     note: added BARRIER in exch_send_put S/R and here above (message mode)
205    C           so that we no longer needs this (undef EXCH_USE_SPINNING)
206    #ifdef EXCH_USE_SPINNING
207        IF ( exchUsesBarrier  ) THEN        IF ( exchUsesBarrier  ) THEN
208  C      o On some machines ( T90 ) use system barrier rather than spinning.  C      o On some machines ( T90 ) use system barrier rather than spinning.
209         CALL BARRIER( myThid )         CALL BARRIER( myThid )
# Line 144  C      o Spin waiting for completetion f Line 212  C      o Spin waiting for completetion f
212  C        i.e. we only lock waiting for data that we need.  C        i.e. we only lock waiting for data that we need.
213         DO bj=myByLo(myThid),myByHi(myThid)         DO bj=myByLo(myThid),myByHi(myThid)
214          DO bi=myBxLo(myThid),myBxHi(myThid)          DO bi=myBxLo(myThid),myBxHi(myThid)
215           ebL = exchangeBufLevel(1,bi,bj)  
216             spinCount = 0
217             eBl = exchangeBufLevel(1,bi,bj)
218           southCommMode = _tileCommModeS(bi,bj)           southCommMode = _tileCommModeS(bi,bj)
219           northCommMode = _tileCommModeN(bi,bj)           northCommMode = _tileCommModeN(bi,bj)
220           spinCount = 0  # ifndef ALLOW_AUTODIFF_OPENAD_AMPI
221     10    CONTINUE     10    CONTINUE
222            CALL FOOL_THE_COMPILER            CALL FOOL_THE_COMPILER( spinCount )
223            spinCount = spinCount+1            spinCount = spinCount+1
224  C         IF ( myThid .EQ. 1 .AND. spinCount .GT. _EXCH_SPIN_LIMIT ) THEN  C         IF ( myThid .EQ. 1 .AND. spinCount .GT. _EXCH_SPIN_LIMIT ) THEN
225  C          STOP ' S/R EXCH_RECV_GET_Y: spinCount .GT. _EXCH_SPIN_LIMIT'  C          STOP ' S/R EXCH_RECV_GET_Y: spinCount .GT. _EXCH_SPIN_LIMIT'
226  C         ENDIF  C         ENDIF
227            IF ( southRecvAck(eBl,bi,bj) .EQ. 0. ) GOTO 10            IF ( southRecvAck(eBl,bi,bj) .EQ. 0 ) GOTO 10
228            IF ( northRecvAck(eBl,bi,bj) .EQ. 0. ) GOTO 10            IF ( northRecvAck(eBl,bi,bj) .EQ. 0 ) GOTO 10
229    # else
230             DO WHILE ((southRecvAck(eBl,bi,bj) .EQ. 0
231         &             .OR.
232         &              northRecvAck(eBl,bi,bj) .EQ. 0 ))
233              CALL FOOL_THE_COMPILER( spinCount )
234              spinCount = spinCount+1
235             ENDDO
236    # endif /* ALLOW_AUTODIFF_OPENAD_AMPI */
237  C        Clear requests  C        Clear requests
238           southRecvAck(eBl,bi,bj) = 0.           southRecvAck(eBl,bi,bj) = 0
239           northRecvAck(eBl,bi,bj) = 0.           northRecvAck(eBl,bi,bj) = 0
240  C        Update statistics  C        Update statistics
241           IF ( exchCollectStatistics ) THEN           IF ( exchCollectStatistics ) THEN
242            exchRecvYExchCount(1,bi,bj) = exchRecvYExchCount(1,bi,bj)+1            exchRecvYExchCount(1,bi,bj) = exchRecvYExchCount(1,bi,bj)+1
243            exchRecvYSpinCount(1,bi,bj) =            exchRecvYSpinCount(1,bi,bj) =
244       &    exchRecvYSpinCount(1,bi,bj)+spinCount       &    exchRecvYSpinCount(1,bi,bj)+spinCount
245            exchRecvYSpinMax(1,bi,bj) =            exchRecvYSpinMax(1,bi,bj) =
246       &    MAX(exchRecvYSpinMax(1,bi,bj),spinCount)       &    MAX(exchRecvYSpinMax(1,bi,bj),spinCount)
247            exchRecvYSpinMin(1,bi,bj) =            exchRecvYSpinMin(1,bi,bj) =
248       &    MIN(exchRecvYSpinMin(1,bi,bj),spinCount)       &    MIN(exchRecvYSpinMin(1,bi,bj),spinCount)
249           ENDIF           ENDIF
250    
   
          IF ( exchNReqsY(1,bi,bj) .GT. 0 ) THEN  
 #ifdef ALLOW_USE_MPI  
 #ifndef ALWAYS_USE_MPI  
          IF ( usingMPI ) THEN  
 #endif  
           CALL MPI_Waitall( exchNReqsY(1,bi,bj), exchReqIdY(1,1,bi,bj),  
      &                      mpiStatus, mpiRC )  
 #ifndef ALWAYS_USE_MPI  
         ENDIF                  
 #endif  
 #endif /* ALLOW_USE_MPI */  
          ENDIF  
 C        Clear outstanding requests counter  
          exchNReqsY(1,bi,bj) = 0  
251          ENDDO          ENDDO
252         ENDDO         ENDDO
253        ENDIF        ENDIF
254    #endif /* EXCH_USE_SPINNING */
255    
256    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
257    
258  C--   Read from the buffers  C--   Read from the buffers
259        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
260         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
261    
262          ebL = exchangeBufLevel(1,bi,bj)          eBl = exchangeBufLevel(1,bi,bj)
263          biN =  _tileBiN(bi,bj)          biN = _tileBiN(bi,bj)
264          bjN =  _tileBjN(bi,bj)          bjN = _tileBjN(bi,bj)
265          biS =  _tileBiS(bi,bj)          biS = _tileBiS(bi,bj)
266          bjS =  _tileBjS(bi,bj)          bjS = _tileBjS(bi,bj)
267          southCommMode = _tileCommModeS(bi,bj)          southCommMode = _tileCommModeS(bi,bj)
268          northCommMode = _tileCommModeN(bi,bj)          northCommMode = _tileCommModeN(bi,bj)
269          IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS ) THEN          IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS ) THEN
# Line 211  C--   Read from the buffers Line 277  C--   Read from the buffers
277           jMin = sNy+1           jMin = sNy+1
278           jMax = sNy+exchWidthY           jMax = sNy+exchWidthY
279           iB0  = 0           iB0  = 0
280           IF (  northCommMode .EQ. COMM_PUT           IF (     northCommMode .EQ. COMM_PUT
281       &        .OR. northCommMode .EQ. COMM_MSG  ) THEN       &       .OR. northCommMode .EQ. COMM_MSG  ) THEN
282            iB  = 0            iB  = 0
283            DO K=1,myNz            DO k=1,myNz
284             DO J=jMin,jMax             DO j=jMin,jMax
285              DO I=iMin,iMax              DO i=iMin,iMax
286               iB = iB + 1               iB = iB + 1
287               array(I,J,K,bi,bj) = northRecvBuf_RX(iB,eBl,bi,bj)               array(i,j,k,bi,bj) = northRecvBuf_RX(iB,eBl,bi,bj)
288              ENDDO              ENDDO
289             ENDDO             ENDDO
290            ENDDO            ENDDO
291           ELSEIF ( northCommMode .EQ. COMM_GET ) THEN           ELSEIF ( northCommMode .EQ. COMM_GET ) THEN
292            DO K=1,myNz            DO k=1,myNz
293             iB = iB0             iB = iB0
294             DO J=jMin,jMax             DO j=jMin,jMax
295              iB = iB+1              iB = iB+1
296              DO I=iMin,iMax              DO i=iMin,iMax
297               array(I,J,K,bi,bj) = array(I,iB,K,biN,bjN)               array(i,j,k,bi,bj) = array(i,iB,k,biN,bjN)
298              ENDDO              ENDDO
299             ENDDO             ENDDO
300            ENDDO            ENDDO
# Line 237  C--   Read from the buffers Line 303  C--   Read from the buffers
303           jMin = sNy-exchWidthY+1           jMin = sNy-exchWidthY+1
304           jMax = sNy           jMax = sNy
305           iB0  = 1-exchWidthY-1           iB0  = 1-exchWidthY-1
306           IF (  northCommMode .EQ. COMM_PUT           IF (     northCommMode .EQ. COMM_PUT
307       &        .OR. northCommMode .EQ. COMM_MSG  ) THEN       &       .OR. northCommMode .EQ. COMM_MSG  ) THEN
308            iB  = 0            iB  = 0
309            DO K=1,myNz            DO k=1,myNz
310             DO J=jMin,jMax             DO j=jMin,jMax
311              DO I=iMin,iMax              DO i=iMin,iMax
312               iB = iB + 1               iB = iB + 1
313               array(I,J,K,bi,bj) =               array(i,j,k,bi,bj) =
314       &       array(I,J,K,bi,bj)+northRecvBuf_RX(iB,eBl,bi,bj)       &       array(i,j,k,bi,bj) + northRecvBuf_RX(iB,eBl,bi,bj)
315              ENDDO              ENDDO
316             ENDDO             ENDDO
317            ENDDO            ENDDO
318           ELSEIF ( northCommMode .EQ. COMM_GET ) THEN           ELSEIF ( northCommMode .EQ. COMM_GET ) THEN
319            DO K=1,myNz            DO k=1,myNz
320             iB = iB0             iB = iB0
321             DO J=jMin,jMax             DO j=jMin,jMax
322              iB = iB+1              iB = iB+1
323              DO I=iMin,iMax              DO i=iMin,iMax
324               array(I,J,K,bi,bj) =               array(i,j,k,bi,bj) =
325       &       array(I,J,K,bi,bj)+array(I,iB,K,biN,bjN)       &       array(i,j,k,bi,bj) + array(i,iB,k,biN,bjN)
326                 array(i,iB,k,biN,bjN) = 0.0
327              ENDDO              ENDDO
328             ENDDO             ENDDO
329            ENDDO            ENDDO
# Line 267  C--   Read from the buffers Line 334  C--   Read from the buffers
334           jMin = 1-exchWidthY           jMin = 1-exchWidthY
335           jMax = 0           jMax = 0
336           iB0  = sNy-exchWidthY           iB0  = sNy-exchWidthY
337           IF (      southCommMode .EQ. COMM_PUT           IF (     southCommMode .EQ. COMM_PUT
338       &        .OR. southCommMode .EQ. COMM_MSG ) THEN       &       .OR. southCommMode .EQ. COMM_MSG ) THEN
339            iB  = 0            iB  = 0
340            DO K=1,myNz            DO k=1,myNz
341             DO J=jMin,jMax             DO j=jMin,jMax
342              DO I=iMin,iMax              DO i=iMin,iMax
343               iB = iB + 1               iB = iB + 1
344               array(I,J,K,bi,bj) = southRecvBuf_RX(iB,eBl,bi,bj)               array(i,j,k,bi,bj) = southRecvBuf_RX(iB,eBl,bi,bj)
345              ENDDO              ENDDO
346             ENDDO             ENDDO
347            ENDDO            ENDDO
348           ELSEIF ( southCommMode .EQ. COMM_GET ) THEN           ELSEIF ( southCommMode .EQ. COMM_GET ) THEN
349            DO K=1,myNz            DO k=1,myNz
350             iB = iB0             iB = iB0
351             DO J=jMin,jMax             DO j=jMin,jMax
352              iB = iB+1              iB = iB+1
353              DO I=iMin,iMax              DO i=iMin,iMax
354               array(I,J,K,bi,bj) = array(I,iB,K,biS,bjS)               array(i,j,k,bi,bj) = array(i,iB,k,biS,bjS)
355              ENDDO              ENDDO
356             ENDDO             ENDDO
357            ENDDO            ENDDO
# Line 293  C--   Read from the buffers Line 360  C--   Read from the buffers
360           jMin = 1           jMin = 1
361           jMax = 1+exchWidthY-1           jMax = 1+exchWidthY-1
362           iB0  = sNy           iB0  = sNy
363           IF (      southCommMode .EQ. COMM_PUT           IF (     southCommMode .EQ. COMM_PUT
364       &        .OR. southCommMode .EQ. COMM_MSG ) THEN       &       .OR. southCommMode .EQ. COMM_MSG ) THEN
365            iB  = 0            iB  = 0
366            DO K=1,myNz            DO k=1,myNz
367             DO J=jMin,jMax             DO j=jMin,jMax
368              DO I=iMin,iMax              DO i=iMin,iMax
369               iB = iB + 1               iB = iB + 1
370               array(I,J,K,bi,bj) =               array(i,j,k,bi,bj) =
371       &       array(I,J,K,bi,bj)+southRecvBuf_RX(iB,eBl,bi,bj)       &       array(i,j,k,bi,bj) + southRecvBuf_RX(iB,eBl,bi,bj)
372              ENDDO              ENDDO
373             ENDDO             ENDDO
374            ENDDO            ENDDO
375           ELSEIF ( southCommMode .EQ. COMM_GET ) THEN           ELSEIF ( southCommMode .EQ. COMM_GET ) THEN
376            DO K=1,myNz            DO k=1,myNz
377             iB = iB0             iB = iB0
378             DO J=jMin,jMax             DO j=jMin,jMax
379              iB = iB+1              iB = iB+1
380              DO I=iMin,iMax              DO i=iMin,iMax
381               array(I,J,K,bi,bj) =               array(i,j,k,bi,bj) =
382       &       array(I,J,K,bi,bj)+array(I,iB,K,biS,bjS)       &       array(i,j,k,bi,bj) + array(i,iB,k,biS,bjS)
383                 array(i,iB,k,biS,bjS) = 0.0
384              ENDDO              ENDDO
385             ENDDO             ENDDO
386            ENDDO            ENDDO
387           ENDIF           ENDIF
388          ENDIF          ENDIF
389    
390         ENDDO         ENDDO
391        ENDDO        ENDDO
392    

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

  ViewVC Help
Powered by ViewVC 1.1.22