/[MITgcm]/MITgcm/pkg/flt/exch_recv_get_vec.F
ViewVC logotype

Annotation of /MITgcm/pkg/flt/exch_recv_get_vec.F

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


Revision 1.8 - (hide annotations) (download)
Wed Aug 31 21:35:11 2011 UTC (12 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63g, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63c
Changes since 1.7: +75 -39 lines
make FLT EXCH working with multi-threads (and MPI + multi-threads)

1 jmc 1.8 C $Header: /u/gcmpack/MITgcm/pkg/flt/exch_recv_get_vec.F,v 1.7 2009/08/04 16:14:09 jmc Exp $
2 jmc 1.2 C $Name: $
3    
4 jmc 1.5 #include "CPP_EEOPTIONS.h"
5 jmc 1.8 #undef EXCH_USE_SPINNING
6 jmc 1.5 #undef DBUG_EXCH_VEC
7 jmc 1.3
8     C-- Contents
9     C-- o EXCH_RL_RECV_GET_VEC_X
10     C-- o EXCH_RL_RECV_GET_VEC_Y
11    
12     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
13 jmc 1.5 CBOP 0
14     C !ROUTINE: EXCH_RL_RECV_GET_VEC_X
15 adcroft 1.1
16 jmc 1.5 C !INTERFACE:
17 jmc 1.4 SUBROUTINE EXCH_RL_RECV_GET_VEC_X(
18     U arrayE, arrayW,
19     I myd1, myThid )
20 jmc 1.5 C !DESCRIPTION:
21     C *==========================================================*
22     C | SUBROUTINE EXCH_RL_RECV_GET_VEC_X
23     C | o "Receive" or "Get" X edges for RL array.
24     C *==========================================================*
25     C | Routine that invokes actual message passing receive
26     C | of data to update buffer in X direction
27     C *==========================================================*
28    
29     C !USES:
30 adcroft 1.1 IMPLICIT NONE
31    
32     C == Global variables ==
33     #include "SIZE.h"
34     #include "EEPARAMS.h"
35     #include "EESUPPORT.h"
36     #include "EXCH.h"
37    
38 jmc 1.5 C !INPUT/OUTPUT PARAMETERS:
39     C arrayE :: buffer array to collect Eastern Neighbour values
40     C arrayW :: buffer array to collect Western Neighbour values
41     C myd1 :: size
42     C myThid :: my Thread Id. number
43 adcroft 1.1 INTEGER myd1
44     _RL arrayE(myd1, nSx, nSy), arrayW(myd1, nSx, nSy)
45     INTEGER myThid
46 jmc 1.5 CEOP
47 adcroft 1.1
48 jmc 1.5 C !LOCAL VARIABLES:
49     C bi, bj :: tile indices
50     C biW, bjW :: West tile indices
51     C biE, bjE :: East tile indices
52 cnh 1.6 C theProc :: Variables used in message building
53     C theTag :: Variables used in message building
54     C theType :: Variables used in message building
55     C theSize :: Variables used in message building
56 jmc 1.5 C westCommMode :: variables holding type of communication
57     C eastCommMode :: a particular tile face uses.
58 jmc 1.4 INTEGER bi, bj
59     c INTEGER biW, bjW, biE, bjE
60 adcroft 1.1 INTEGER westCommMode
61     INTEGER eastCommMode
62     INTEGER spinCount
63 jmc 1.5 INTEGER ioUnit
64 adcroft 1.1 #ifdef ALLOW_USE_MPI
65     INTEGER theProc, theTag, theType, theSize
66     INTEGER mpiStatus(MPI_STATUS_SIZE,4), mpiRc
67     #endif
68    
69 jmc 1.2 C-- Under a "put" scenario we
70 adcroft 1.1 C-- i. set completetion signal for buffer we put into.
71 jmc 1.2 C-- ii. wait for completetion signal indicating data has been put in
72 adcroft 1.1 C-- our buffer.
73     C-- Under a messaging mode we "receive" the message.
74 jmc 1.5 C-- Under a "get" scenario <= not implemented, we
75 adcroft 1.1 C-- i. Check that the data is ready.
76     C-- ii. Read the data.
77     C-- iii. Set data read flag + memory sync.
78    
79 jmc 1.5 ioUnit = errorMessageUnit
80 adcroft 1.1
81 jmc 1.8 _BEGIN_MASTER(myThid)
82    
83     DO bj=1,nSy
84     DO bi=1,nSx
85 adcroft 1.1 westCommMode = _tileCommModeW(bi,bj)
86     eastCommMode = _tileCommModeE(bi,bj)
87 jmc 1.5 #ifdef DBUG_EXCH_VEC
88     write(ioUnit,'(A,5I6)') 'RECV_X,0 :',myProcId,bi,bj
89     #endif
90 jmc 1.4 c biE = _tileBiE(bi,bj)
91     c bjE = _tileBjE(bi,bj)
92     c biW = _tileBiW(bi,bj)
93     c bjW = _tileBjW(bi,bj)
94 adcroft 1.1 IF ( westCommMode .EQ. COMM_MSG ) THEN
95     #ifdef ALLOW_USE_MPI
96     #ifndef ALWAYS_USE_MPI
97     IF ( usingMPI ) THEN
98     #endif
99     theProc = tilePidW(bi,bj)
100     theTag = _tileTagRecvW(bi,bj)
101 jmc 1.5 theType = _MPI_TYPE_RL
102 adcroft 1.1 theSize = myd1
103 jmc 1.5 #ifdef DBUG_EXCH_VEC
104     write(ioUnit,'(A,5I5,I8)') 'qq2xW: ',myProcId,bi,bj,
105     & theProc,theTag,theSize
106     #endif
107 adcroft 1.1 CALL MPI_Recv( arrayW(1,bi,bj), theSize, theType,
108     & theProc, theTag, MPI_COMM_MODEL,
109     & mpiStatus, mpiRc )
110     c if (theProc .eq. 0 .or. theProc .eq. 2) then
111     c if (arrayW(1,bi,bj) .ne. 0.) then
112 jmc 1.5 c write(errormessageunit,*) 'qq2y: ',myProcId,
113 adcroft 1.1 c & theProc,theTag,theSize,(arrayW(i,bi,bj),i=1,32)
114     c else
115 jmc 1.5 c write(errormessageunit,*) 'qq2n: ',myProcId,
116 adcroft 1.1 c & theProc,theTag,theSize,(arrayW(i,bi,bj),i=1,32)
117     c endif
118     c endif
119     #ifndef ALWAYS_USE_MPI
120 jmc 1.5 ENDIF
121 adcroft 1.1 #endif
122     #endif /* ALLOW_USE_MPI */
123     ENDIF
124 jmc 1.5 #ifdef DBUG_EXCH_VEC
125     write(ioUnit,'(A,5I6)') 'RECV_X,1 :',myProcId,bi,bj
126     #endif
127 adcroft 1.1 IF ( eastCommMode .EQ. COMM_MSG ) THEN
128     #ifdef ALLOW_USE_MPI
129     #ifndef ALWAYS_USE_MPI
130     IF ( usingMPI ) THEN
131     #endif
132     theProc = tilePidE(bi,bj)
133     theTag = _tileTagRecvE(bi,bj)
134 jmc 1.5 theType = _MPI_TYPE_RL
135 adcroft 1.1 theSize = myd1
136 jmc 1.5 #ifdef DBUG_EXCH_VEC
137     write(ioUnit,'(A,5I5,I8)') 'qq2xE: ',myProcId,bi,bj,
138     & theProc,theTag,theSize
139     #endif
140 adcroft 1.1 CALL MPI_Recv( arrayE(1,bi,bj), theSize, theType,
141     & theProc, theTag, MPI_COMM_MODEL,
142     & mpiStatus, mpiRc )
143     #ifndef ALWAYS_USE_MPI
144 jmc 1.5 ENDIF
145 adcroft 1.1 #endif
146     #endif /* ALLOW_USE_MPI */
147     ENDIF
148 jmc 1.5 #ifdef DBUG_EXCH_VEC
149     write(ioUnit,'(A,5I6)') 'RECV_X,2 :',myProcId,bi,bj
150     #endif
151 adcroft 1.1 ENDDO
152     ENDDO
153 jmc 1.5 #ifdef DBUG_EXCH_VEC
154     write(ioUnit,'(A,5I6,I12)') 'RECV_X:',myProcId
155     #endif
156 adcroft 1.1
157 jmc 1.8 IF ( .NOT.exchUsesBarrier ) THEN
158     DO bj=1,nSy
159     DO bi=1,nSx
160     IF ( exchNReqsX(1,bi,bj) .GT. 0 ) THEN
161     #ifdef ALLOW_USE_MPI
162     #ifndef ALWAYS_USE_MPI
163     IF ( usingMPI ) THEN
164     #endif
165     CALL MPI_Waitall( exchNReqsX(1,bi,bj), exchReqIdX(1,1,bi,bj),
166     & mpiStatus, mpiRC )
167     #ifndef ALWAYS_USE_MPI
168     ENDIF
169     #endif
170     #endif /* ALLOW_USE_MPI */
171     ENDIF
172     C Clear outstanding requests counter
173     exchNReqsX(1,bi,bj) = 0
174     ENDDO
175     ENDDO
176     ENDIF
177    
178     _END_MASTER(myThid)
179    
180     C-- need to sync threads after master has received data ;
181     C (done after mpi waitall in case waitall is really needed)
182     _BARRIER
183    
184     C-- Threads wait for buffers I am going to read to be ready.
185     C note: added BARRIER in exch_send_put S/R and here above (message
186     C mode) so that we no longer needs this (undef EXCH_USE_SPINNING)
187     #ifdef EXCH_USE_SPINNING
188 adcroft 1.1 IF ( exchUsesBarrier ) THEN
189     C o On some machines ( T90 ) use system barrier rather than spinning.
190     CALL BARRIER( myThid )
191     ELSE
192     C o Spin waiting for completetion flag. This avoids a global-lock
193     C i.e. we only lock waiting for data that we need.
194     DO bj=myByLo(myThid),myByHi(myThid)
195     DO bi=myBxLo(myThid),myBxHi(myThid)
196     spinCount = 0
197     westCommMode = _tileCommModeW(bi,bj)
198     eastCommMode = _tileCommModeE(bi,bj)
199 jmc 1.5 #ifdef DBUG_EXCH_VEC
200     write(ioUnit,'(A,5I6,I12)') 'spin:', myProcId,bi,bj,
201     & westRecvAck(1,bi,bj), eastRecvAck(1,bi,bj), spinCount
202     #endif
203 adcroft 1.1 10 CONTINUE
204 jmc 1.7 CALL FOOL_THE_COMPILER( spinCount )
205 adcroft 1.1 spinCount = spinCount+1
206 jmc 1.5 #ifdef DBUG_EXCH_VEC
207     write(ioUnit,'(A,5I6,I12)') 'spin:', myProcId,bi,bj,
208     & westRecvAck(1,bi,bj), eastRecvAck(1,bi,bj), spinCount
209     IF ( myThid.EQ.1 .AND. spinCount.GT. _EXCH_SPIN_LIMIT ) THEN
210     STOP ' S/R EXCH_RECV_GET_X: spinCount > _EXCH_SPIN_LIMIT'
211     ENDIF
212     #endif
213     IF ( westRecvAck(1,bi,bj) .EQ. 0 ) GOTO 10
214     IF ( eastRecvAck(1,bi,bj) .EQ. 0 ) GOTO 10
215 adcroft 1.1 C Clear outstanding requests
216 jmc 1.5 westRecvAck(1,bi,bj) = 0
217     eastRecvAck(1,bi,bj) = 0
218 adcroft 1.1 ENDDO
219     ENDDO
220     ENDIF
221 jmc 1.8 #endif /* EXCH_USE_SPINNING */
222 adcroft 1.1
223     RETURN
224     END
225    
226 jmc 1.3 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
227 jmc 1.5 CBOP 0
228     C !ROUTINE: EXCH_RL_RECV_GET_VEC_Y
229 adcroft 1.1
230 jmc 1.5 C !INTERFACE:
231 jmc 1.4 SUBROUTINE EXCH_RL_RECV_GET_VEC_Y(
232     U arrayN, arrayS,
233     I myd1, myThid )
234 jmc 1.5 C !DESCRIPTION:
235     C *==========================================================*
236     C | SUBROUTINE EXCH_RL_RECV_GET_VEC_Y
237     C | o "Receive" or "Get" Y edges for RL array.
238     C *==========================================================*
239     C | Routine that invokes actual message passing receive
240     C | of data to update buffer in Y direction
241     C *==========================================================*
242    
243     C !USES:
244 adcroft 1.1 IMPLICIT NONE
245    
246     C == Global variables ==
247     #include "SIZE.h"
248     #include "EEPARAMS.h"
249     #include "EESUPPORT.h"
250     #include "EXCH.h"
251    
252 jmc 1.5 C !INPUT/OUTPUT PARAMETERS:
253     C arrayN :: buffer array to collect Northern Neighbour values
254     C arrayS :: buffer array to collect Southern Neighbour values
255     C myd1 :: size
256     C myThid :: my Thread Id. number
257 adcroft 1.1 INTEGER myd1
258     _RL arrayN(myd1, nSx, nSy), arrayS(myd1, nSx, nSy)
259     INTEGER myThid
260 jmc 1.5 CEOP
261 adcroft 1.1
262 jmc 1.5 C !LOCAL VARIABLES:
263     C bi, bj :: tile indices
264     C biS, bjS :: South tile indices
265     C biN, bjN :: North tile indices
266 cnh 1.6 C theProc :: Variables used in message building
267     C theTag :: Variables used in message building
268     C theType :: Variables used in message building
269     C theSize :: Variables used in message building
270 jmc 1.5 C southCommMode :: variables holding type of communication
271     C northCommMode :: a particular tile face uses.
272 jmc 1.4 INTEGER bi, bj
273     c INTEGER biS, bjS, biN, bjN
274 adcroft 1.1 INTEGER southCommMode
275     INTEGER northCommMode
276     INTEGER spinCount
277 jmc 1.5 INTEGER ioUnit
278 adcroft 1.1 #ifdef ALLOW_USE_MPI
279     INTEGER theProc, theTag, theType, theSize
280     INTEGER mpiStatus(MPI_STATUS_SIZE,4), mpiRc
281     #endif
282    
283 jmc 1.2 C-- Under a "put" scenario we
284 adcroft 1.1 C-- i. set completetion signal for buffer we put into.
285 jmc 1.2 C-- ii. wait for completetion signal indicating data has been put in
286 adcroft 1.1 C-- our buffer.
287     C-- Under a messaging mode we "receive" the message.
288 jmc 1.5 C-- Under a "get" scenario <= not implemented, we
289 adcroft 1.1 C-- i. Check that the data is ready.
290     C-- ii. Read the data.
291     C-- iii. Set data read flag + memory sync.
292    
293 jmc 1.5 ioUnit = errorMessageUnit
294 adcroft 1.1
295 jmc 1.8 _BEGIN_MASTER(myThid)
296    
297     DO bj=1,nSy
298     DO bi=1,nSx
299 adcroft 1.1 southCommMode = _tileCommModeS(bi,bj)
300     northCommMode = _tileCommModeN(bi,bj)
301 jmc 1.5 #ifdef DBUG_EXCH_VEC
302     write(ioUnit,'(A,5I6)') 'RECV_Y,0 :',myProcId,bi,bj
303     #endif
304 jmc 1.4 c biN = _tileBiN(bi,bj)
305     c bjN = _tileBjN(bi,bj)
306     c biS = _tileBiS(bi,bj)
307     c bjS = _tileBjS(bi,bj)
308 adcroft 1.1 IF ( southCommMode .EQ. COMM_MSG ) THEN
309     #ifdef ALLOW_USE_MPI
310     #ifndef ALWAYS_USE_MPI
311     IF ( usingMPI ) THEN
312     #endif
313     theProc = tilePidS(bi,bj)
314     theTag = _tileTagRecvS(bi,bj)
315 jmc 1.5 theType = _MPI_TYPE_RL
316 adcroft 1.1 theSize = myd1
317     CALL MPI_Recv( arrayS(1,bi,bj), theSize, theType,
318     & theProc, theTag, MPI_COMM_MODEL,
319     & mpiStatus, mpiRc )
320     #ifndef ALWAYS_USE_MPI
321 jmc 1.5 ENDIF
322 adcroft 1.1 #endif
323     #endif /* ALLOW_USE_MPI */
324     ENDIF
325 jmc 1.5 #ifdef DBUG_EXCH_VEC
326     write(ioUnit,'(A,5I6)') 'RECV_Y,1 :',myProcId,bi,bj
327     #endif
328 adcroft 1.1 IF ( northCommMode .EQ. COMM_MSG ) THEN
329     #ifdef ALLOW_USE_MPI
330     #ifndef ALWAYS_USE_MPI
331     IF ( usingMPI ) THEN
332     #endif
333     theProc = tilePidN(bi,bj)
334     theTag = _tileTagRecvN(bi,bj)
335 jmc 1.5 theType = _MPI_TYPE_RL
336 adcroft 1.1 theSize = myd1
337     CALL MPI_Recv( arrayN(1,bi,bj), theSize, theType,
338     & theProc, theTag, MPI_COMM_MODEL,
339     & mpiStatus, mpiRc )
340     #ifndef ALWAYS_USE_MPI
341 jmc 1.5 ENDIF
342 adcroft 1.1 #endif
343     #endif /* ALLOW_USE_MPI */
344     ENDIF
345 jmc 1.5 #ifdef DBUG_EXCH_VEC
346     write(ioUnit,'(A,5I6)') 'RECV_Y,2 :',myProcId,bi,bj
347     #endif
348 adcroft 1.1 ENDDO
349     ENDDO
350 jmc 1.5 #ifdef DBUG_EXCH_VEC
351     write(ioUnit,'(A,5I6,I12)') 'RECV_Y:',myProcId
352     #endif
353 adcroft 1.1
354 jmc 1.8 C-- Processes wait for buffers I am going to read to be ready.
355     IF ( .NOT.exchUsesBarrier ) THEN
356     DO bj=1,nSy
357     DO bi=1,nSx
358     IF ( exchNReqsY(1,bi,bj) .GT. 0 ) THEN
359     #ifdef ALLOW_USE_MPI
360     #ifndef ALWAYS_USE_MPI
361     IF ( usingMPI ) THEN
362     #endif
363     CALL MPI_Waitall( exchNReqsY(1,bi,bj), exchReqIdY(1,1,bi,bj),
364     & mpiStatus, mpiRC )
365     #ifndef ALWAYS_USE_MPI
366     ENDIF
367     #endif
368     #endif /* ALLOW_USE_MPI */
369     ENDIF
370     C Clear outstanding requests counter
371     exchNReqsY(1,bi,bj) = 0
372     ENDDO
373     ENDDO
374     ENDIF
375    
376     _END_MASTER(myThid)
377    
378     C-- need to sync threads after master has received data ;
379     C (done after mpi waitall in case waitall is really needed)
380     _BARRIER
381    
382     C-- Threads wait for buffers I am going to read to be ready.
383     C note: added BARRIER in exch_send_put S/R and here above (message
384     C mode) so that we no longer needs this (undef EXCH_USE_SPINNING)
385     #ifdef EXCH_USE_SPINNING
386 adcroft 1.1 IF ( exchUsesBarrier ) THEN
387     C o On some machines ( T90 ) use system barrier rather than spinning.
388     CALL BARRIER( myThid )
389     ELSE
390     C o Spin waiting for completetion flag. This avoids a global-lock
391     C i.e. we only lock waiting for data that we need.
392     DO bj=myByLo(myThid),myByHi(myThid)
393     DO bi=myBxLo(myThid),myBxHi(myThid)
394     spinCount = 0
395     southCommMode = _tileCommModeS(bi,bj)
396     northCommMode = _tileCommModeN(bi,bj)
397 jmc 1.5 #ifdef DBUG_EXCH_VEC
398     write(ioUnit,'(A,5I6,I12)') 'spin:', myProcId,bi,bj,
399     & southRecvAck(1,bi,bj), northRecvAck(1,bi,bj), spinCount
400     #endif
401 adcroft 1.1 10 CONTINUE
402 jmc 1.7 CALL FOOL_THE_COMPILER( spinCount )
403 adcroft 1.1 spinCount = spinCount+1
404 jmc 1.5 #ifdef DBUG_EXCH_VEC
405     write(ioUnit,'(A,5I6,I12)') 'spin:', myProcId,bi,bj,
406     & southRecvAck(1,bi,bj), northRecvAck(1,bi,bj), spinCount
407     IF ( myThid.EQ.1 .AND. spinCount.GT. _EXCH_SPIN_LIMIT ) THEN
408     STOP ' S/R EXCH_RECV_GET_X: spinCount > _EXCH_SPIN_LIMIT'
409     ENDIF
410     #endif
411     IF ( southRecvAck(1,bi,bj) .EQ. 0 ) GOTO 10
412     IF ( northRecvAck(1,bi,bj) .EQ. 0 ) GOTO 10
413 adcroft 1.1 C Clear outstanding requests
414 jmc 1.5 southRecvAck(1,bi,bj) = 0
415     northRecvAck(1,bi,bj) = 0
416 adcroft 1.1 ENDDO
417     ENDDO
418     ENDIF
419 jmc 1.8 #endif /* EXCH_USE_SPINNING */
420 adcroft 1.1
421     RETURN
422     END

  ViewVC Help
Powered by ViewVC 1.1.22