/[MITgcm]/MITgcm/eesupp/src/exch_recv_get_y.F
ViewVC logotype

Annotation of /MITgcm/eesupp/src/exch_recv_get_y.F

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


Revision 1.1 - (hide annotations) (download)
Tue Sep 29 18:53:45 1998 UTC (25 years, 7 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint15
CHanges to exchange routines for general tile <-> tile connectivity, DMA and shared
memory communication hooks, variable width overlaps and TAMC reverse mode flag.

1 cnh 1.1 C $Header: $
2     #include "CPP_EEOPTIONS.h"
3    
4     SUBROUTINE EXCH_RL_RECV_GET_Y( array,
5     I myOLw, myOLe, myOLs, myOLn, myNz,
6     I exchWidthX, exchWidthY,
7     I theSimulationMode, theCornerMode, myThid )
8     C /==========================================================\
9     C | SUBROUTINE RECV_GET_Y |
10     C | o "Send" or "put" Y edges for RL array. |
11     C |==========================================================|
12     C | Routine that invokes actual message passing send or |
13     C | direct "put" of data to update X faces of an XY[R] array.|
14     C \==========================================================/
15     IMPLICIT NONE
16    
17     C == Global variables ==
18     #include "SIZE.h"
19     #include "EEPARAMS.h"
20     #include "EESUPPORT.h"
21     #include "EXCH.h"
22    
23     C == Routine arguments ==
24     C array - Array with edges to exchange.
25     C myOLw - West, East, North and South overlap region sizes.
26     C myOLe
27     C myOLn
28     C myOLs
29     C exchWidthX - Width of data region exchanged.
30     C exchWidthY
31     C theSimulationMode - Forward or reverse mode exchange ( provides
32     C support for adjoint integration of code. )
33     C theCornerMode - Flag indicating whether corner updates are
34     C needed.
35     C myThid - Thread number of this instance of S/R EXCH...
36     C eBl - Edge buffer level
37     INTEGER myOLw
38     INTEGER myOLe
39     INTEGER myOLs
40     INTEGER myOLn
41     INTEGER myNz
42     _RL array(1-myOLw:sNx+myOLe,
43     & 1-myOLs:sNy+myOLn,
44     & myNZ, nSx, nSy)
45     INTEGER exchWidthX
46     INTEGER exchWidthY
47     INTEGER theSimulationMode
48     INTEGER theCornerMode
49     INTEGER myThid
50     CEndOfInterface
51    
52     C == Local variables ==
53     C I, J, K, iMin, iMax, iB - Loop counters and extents
54     C bi, bj
55     C biS, bjS - South tile indices
56     C biN, bjN - North tile indices
57     C eBl - Current exchange buffer level
58     C theProc, theTag, theType, - Variables used in message building
59     C theSize
60     C southCommMode - Working variables holding type
61     C northCommMode of communication a particular
62     C tile face uses.
63     C spinCount - Exchange statistics counter
64     INTEGER I, J, K, iMin, iMax, jMin, jMax, iB, iB0
65     INTEGER bi, bj, biS, bjS, biN, bjN
66     INTEGER eBl
67     INTEGER southCommMode
68     INTEGER northCommMode
69     INTEGER spinCount
70     #ifdef ALLOW_USE_MPI
71     INTEGER theProc, theTag, theType, theSize
72     INTEGER mpiStatus(MPI_STATUS_SIZE), mpiRc
73     #endif
74    
75    
76     C-- Under a "put" scenario we
77     C-- i. set completetion signal for buffer we put into.
78     C-- ii. wait for completetion signal indicating data has been put in
79     C-- our buffer.
80     C-- Under a messaging mode we "receive" the message.
81     C-- Under a "get" scenario we
82     C-- i. Check that the data is ready.
83     C-- ii. Read the data.
84     C-- iii. Set data read flag + memory sync.
85    
86    
87     DO bj=myByLo(myThid),myByHi(myThid)
88     DO bi=myBxLo(myThid),myBxHi(myThid)
89     ebL = exchangeBufLevel(1,bi,bj)
90     southCommMode = _tileCommModeS(bi,bj)
91     northCommMode = _tileCommModeN(bi,bj)
92     biN = _tileBiN(bi,bj)
93     bjN = _tileBjN(bi,bj)
94     biS = _tileBiS(bi,bj)
95     bjS = _tileBjS(bi,bj)
96     IF ( southCommMode .EQ. COMM_MSG ) THEN
97     #ifdef ALLOW_USE_MPI
98     #ifndef ALWAYS_USE_MPI
99     IF ( usingMPI ) THEN
100     #endif
101     theProc = tilePidS(bi,bj)
102     theTag = _tileTagRecvS(bi,bj)
103     theType = MPI_DOUBLE_PRECISION
104     theSize = sNx*exchWidthY*myNz
105     IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS )
106     & theSize = (sNx+2*exchWidthX)*exchWidthY*myNz
107     CALL MPI_Recv( southRecvBuf_RL(1,eBl,bi,bj), theSize, theType,
108     & theProc, theTag, MPI_COMM_WORLD,
109     & mpiStatus, mpiRc )
110     #ifndef ALWAYS_USE_MPI
111     ENDIF
112     #endif
113     #endif /* ALLOW_USE_MPI */
114     ENDIF
115     IF ( northCommMode .EQ. COMM_MSG ) THEN
116     #ifdef ALLOW_USE_MPI
117     #ifndef ALWAYS_USE_MPI
118     IF ( usingMPI ) THEN
119     #endif
120     theProc = tilePidN(bi,bj)
121     theTag = _tileTagRecvN(bi,bj)
122     theType = MPI_DOUBLE_PRECISION
123     theSize = sNx*exchWidthY*myNz
124     IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS )
125     & theSize = (sNx+2*exchWidthX)*exchWidthY*myNz
126     CALL MPI_Recv( northRecvBuf_RL(1,eBl,bi,bj), theSize, theType,
127     & theProc, theTag, MPI_COMM_WORLD,
128     & mpiStatus, mpiRc )
129     #ifndef ALWAYS_USE_MPI
130     ENDIF
131     #endif
132     #endif /* ALLOW_USE_MPI */
133     ENDIF
134     ENDDO
135     ENDDO
136    
137     C-- Wait for buffers I am going read to be ready.
138     IF ( exchUsesBarrier ) THEN
139     C o On some machines ( T90 ) use system barrier rather than spinning.
140     CALL BARRIER( myThid )
141     ELSE
142     C o Spin waiting for completetion flag. This avoids a global-lock
143     C i.e. we only lock waiting for data that we need.
144     DO bj=myByLo(myThid),myByHi(myThid)
145     DO bi=myBxLo(myThid),myBxHi(myThid)
146     ebL = exchangeBufLevel(1,bi,bj)
147     southCommMode = _tileCommModeS(bi,bj)
148     northCommMode = _tileCommModeN(bi,bj)
149     spinCount = 0
150     10 CONTINUE
151     CALL FOOL_THE_COMPILER
152     spinCount = spinCount+1
153     C IF ( myThid .EQ. 1 .AND. spinCount .GT. _EXCH_SPIN_LIMIT ) THEN
154     C STOP ' S/R EXCH_RECV_GET_Y: spinCount .GT. _EXCH_SPIN_LIMIT'
155     C ENDIF
156     IF ( southRecvAck(eBl,bi,bj) .EQ. 0. ) GOTO 10
157     IF ( northRecvAck(eBl,bi,bj) .EQ. 0. ) GOTO 10
158     C Clear requests
159     southRecvAck(eBl,bi,bj) = 0.
160     northRecvAck(eBl,bi,bj) = 0.
161     C Update statistics
162     IF ( exchCollectStatistics ) THEN
163     exchRecvYExchCount(1,bi,bj) = exchRecvYExchCount(1,bi,bj)+1
164     exchRecvYSpinCount(1,bi,bj) = exchRecvYSpinCount(1,bi,bj)+spinCount
165     exchRecvYSpinMax(1,bi,bj) = MAX(exchRecvYSpinMax(1,bi,bj),spinCount)
166     exchRecvYSpinMin(1,bi,bj) = MIN(exchRecvYSpinMin(1,bi,bj),spinCount)
167     ENDIF
168    
169    
170     IF ( exchNReqsY(1,bi,bj) .GT. 0 ) THEN
171     #ifdef ALLOW_USE_MPI
172     #ifndef ALWAYS_USE_MPI
173     IF ( usingMPI ) THEN
174     #endif
175     CALL MPI_Waitall( exchNReqsY(1,bi,bj), exchReqIdY(1,1,bi,bj),
176     & mpiStatus, mpiRC )
177     #ifndef ALWAYS_USE_MPI
178     ENDIF
179     #endif
180     #endif /* ALLOW_USE_MPI */
181     ENDIF
182     C Clear outstanding requests counter
183     exchNReqsY(1,bi,bj) = 0
184     ENDDO
185     ENDDO
186     ENDIF
187    
188     C-- Read from the buffers
189     DO bj=myByLo(myThid),myByHi(myThid)
190     DO bi=myBxLo(myThid),myBxHi(myThid)
191    
192     ebL = exchangeBufLevel(1,bi,bj)
193     biN = _tileBiN(bi,bj)
194     bjN = _tileBjN(bi,bj)
195     biS = _tileBiS(bi,bj)
196     bjS = _tileBjS(bi,bj)
197     southCommMode = _tileCommModeS(bi,bj)
198     northCommMode = _tileCommModeN(bi,bj)
199     IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS ) THEN
200     iMin = 1-exchWidthX
201     iMax = sNx+exchWidthX
202     ELSE
203     iMin = 1
204     iMax = sNx
205     ENDIF
206     IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
207     jMin = sNy+1
208     jMax = sNy+exchWidthY
209     iB0 = 0
210     ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
211     jMin = sNy-exchWidthY+1
212     jMax = sNy
213     iB0 = 1-exchWidthY-1
214     ENDIF
215     IF ( northCommMode .EQ. COMM_PUT
216     & .OR. northCommMode .EQ. COMM_MSG ) THEN
217     iB = 0
218     DO K=1,myNz
219     DO J=jMin,jMax
220     DO I=iMin,iMax
221     iB = iB + 1
222     array(I,J,K,bi,bj) = northRecvBuf_RL(iB,eBl,bi,bj)
223     ENDDO
224     ENDDO
225     ENDDO
226     ELSEIF ( northCommMode .EQ. COMM_GET ) THEN
227     DO K=1,myNz
228     iB = iB0
229     DO J=jMin,jMax
230     iB = iB+1
231     DO I=iMin,iMax
232     array(I,J,K,bi,bj) = array(I,iB,K,biN,bjN)
233     ENDDO
234     ENDDO
235     ENDDO
236     ENDIF
237     IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
238     jMin = 1-exchWidthY
239     jMax = 0
240     iB0 = sNy-exchWidthY
241     ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
242     jMin = 1
243     jMax = 1+exchWidthY-1
244     iB0 = sNy
245     ENDIF
246     IF ( southCommMode .EQ. COMM_PUT
247     & .OR. southCommMode .EQ. COMM_MSG ) THEN
248     iB = 0
249     DO K=1,myNz
250     DO J=jMin,jMax
251     DO I=iMin,iMax
252     iB = iB + 1
253     array(I,J,K,bi,bj) = southRecvBuf_RL(iB,eBl,bi,bj)
254     ENDDO
255     ENDDO
256     ENDDO
257     ELSEIF ( southCommMode .EQ. COMM_GET ) THEN
258     DO K=1,myNz
259     iB = iB0
260     DO J=jMin,jMax
261     iB = iB+1
262     DO I=iMin,iMax
263     array(I,J,K,bi,bj) = array(I,iB,K,biS,bjS)
264     ENDDO
265     ENDDO
266     ENDDO
267     ENDIF
268    
269     ENDDO
270     ENDDO
271    
272     RETURN
273     END
274    
275    
276     SUBROUTINE EXCH_RS_RECV_GET_Y( array,
277     I myOLw, myOLe, myOLs, myOLn, myNz,
278     I exchWidthX, exchWidthY,
279     I theSimulationMode, theCornerMode, myThid )
280     C /==========================================================\
281     C | SUBROUTINE RECV_GET_Y |
282     C | o "Send" or "put" Y edges for RS array. |
283     C |==========================================================|
284     C | Routine that invokes actual message passing send or |
285     C | direct "put" of data to update X faces of an XY[R] array.|
286     C \==========================================================/
287     IMPLICIT NONE
288    
289     C == Global variables ==
290     #include "SIZE.h"
291     #include "EEPARAMS.h"
292     #include "EESUPPORT.h"
293     #include "EXCH.h"
294    
295     C == Routine arguments ==
296     C array - Array with edges to exchange.
297     C myOLw - West, East, North and South overlap region sizes.
298     C myOLe
299     C myOLn
300     C myOLs
301     C exchWidthX - Width of data region exchanged.
302     C exchWidthY
303     C theSimulationMode - Forward or reverse mode exchange ( provides
304     C support for adjoint integration of code. )
305     C theCornerMode - Flag indicating whether corner updates are
306     C needed.
307     C myThid - Thread number of this instance of S/R EXCH...
308     C eBl - Edge buffer level
309     INTEGER myOLw
310     INTEGER myOLe
311     INTEGER myOLs
312     INTEGER myOLn
313     INTEGER myNz
314     _RS array(1-myOLw:sNx+myOLe,
315     & 1-myOLs:sNy+myOLn,
316     & myNZ, nSx, nSy)
317     INTEGER exchWidthX
318     INTEGER exchWidthY
319     INTEGER theSimulationMode
320     INTEGER theCornerMode
321     INTEGER myThid
322     CEndOfInterface
323    
324     C == Local variables ==
325     C I, J, K, iMin, iMax, iB - Loop counters and extents
326     C bi, bj
327     C biS, bjS - South tile indices
328     C biN, bjN - North tile indices
329     C eBl - Current exchange buffer level
330     C theProc, theTag, theType, - Variables used in message building
331     C theSize
332     C southCommMode - Working variables holding type
333     C northCommMode of communication a particular
334     C tile face uses.
335     C spinCount - Exchange statistics counter
336     INTEGER I, J, K, iMin, iMax, jMin, jMax, iB, iB0
337     INTEGER bi, bj, biS, bjS, biN, bjN
338     INTEGER eBl
339     INTEGER southCommMode
340     INTEGER northCommMode
341     INTEGER spinCount
342     #ifdef ALLOW_USE_MPI
343     INTEGER theProc, theTag, theType, theSize
344     INTEGER mpiStatus(MPI_STATUS_SIZE), mpiRc
345     #endif
346    
347    
348     C-- Under a "put" scenario we
349     C-- i. set completetion signal for buffer we put into.
350     C-- ii. wait for completetion signal indicating data has been put in
351     C-- our buffer.
352     C-- Under a messaging mode we "receive" the message.
353     C-- Under a "get" scenario we
354     C-- i. Check that the data is ready.
355     C-- ii. Read the data.
356     C-- iii. Set data read flag + memory sync.
357    
358    
359     DO bj=myByLo(myThid),myByHi(myThid)
360     DO bi=myBxLo(myThid),myBxHi(myThid)
361     ebL = exchangeBufLevel(1,bi,bj)
362     southCommMode = _tileCommModeS(bi,bj)
363     northCommMode = _tileCommModeN(bi,bj)
364     biN = _tileBiN(bi,bj)
365     bjN = _tileBjN(bi,bj)
366     biS = _tileBiS(bi,bj)
367     bjS = _tileBjS(bi,bj)
368     IF ( southCommMode .EQ. COMM_MSG ) THEN
369     #ifdef ALLOW_USE_MPI
370     #ifndef ALWAYS_USE_MPI
371     IF ( usingMPI ) THEN
372     #endif
373     theProc = tilePidS(bi,bj)
374     theTag = _tileTagRecvS(bi,bj)
375     theType = MPI_DOUBLE_PRECISION
376     #ifdef RS_IS_REAL4
377     theType = MPI_REAL4
378     #endif
379     theSize = sNx*exchWidthY*myNz
380     IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS )
381     & theSize = (sNx+2*exchWidthX)*exchWidthY*myNz
382     CALL MPI_Recv( southRecvBuf_RS(1,eBl,bi,bj), theSize, theType,
383     & theProc, theTag, MPI_COMM_WORLD,
384     & mpiStatus, mpiRc )
385     #ifndef ALWAYS_USE_MPI
386     ENDIF
387     #endif
388     #endif /* ALLOW_USE_MPI */
389     ENDIF
390     IF ( northCommMode .EQ. COMM_MSG ) THEN
391     #ifdef ALLOW_USE_MPI
392     #ifndef ALWAYS_USE_MPI
393     IF ( usingMPI ) THEN
394     #endif
395     theProc = tilePidN(bi,bj)
396     theTag = _tileTagRecvN(bi,bj)
397     theType = MPI_DOUBLE_PRECISION
398     #ifdef RS_IS_REAL4
399     theType = MPI_REAL4
400     #endif
401     theSize = sNx*exchWidthY*myNz
402     IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS )
403     & theSize = (sNx+2*exchWidthX)*exchWidthY*myNz
404     CALL MPI_Recv( northRecvBuf_RS(1,eBl,bi,bj), theSize, theType,
405     & theProc, theTag, MPI_COMM_WORLD,
406     & mpiStatus, mpiRc )
407     #ifndef ALWAYS_USE_MPI
408     ENDIF
409     #endif
410     #endif /* ALLOW_USE_MPI */
411     ENDIF
412     ENDDO
413     ENDDO
414    
415     C-- Wait for buffers I am going read to be ready.
416     IF ( exchUsesBarrier ) THEN
417     C o On some machines ( T90 ) use system barrier rather than spinning.
418     CALL BARRIER( myThid )
419     ELSE
420     C o Spin waiting for completetion flag. This avoids a global-lock
421     C i.e. we only lock waiting for data that we need.
422     DO bj=myByLo(myThid),myByHi(myThid)
423     DO bi=myBxLo(myThid),myBxHi(myThid)
424     ebL = exchangeBufLevel(1,bi,bj)
425     southCommMode = _tileCommModeS(bi,bj)
426     northCommMode = _tileCommModeN(bi,bj)
427     spinCount = 0
428     10 CONTINUE
429     CALL FOOL_THE_COMPILER
430     spinCount = spinCount+1
431     C IF ( myThid .EQ. 1 .AND. spinCount .GT. _EXCH_SPIN_LIMIT ) THEN
432     C STOP ' S/R EXCH_RECV_GET_Y: spinCount .GT. _EXCH_SPIN_LIMIT'
433     C ENDIF
434     IF ( southRecvAck(eBl,bi,bj) .EQ. 0. ) GOTO 10
435     IF ( northRecvAck(eBl,bi,bj) .EQ. 0. ) GOTO 10
436     C Clear requests
437     southRecvAck(eBl,bi,bj) = 0.
438     northRecvAck(eBl,bi,bj) = 0.
439     C Update statistics
440     IF ( exchCollectStatistics ) THEN
441     exchRecvYExchCount(1,bi,bj) = exchRecvYExchCount(1,bi,bj)+1
442     exchRecvYSpinCount(1,bi,bj) = exchRecvYSpinCount(1,bi,bj)+spinCount
443     exchRecvYSpinMax(1,bi,bj) = MAX(exchRecvYSpinMax(1,bi,bj),spinCount)
444     exchRecvYSpinMin(1,bi,bj) = MIN(exchRecvYSpinMin(1,bi,bj),spinCount)
445     ENDIF
446    
447    
448     IF ( exchNReqsY(1,bi,bj) .GT. 0 ) THEN
449     #ifdef ALLOW_USE_MPI
450     #ifndef ALWAYS_USE_MPI
451     IF ( usingMPI ) THEN
452     #endif
453     CALL MPI_Waitall( exchNReqsY(1,bi,bj), exchReqIdY(1,1,bi,bj),
454     & mpiStatus, mpiRC )
455     #ifndef ALWAYS_USE_MPI
456     ENDIF
457     #endif
458     #endif /* ALLOW_USE_MPI */
459     ENDIF
460     C Clear outstanding requests counter
461     exchNReqsY(1,bi,bj) = 0
462     ENDDO
463     ENDDO
464     ENDIF
465    
466     C-- Read from the buffers
467     DO bj=myByLo(myThid),myByHi(myThid)
468     DO bi=myBxLo(myThid),myBxHi(myThid)
469    
470     ebL = exchangeBufLevel(1,bi,bj)
471     biN = _tileBiN(bi,bj)
472     bjN = _tileBjN(bi,bj)
473     biS = _tileBiS(bi,bj)
474     bjS = _tileBjS(bi,bj)
475     southCommMode = _tileCommModeS(bi,bj)
476     northCommMode = _tileCommModeN(bi,bj)
477     IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS ) THEN
478     iMin = 1-exchWidthX
479     iMax = sNx+exchWidthX
480     ELSE
481     iMin = 1
482     iMax = sNx
483     ENDIF
484     IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
485     jMin = sNy+1
486     jMax = sNy+exchWidthY
487     iB0 = 0
488     ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
489     jMin = sNy-exchWidthY+1
490     jMax = sNy
491     iB0 = 1-exchWidthY-1
492     ENDIF
493     IF ( northCommMode .EQ. COMM_PUT
494     & .OR. northCommMode .EQ. COMM_MSG ) THEN
495     iB = 0
496     DO K=1,myNz
497     DO J=jMin,jMax
498     DO I=iMin,iMax
499     iB = iB + 1
500     array(I,J,K,bi,bj) = northRecvBuf_RS(iB,eBl,bi,bj)
501     ENDDO
502     ENDDO
503     ENDDO
504     ELSEIF ( northCommMode .EQ. COMM_GET ) THEN
505     DO K=1,myNz
506     iB = iB0
507     DO J=jMin,jMax
508     iB = iB+1
509     DO I=iMin,iMax
510     array(I,J,K,bi,bj) = array(I,iB,K,biN,bjN)
511     ENDDO
512     ENDDO
513     ENDDO
514     ENDIF
515     IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
516     jMin = 1-exchWidthY
517     jMax = 0
518     iB0 = sNy-exchWidthY
519     ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
520     jMin = 1
521     jMax = 1+exchWidthY-1
522     iB0 = sNy
523     ENDIF
524     IF ( southCommMode .EQ. COMM_PUT
525     & .OR. southCommMode .EQ. COMM_MSG ) THEN
526     iB = 0
527     DO K=1,myNz
528     DO J=jMin,jMax
529     DO I=iMin,iMax
530     iB = iB + 1
531     array(I,J,K,bi,bj) = southRecvBuf_RS(iB,eBl,bi,bj)
532     ENDDO
533     ENDDO
534     ENDDO
535     ELSEIF ( southCommMode .EQ. COMM_GET ) THEN
536     DO K=1,myNz
537     iB = iB0
538     DO J=jMin,jMax
539     iB = iB+1
540     DO I=iMin,iMax
541     array(I,J,K,bi,bj) = array(I,iB,K,biS,bjS)
542     ENDDO
543     ENDDO
544     ENDDO
545     ENDIF
546    
547     ENDDO
548     ENDDO
549    
550     RETURN
551     END
552    

  ViewVC Help
Powered by ViewVC 1.1.22