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

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

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


Revision 1.5 - (hide annotations) (download)
Mon Nov 7 19:03:36 2005 UTC (18 years, 6 months ago) by cnh
Branch: MAIN
Changes since 1.4: +42 -1 lines
Adding CPP option to switch to single-threaded EXCH comms in a multi-threaded run.
This is useful for broken MPI implementations that can only do single
threaded messaging (almost every MPI implementation is like this!).

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

  ViewVC Help
Powered by ViewVC 1.1.22