/[MITgcm]/MITgcm/pkg/exch2/exch2_rx2_cube.template
ViewVC logotype

Contents of /MITgcm/pkg/exch2/exch2_rx2_cube.template

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


Revision 1.12 - (show annotations) (download)
Mon Jun 29 23:46:50 2009 UTC (14 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62e, checkpoint62d, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61s, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.11: +10 -12 lines
remove last BARRIER (no need to synchronise after getting data from shared
 buffer (get) as long as any change to buffer (put,recv) is between BARRIER)

1 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_rx2_cube.template,v 1.11 2009/06/28 01:00:23 jmc Exp $
2 C $Name: $
3
4 #include "CPP_EEOPTIONS.h"
5 #undef LOCAL_DBUG
6
7 CBOP
8 C !ROUTINE: EXCH_RX2_CUBE
9
10 C !INTERFACE:
11 SUBROUTINE EXCH2_RX2_CUBE(
12 U array1, array2,
13 I signOption, fieldCode,
14 I myOLw, myOLe, myOLn, myOLs, myNz,
15 I exchWidthX, exchWidthY,
16 I simulationMode, cornerMode, myThid )
17
18 C !DESCRIPTION:
19 C Two components vector field Exchange:
20 C Fill-in tile-edge overlap-region of a 2 component vector field
21 C with corresponding near-edge interior data point
22
23 C !USES:
24 IMPLICIT NONE
25
26 C == Global data ==
27 #include "SIZE.h"
28 #include "EEPARAMS.h"
29 #include "EESUPPORT.h"
30 #include "W2_EXCH2_SIZE.h"
31 #include "W2_EXCH2_TOPOLOGY.h"
32 #include "W2_EXCH2_BUFFER.h"
33
34 C !INPUT/OUTPUT PARAMETERS:
35 C array1 :: 1rst component array with edges to exchange.
36 C array2 :: 2nd component array with edges to exchange.
37 C signOption :: Flag controlling whether vector is signed.
38 C fieldCode :: field code (position on staggered grid)
39 C myOLw,myOLe :: West and East overlap region sizes.
40 C myOLn,myOLs :: North and South overlap region sizes.
41 C exchWidthX :: Width of data region exchanged in X.
42 C exchWidthY :: Width of data region exchanged in Y.
43 C cornerMode :: halo-corner-region treatment: update/ignore corner region
44 C myThid :: Thread number of this instance of S/R EXCH...
45
46 INTEGER myOLw, myOLe, myOLn, myOLs, myNz
47 _RX array1(1-myOLw:sNx+myOLe,
48 & 1-myOLs:sNy+myOLn,
49 & myNz, nSx, nSy)
50 _RX array2(1-myOLw:sNx+myOLe,
51 & 1-myOLs:sNy+myOLn,
52 & myNz, nSx, nSy)
53 LOGICAL signOption
54 CHARACTER*2 fieldCode
55 INTEGER exchWidthX
56 INTEGER exchWidthY
57 INTEGER simulationMode
58 INTEGER cornerMode
59 INTEGER myThid
60
61 C !LOCAL VARIABLES:
62 C e2_msgHandles :: Synchronization and coordination data structure used to
63 C :: coordinate access to e2Bufr1_RX or to regulate message
64 C :: buffering. In PUT communication sender will increment
65 C :: handle entry once data is ready in buffer. Receiver will
66 C :: decrement handle once data is consumed from buffer.
67 C :: For MPI MSG communication MPI_Wait uses hanlde to check
68 C :: Isend has cleared. This is done in routine after receives.
69 C note: a) current implementation does not use e2_msgHandles for communication
70 C between threads: all-threads barriers are used (see CNH note below).
71 C For a 2-threads synchro communication (future version),
72 C e2_msgHandles should be shared (in common block, moved to BUFFER.h)
73 INTEGER bi, bj
74 C Variables for working through W2 topology
75 INTEGER e2_msgHandles( 2, W2_maxNeighbours, nSx, nSy )
76 INTEGER thisTile, farTile, N, nN, oN
77 INTEGER tIlo1, tIhi1, tJlo1, tJhi1, oIs1, oJs1
78 INTEGER tIlo2, tIhi2, tJlo2, tJhi2, oIs2, oJs2
79 INTEGER tIStride, tJStride
80 INTEGER tKlo, tKhi, tKStride
81 INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
82 INTEGER i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi
83
84 #ifdef ALLOW_USE_MPI
85 INTEGER iBufr1, iBufr2, nri, nrj
86 C MPI stuff (should be in a routine call)
87 INTEGER mpiStatus(MPI_STATUS_SIZE)
88 INTEGER mpiRc
89 INTEGER wHandle
90 #endif
91 CEOP
92
93 C- Tile size of arrays to exchange:
94 i1Lo = 1-myOLw
95 i1Hi = sNx+myOLe
96 j1Lo = 1-myOLs
97 j1Hi = sNy+myOLn
98 k1Lo = 1
99 k1Hi = myNz
100 i2Lo = 1-myOLw
101 i2Hi = sNx+myOLe
102 j2Lo = 1-myOLs
103 j2Hi = sNy+myOLn
104 k2Lo = 1
105 k2Hi = myNz
106
107 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
108
109 C Prevent anyone to access shared buffer while an other thread modifies it
110 CALL BAR2( myThid )
111
112 C-- Post sends into buffer (buffer level 1):
113 DO bj=myByLo(myThid), myByHi(myThid)
114 DO bi=myBxLo(myThid), myBxHi(myThid)
115 thisTile=W2_myTileList(bi,bj)
116 nN=exch2_nNeighbours(thisTile)
117 DO N=1,nN
118 farTile=exch2_neighbourId(N,thisTile)
119 oN = exch2_opposingSend(N,thisTile)
120 #ifdef LOCAL_DBUG
121 WRITE(errorMessageUnit,'(A,3I3,A,4I4,A,2I5)')
122 & 'send_0 bi,N=', bi,bj, N, ' , tI,J_lo,hi=',
123 & exch2_iLo(oN,farTile), exch2_iHi(oN,farTile),
124 & exch2_jLo(oN,farTile), exch2_jHi(oN,farTile),
125 & ' , oIs,oJs=', exch2_oi(N,thisTile), exch2_oj(N,thisTile)
126 #endif
127 CALL EXCH2_GET_UV_BOUNDS(
128 I fieldCode, exchWidthX,
129 I farTile, oN,
130 O tIlo1, tIhi1, tJlo1, tJhi1,
131 O tIlo2, tIhi2, tJlo2, tJhi2,
132 O tiStride, tjStride,
133 O oIs1, oJs1, oIs2, oJs2,
134 I myThid )
135 #ifdef LOCAL_DBUG
136 WRITE(errorMessageUnit,'(A,3I3,A,4I4,A,2I5)')
137 & 'send_1 bi,N=', bi,bj, N, ' , tI,J_lo,hi=',
138 & tIlo1, tIhi1, tJlo1, tJhi1, ' , oIs,oJs=', oIs1, oJs1
139 WRITE(errorMessageUnit,'(A,3I3,A,4I4,A,2I5)')
140 & 'send_2 bi,N=', bi,bj, N, ' , tI,J_lo,hi=',
141 & tIlo2, tIhi2, tJlo2, tJhi2, ' , oIs,oJs=', oIs2, oJs2
142 #endif
143 tKLo=1
144 tKHi=myNz
145 tKStride=1
146 C- Put my points in buffer for neighbour N to fill points
147 C (tIlo:tIhi:tiStride,tJlo:tJhi,tJStride,tKlo:tKhi,tKStride)
148 C in its copy of "array1" & "array2".
149 CALL EXCH2_PUT_RX2(
150 I tIlo1, tIhi1, tIlo2, tIhi2, tiStride,
151 I tJlo1, tJhi1, tJlo2, tJhi2, tjStride,
152 I tKlo, tKhi, tkStride,
153 I oIs1, oJs1, oIs2, oJs2,
154 I thisTile, N,
155 I e2BufrRecSize,
156 O iBuf1Filled(N,bi,bj), iBuf2Filled(N,bi,bj),
157 O e2Bufr1_RX(1,N,bi,bj,1), e2Bufr2_RX(1,N,bi,bj,1),
158 I array1(1-myOLw,1-myOLs,1,bi,bj),
159 I array2(1-myOLw,1-myOLs,1,bi,bj),
160 I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
161 I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
162 O e2_msgHandles(1,N,bi,bj),
163 I W2_myCommFlag(N,bi,bj), signOption, myThid )
164 ENDDO
165 ENDDO
166 ENDDO
167
168 C Wait until all threads finish filling buffer
169 CALL BAR2( myThid )
170
171 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
172
173 #ifdef ALLOW_USE_MPI
174 _BEGIN_MASTER( myThid )
175
176 C-- Send my data (in buffer, level 1) to target Process
177 DO bj=1,nSy
178 DO bi=1,nSx
179 thisTile=W2_myTileList(bi,bj)
180 nN=exch2_nNeighbours(thisTile)
181 DO N=1,nN
182 C- Skip the call if this is an internal exchange
183 IF ( W2_myCommFlag(N,bi,bj) .EQ. 'M' ) THEN
184 CALL EXCH2_SEND_RX2(
185 I thisTile, N,
186 I e2BufrRecSize,
187 I iBuf1Filled(N,bi,bj), iBuf2Filled(N,bi,bj),
188 I e2Bufr1_RX(1,N,bi,bj,1), e2Bufr2_RX(1,N,bi,bj,1),
189 O e2_msgHandles(1,N,bi,bj),
190 I W2_myCommFlag(N,bi,bj), myThid )
191 ENDIF
192 ENDDO
193 ENDDO
194 ENDDO
195
196 C-- Receive data (in buffer, level 2) from source Process
197 DO bj=1,nSy
198 DO bi=1,nSx
199 thisTile=W2_myTileList(bi,bj)
200 nN=exch2_nNeighbours(thisTile)
201 DO N=1,nN
202 C- Skip the call if this is an internal exchange
203 IF ( W2_myCommFlag(N,bi,bj) .EQ. 'M' ) THEN
204 CALL EXCH2_GET_UV_BOUNDS(
205 I fieldCode, exchWidthX,
206 I thisTile, N,
207 O tIlo1, tIhi1, tJlo1, tJhi1,
208 O tIlo2, tIhi2, tJlo2, tJhi2,
209 O tiStride, tjStride,
210 O oIs1, oJs1, oIs2, oJs2,
211 I myThid )
212 nri = 1 + (tIhi1-tIlo1)/tiStride
213 nrj = 1 + (tJhi1-tJlo1)/tjStride
214 iBufr1 = nri*nrj*myNz
215 nri = 1 + (tIhi2-tIlo2)/tiStride
216 nrj = 1 + (tJhi2-tJlo2)/tjStride
217 iBufr2 = nri*nrj*myNz
218 C Receive from neighbour N to fill buffer and later on the array
219 CALL EXCH2_RECV_RX2(
220 I thisTile, N,
221 I e2BufrRecSize,
222 I iBufr1, iBufr2,
223 I e2Bufr1_RX(1,N,bi,bj,2), e2Bufr2_RX(1,N,bi,bj,2),
224 I W2_myCommFlag(N,bi,bj), myThid )
225 ENDIF
226 ENDDO
227 ENDDO
228 ENDDO
229
230 C-- Clear message handles/locks
231 DO bj=1,nSy
232 DO bi=1,nSx
233 thisTile=W2_myTileList(bi,bj)
234 nN=exch2_nNeighbours(thisTile)
235 DO N=1,nN
236 C Note: In a between process tile-tile data transport using
237 C MPI the sender needs to clear an Isend wait handle here.
238 C In a within process tile-tile data transport using true
239 C shared address space/or direct transfer through commonly
240 C addressable memory blocks the receiver needs to assert
241 C that he has consumed the buffer the sender filled here.
242 farTile=exch2_neighbourId(N,thisTile)
243 IF ( W2_myCommFlag(N,bi,bj) .EQ. 'M' ) THEN
244 wHandle = e2_msgHandles(1,N,bi,bj)
245 CALL MPI_Wait( wHandle, mpiStatus, mpiRc )
246 wHandle = e2_msgHandles(2,N,bi,bj)
247 CALL MPI_Wait( wHandle, mpiStatus, mpiRc )
248 ELSEIF ( W2_myCommFlag(N,bi,bj) .EQ. 'P' ) THEN
249 ELSE
250 ENDIF
251 ENDDO
252 ENDDO
253 ENDDO
254
255 _END_MASTER( myThid )
256 C Everyone waits until master-thread finishes receiving
257 CALL BAR2( myThid )
258
259 #endif /* ALLOW_USE_MPI */
260
261 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
262
263 C-- Extract from buffer (either from level 1 if local exch,
264 C or level 2 if coming from an other Proc)
265 DO bj=myByLo(myThid), myByHi(myThid)
266 DO bi=myBxLo(myThid), myBxHi(myThid)
267 thisTile=W2_myTileList(bi,bj)
268 nN=exch2_nNeighbours(thisTile)
269 DO N=1,nN
270 #ifdef LOCAL_DBUG
271 WRITE(errorMessageUnit,'(A,3I3,A,4I4,A,2I5)')
272 & 'recv_0 bi,N=', bi,bj, N, ' , tI,J_lo,hi=',
273 & exch2_iLo(N,thisTile), exch2_iHi(N,thisTile),
274 & exch2_jLo(N,thisTile), exch2_jHi(N,thisTile)
275 #endif
276 CALL EXCH2_GET_UV_BOUNDS(
277 I fieldCode, exchWidthX,
278 I thisTile, N,
279 O tIlo1, tIhi1, tJlo1, tJhi1,
280 O tIlo2, tIhi2, tJlo2, tJhi2,
281 O tiStride, tjStride,
282 O oIs1, oJs1, oIs2, oJs2,
283 I myThid )
284 #ifdef LOCAL_DBUG
285 WRITE(errorMessageUnit,'(A,3I3,A,4I4,A,2I5)')
286 & 'recv_1 bi,N=', bi,bj, N, ' , tI,J_lo,hi=',
287 & tIlo1, tIhi1, tJlo1, tJhi1
288 WRITE(errorMessageUnit,'(A,3I3,A,4I4,A,2I5)')
289 & 'recv_2 bi,N=', bi,bj, N, ' , tI,J_lo,hi=',
290 & tIlo2, tIhi2, tJlo2, tJhi2
291 #endif
292 tKLo=1
293 tKHi=myNz
294 tKStride=1
295
296 C From buffer, get my points
297 C (tIlo:tIhi:tiStride,tJlo:tJhi,tJStride,tKlo:tKhi,tKStride) in "array1,2":
298 C Note: when transferring data within a process:
299 C o e2Bufr entry to read is entry associated with opposing send record
300 C o e2_msgHandle entry to read is entry associated with opposing send record.
301 CALL EXCH2_GET_RX2(
302 I tIlo1, tIhi1, tIlo2, tIhi2, tiStride,
303 I tJlo1, tJhi1, tJlo2, tJhi2, tjStride,
304 I tKlo, tKhi, tkStride,
305 I thisTile, N, bi, bj,
306 I e2BufrRecSize, W2_maxNeighbours, nSx, nSy,
307 I e2Bufr1_RX, e2Bufr2_RX,
308 U array1(1-myOLw,1-myOLs,1,bi,bj),
309 U array2(1-myOLw,1-myOLs,1,bi,bj),
310 I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
311 I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
312 U e2_msgHandles,
313 I W2_myCommFlag(N,bi,bj), myThid )
314 ENDDO
315 ENDDO
316 ENDDO
317
318 RETURN
319 END
320
321 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
322
323 CEH3 ;;; Local Variables: ***
324 CEH3 ;;; mode:fortran ***
325 CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22