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

Annotation of /MITgcm/eesupp/src/exch_rx_recv_get_x.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_x.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_X
7    
8     C !INTERFACE:
9 adcroft 1.1 SUBROUTINE EXCH_RX_RECV_GET_X( 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_RX_GET_X
18     C | o "Send" or "put" X 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 adcroft 1.1 C support for adjoint integration of code. )
42 cnh 1.2 C theCornerMode :: Flag indicating whether corner updates are
43 adcroft 1.1 C needed.
44 cnh 1.2 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 biW, bjW :: West tile indices
65     C biE, bjE :: East 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 westCommMode :: Working variables holding type
70     C eastCommMode of communication a particular
71     C tile face uses.
72 adcroft 1.1 INTEGER I, J, K, iMin, iMax, iB, iB0
73     INTEGER bi, bj, biW, bjW, biE, bjE
74     INTEGER eBl
75     INTEGER westCommMode
76     INTEGER eastCommMode
77     INTEGER spinCount
78     #ifdef ALLOW_USE_MPI
79     INTEGER theProc, theTag, theType, theSize
80     INTEGER mpiStatus(MPI_STATUS_SIZE,4), mpiRc
81     #endif
82 cnh 1.2 CEOP
83 adcroft 1.1
84 cnh 1.5 #ifdef USE_SINGLE_THREADED_EXCH_COMMS
85     INTEGER myBxLoSave(MAX_NO_THREADS)
86     INTEGER myBxHiSave(MAX_NO_THREADS)
87     INTEGER myByLoSave(MAX_NO_THREADS)
88     INTEGER myByHiSave(MAX_NO_THREADS)
89     #endif /* SINGLE_THREADED_EXCH_COMMS */
90    
91     #ifdef USE_SINGLE_THREADED_EXCH_COMMS
92     _BARRIER
93     IF ( myThid .EQ. 1 ) THEN
94     DO I=1,nThreads
95     myBxLoSave(I) = myBxLo(I)
96     myBxHiSave(I) = myBxHi(I)
97     myByLoSave(I) = myByLo(I)
98     myByHiSave(I) = myByHi(I)
99     myBxLo(I) = 0
100     myBxHi(I) = -1
101     myByLo(I) = 0
102     myByHi(I) = -1
103     ENDDO
104     myBxLo(1) = 1
105     myBxHi(1) = nSx
106     myByLo(1) = 1
107     myByHi(1) = nSy
108     ENDIF
109     _BARRIER
110     #endif /* SINGLE_THREADED_EXCH_COMMS */
111    
112 adcroft 1.1
113     C-- Under a "put" scenario we
114     C-- i. set completetion signal for buffer we put into.
115     C-- ii. wait for completetion signal indicating data has been put in
116     C-- our buffer.
117     C-- Under a messaging mode we "receive" the message.
118     C-- Under a "get" scenario we
119     C-- i. Check that the data is ready.
120     C-- ii. Read the data.
121     C-- iii. Set data read flag + memory sync.
122    
123    
124     DO bj=myByLo(myThid),myByHi(myThid)
125     DO bi=myBxLo(myThid),myBxHi(myThid)
126     ebL = exchangeBufLevel(1,bi,bj)
127     westCommMode = _tileCommModeW(bi,bj)
128     eastCommMode = _tileCommModeE(bi,bj)
129     biE = _tileBiE(bi,bj)
130     bjE = _tileBjE(bi,bj)
131     biW = _tileBiW(bi,bj)
132     bjW = _tileBjW(bi,bj)
133     IF ( westCommMode .EQ. COMM_MSG ) THEN
134     #ifdef ALLOW_USE_MPI
135     #ifndef ALWAYS_USE_MPI
136     IF ( usingMPI ) THEN
137     #endif
138     theProc = tilePidW(bi,bj)
139     theTag = _tileTagRecvW(bi,bj)
140 dimitri 1.3 theType = _MPI_TYPE_RX
141 adcroft 1.1 theSize = sNy*exchWidthX*myNz
142     CALL MPI_Recv( westRecvBuf_RX(1,eBl,bi,bj), theSize, theType,
143     & theProc, theTag, MPI_COMM_MODEL,
144     & mpiStatus, mpiRc )
145     #ifndef ALWAYS_USE_MPI
146     ENDIF
147     #endif
148     #endif /* ALLOW_USE_MPI */
149     ENDIF
150     IF ( eastCommMode .EQ. COMM_MSG ) THEN
151     #ifdef ALLOW_USE_MPI
152     #ifndef ALWAYS_USE_MPI
153     IF ( usingMPI ) THEN
154     #endif
155     theProc = tilePidE(bi,bj)
156     theTag = _tileTagRecvE(bi,bj)
157 dimitri 1.3 theType = _MPI_TYPE_RX
158 adcroft 1.1 theSize = sNy*exchWidthX*myNz
159     CALL MPI_Recv( eastRecvBuf_RX(1,eBl,bi,bj), theSize, theType,
160     & theProc, theTag, MPI_COMM_MODEL,
161     & mpiStatus, mpiRc )
162     #ifndef ALWAYS_USE_MPI
163     ENDIF
164     #endif
165     #endif /* ALLOW_USE_MPI */
166     ENDIF
167     ENDDO
168     ENDDO
169    
170     C-- Wait for buffers I am going read to be ready.
171     IF ( exchUsesBarrier ) THEN
172     C o On some machines ( T90 ) use system barrier rather than spinning.
173     CALL BARRIER( myThid )
174     ELSE
175     C o Spin waiting for completetion flag. This avoids a global-lock
176     C i.e. we only lock waiting for data that we need.
177     DO bj=myByLo(myThid),myByHi(myThid)
178     DO bi=myBxLo(myThid),myBxHi(myThid)
179     spinCount = 0
180     ebL = exchangeBufLevel(1,bi,bj)
181     westCommMode = _tileCommModeW(bi,bj)
182     eastCommMode = _tileCommModeE(bi,bj)
183     10 CONTINUE
184 jmc 1.4 CALL FOOL_THE_COMPILER( spinCount )
185 adcroft 1.1 spinCount = spinCount+1
186     C IF ( myThid .EQ. 1 .AND. spinCount .GT. _EXCH_SPIN_LIMIT ) THEN
187     C WRITE(*,*) ' eBl = ', ebl
188     C STOP ' S/R EXCH_RECV_GET_X: spinCount .GT. _EXCH_SPIN_LIMIT'
189     C ENDIF
190     IF ( westRecvAck(eBl,bi,bj) .EQ. 0. ) GOTO 10
191     IF ( eastRecvAck(eBl,bi,bj) .EQ. 0. ) GOTO 10
192     C Clear outstanding requests
193     westRecvAck(eBl,bi,bj) = 0.
194     eastRecvAck(eBl,bi,bj) = 0.
195    
196     IF ( exchNReqsX(1,bi,bj) .GT. 0 ) THEN
197     #ifdef ALLOW_USE_MPI
198     #ifndef ALWAYS_USE_MPI
199     IF ( usingMPI ) THEN
200     #endif
201     CALL MPI_Waitall( exchNReqsX(1,bi,bj), exchReqIdX(1,1,bi,bj),
202     & mpiStatus, mpiRC )
203     #ifndef ALWAYS_USE_MPI
204     ENDIF
205     #endif
206     #endif /* ALLOW_USE_MPI */
207     ENDIF
208     C Clear outstanding requests counter
209     exchNReqsX(1,bi,bj) = 0
210     C Update statistics
211     IF ( exchCollectStatistics ) THEN
212     exchRecvXExchCount(1,bi,bj) = exchRecvXExchCount(1,bi,bj)+1
213     exchRecvXSpinCount(1,bi,bj) =
214     & exchRecvXSpinCount(1,bi,bj)+spinCount
215     exchRecvXSpinMax(1,bi,bj) =
216     & MAX(exchRecvXSpinMax(1,bi,bj),spinCount)
217     exchRecvXSpinMin(1,bi,bj) =
218     & MIN(exchRecvXSpinMin(1,bi,bj),spinCount)
219     ENDIF
220     ENDDO
221     ENDDO
222     ENDIF
223    
224     C-- Read from the buffers
225     DO bj=myByLo(myThid),myByHi(myThid)
226     DO bi=myBxLo(myThid),myBxHi(myThid)
227    
228     ebL = exchangeBufLevel(1,bi,bj)
229     biE = _tileBiE(bi,bj)
230     bjE = _tileBjE(bi,bj)
231     biW = _tileBiW(bi,bj)
232     bjW = _tileBjW(bi,bj)
233     westCommMode = _tileCommModeW(bi,bj)
234     eastCommMode = _tileCommModeE(bi,bj)
235     IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
236     iMin = sNx+1
237     iMax = sNx+exchWidthX
238     iB0 = 0
239     IF ( eastCommMode .EQ. COMM_PUT
240     & .OR. eastCommMode .EQ. COMM_MSG ) THEN
241     iB = 0
242     DO K=1,myNz
243     DO J=1,sNy
244     DO I=iMin,iMax
245     iB = iB + 1
246     array(I,J,K,bi,bj) = eastRecvBuf_RX(iB,eBl,bi,bj)
247     ENDDO
248     ENDDO
249     ENDDO
250     ELSEIF ( eastCommMode .EQ. COMM_GET ) THEN
251     DO K=1,myNz
252     DO J=1,sNy
253     iB = iB0
254     DO I=iMin,iMax
255     iB = iB+1
256     array(I,J,K,bi,bj) = array(iB,J,K,biE,bjE)
257     ENDDO
258     ENDDO
259     ENDDO
260     ENDIF
261     ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
262     iMin = sNx-exchWidthX+1
263     iMax = sNx
264     iB0 = 1-exchWidthX-1
265     IF ( eastCommMode .EQ. COMM_PUT
266     & .OR. eastCommMode .EQ. COMM_MSG ) THEN
267     iB = 0
268     DO K=1,myNz
269     DO J=1,sNy
270     DO I=iMin,iMax
271     iB = iB + 1
272     array(I,J,K,bi,bj) =
273     & array(I,J,K,bi,bj)+eastRecvBuf_RX(iB,eBl,bi,bj)
274     ENDDO
275     ENDDO
276     ENDDO
277     ELSEIF ( eastCommMode .EQ. COMM_GET ) THEN
278     DO K=1,myNz
279     DO J=1,sNy
280     iB = iB0
281     DO I=iMin,iMax
282     iB = iB+1
283     array(I,J,K,bi,bj) =
284     & array(I,J,K,bi,bj)+array(iB,J,K,biE,bjE)
285     ENDDO
286     ENDDO
287     ENDDO
288     ENDIF
289     ENDIF
290     IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
291     iMin = 1-exchWidthX
292     iMax = 0
293     iB0 = sNx-exchWidthX
294     IF ( westCommMode .EQ. COMM_PUT
295     & .OR. westCommMode .EQ. COMM_MSG ) THEN
296     iB = 0
297     DO K=1,myNz
298     DO J=1,sNy
299     DO I=iMin,iMax
300     iB = iB + 1
301     array(I,J,K,bi,bj) = westRecvBuf_RX(iB,eBl,bi,bj)
302     ENDDO
303     ENDDO
304     ENDDO
305     ELSEIF ( westCommMode .EQ. COMM_GET ) THEN
306     DO K=1,myNz
307     DO J=1,sNy
308     iB = iB0
309     DO I=iMin,iMax
310     iB = iB+1
311     array(I,J,K,bi,bj) = array(iB,J,K,biW,bjW)
312     ENDDO
313     ENDDO
314     ENDDO
315     ENDIF
316     ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
317     iMin = 1
318     iMax = 1+exchWidthX-1
319     iB0 = sNx
320     IF ( westCommMode .EQ. COMM_PUT
321     & .OR. westCommMode .EQ. COMM_MSG ) THEN
322     iB = 0
323     DO K=1,myNz
324     DO J=1,sNy
325     DO I=iMin,iMax
326     iB = iB + 1
327     array(I,J,K,bi,bj) =
328     & array(I,J,K,bi,bj)+westRecvBuf_RX(iB,eBl,bi,bj)
329     ENDDO
330     ENDDO
331     ENDDO
332     ELSEIF ( westCommMode .EQ. COMM_GET ) THEN
333     DO K=1,myNz
334     DO J=1,sNy
335     iB = iB0
336     DO I=iMin,iMax
337     iB = iB+1
338     array(I,J,K,bi,bj) =
339     & array(I,J,K,bi,bj)+array(iB,J,K,biW,bjW)
340     ENDDO
341     ENDDO
342     ENDDO
343     ENDIF
344     ENDIF
345    
346     ENDDO
347     ENDDO
348    
349 cnh 1.5 #ifdef USE_SINGLE_THREADED_EXCH_COMMS
350     _BARRIER
351     IF ( myThid .EQ. 1 ) THEN
352     DO I=1,nThreads
353     myBxLo(I) = myBxLoSave(I)
354     myBxHi(I) = myBxHiSave(I)
355     myByLo(I) = myByLoSave(I)
356     myByHi(I) = myByHiSave(I)
357     ENDDO
358     ENDIF
359     _BARRIER
360     #endif /* USE_SINGLE_THREADED_EXCH_COMMS */
361    
362 adcroft 1.1 RETURN
363     END

  ViewVC Help
Powered by ViewVC 1.1.22