/[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.15 - (show annotations) (download)
Wed May 19 01:25:17 2010 UTC (13 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62g, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.14: +4 -4 lines
stwich order of arguments myOLn,myOLs to match calling S/R

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

  ViewVC Help
Powered by ViewVC 1.1.22