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

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

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


Revision 1.6 - (show annotations) (download)
Tue Jul 29 20:25:23 2008 UTC (15 years, 10 months ago) by jmc
Branch: MAIN
Changes since 1.5: +61 -69 lines
- change index-bounds storage (move from target to local tile,
  more intuitive this way)
- rename/remove some variables

1 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_send_rx2.template,v 1.5 2005/07/24 01:21:36 jmc Exp $
2 C $Name: $
3
4 #include "CPP_EEOPTIONS.h"
5 #include "W2_OPTIONS.h"
6
7 SUBROUTINE EXCH2_SEND_RX2 (
8 I tIlo, tIhi, tiStride,
9 I tJlo, tJhi, tjStride,
10 I tKlo, tKhi, tkStride,
11 I thisTile, nN,
12 O e2Bufr1_RX, e2BufrRecSize,
13 O e2Bufr2_RX,
14 I array1,
15 I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
16 I array2,
17 I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
18 O e2_msgHandle1,
19 O e2_msgHandle2,
20 I commSetting, withSigns, myThid )
21
22 C Vector exchange with bufr1 along +i axis in target tile and
23 C bufr2 along +j axis in target tile.
24
25 IMPLICIT NONE
26
27 #include "SIZE.h"
28 #include "EEPARAMS.h"
29 #include "EESUPPORT.h"
30 #include "W2_EXCH2_TOPOLOGY.h"
31
32 C === Routine arguments ===
33 INTEGER tILo, tIHi, tiStride
34 INTEGER tJLo, tJHi, tjStride
35 INTEGER tKLo, tKHi, tkStride
36 INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
37 INTEGER i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi
38 INTEGER thisTile, nN
39 INTEGER e2BufrRecSize
40 _RX e2Bufr1_RX( e2BufrRecSize )
41 _RX e2Bufr2_RX( e2BufrRecSize )
42 _RX array1(i1Lo:i1Hi,j1Lo:j1Hi,k1Lo:k1Hi)
43 _RX array2(i2Lo:i2Hi,j2Lo:j2Hi,k2Lo:k2Hi)
44 INTEGER e2_msgHandle1(1)
45 INTEGER e2_msgHandle2(1)
46 INTEGER myThid
47 CHARACTER commSetting
48 LOGICAL withSigns
49
50 C == Local variables ==
51 C itl, jtl, ktl :: Loop counters
52 C :: itl etc... target local
53 C :: itc etc... target canonical
54 C :: isl etc... source local
55 C :: isc etc... source canonical
56 INTEGER itl, jtl, ktl
57 INTEGER itc, jtc
58 INTEGER isc, jsc
59 INTEGER isl, jsl
60 c INTEGER ktc, ksc, ksl
61 C tt :: Target tile
62 C itb, jtb :: Target local to canonical offsets
63 C
64 INTEGER tt
65 INTEGER itb, jtb
66 INTEGER isb, jsb
67 INTEGER pi(2), pj(2), oi, oj
68 _RX sa1, sa2, val1, val2
69 INTEGER iBufr1, iBufr2
70 INTEGER itlreduce
71 INTEGER jtlreduce
72
73 C MPI setup
74 #ifdef ALLOW_USE_MPI
75 INTEGER theTag1, theTag2, theType, theHandle1, theHandle2
76 INTEGER sProc, tProc, mpiRc
77 #endif
78 CHARACTER*(MAX_LEN_MBUF) messageBuffer
79
80 IF ( commSetting .EQ. 'P' ) THEN
81 C Need to check that buffer synchronisation token is decremented
82 C before filling buffer. This is needed for parallel processing
83 C shared memory modes only.
84 ENDIF
85
86 tt=exch2_neighbourId(nN, thisTile )
87 itb=exch2_tBasex(tt)
88 jtb=exch2_tBasey(tt)
89 isb=exch2_tBasex(thisTile)
90 jsb=exch2_tBasey(thisTile)
91 pi(1)=exch2_pij(1,nN,thisTile)
92 pi(2)=exch2_pij(2,nN,thisTile)
93 pj(1)=exch2_pij(3,nN,thisTile)
94 pj(2)=exch2_pij(4,nN,thisTile)
95
96 C Extract into bufr1 (target i-index array)
97 C if pi(1) is 1 then +i in target <=> +i in source so bufr1 should get +array1
98 C if pi(1) is -1 then +i in target <=> -i in source so bufr1 should get -array1
99 C if pj(1) is 1 then +i in target <=> +j in source so bufr1 should get +array2
100 C if pj(1) is -1 then +i in target <=> -j in source so bufr1 should get -array2
101 sa1 = pi(1)
102 sa2 = pj(1)
103 IF ( .NOT. withSigns ) THEN
104 sa1 = ABS(sa1)
105 sa2 = ABS(sa2)
106 ENDIF
107 oi = exch2_oi(nN,thisTile)
108 oj = exch2_oj(nN,thisTile)
109 C if pi(1) is 1 then +i in source aligns with +i in target
110 C if pj(1) is 1 then +i in source aligns with +j in target
111 itlreduce=0
112 jtlreduce=0
113 IF ( pi(1) .EQ. -1 ) THEN
114 oi = exch2_oi(nN,thisTile)+1
115 itlreduce=1
116 ENDIF
117 IF ( pj(1) .EQ. -1 ) THEN
118 oj = exch2_oj(nN,thisTile)+1
119 itlreduce=1
120 ENDIF
121 iBufr1=0
122 #ifdef W2_E2_DEBUG_ON
123 WRITE(messageBuffer,'(A,I4,A,I4)') 'EXCH2_SEND_RX2 sourceTile= ',
124 & thisTile,
125 & ' targetTile= ',tt
126 CALL PRINT_MESSAGE(messageBuffer,
127 I standardMessageUnit,SQUEEZE_BOTH,
128 I myThid)
129 #endif /* W2_E2_DEBUG_ON */
130 DO ktl=tKlo,tKhi,tKStride
131 DO jtl=tJLo+jtlreduce, tJHi, tjStride
132 DO itl=tILo+itlreduce, tIHi, tiStride
133 C DO jtl=1,32,31
134 C DO itl=1,32,31
135 iBufr1=iBufr1+1
136 itc=itl+itb
137 jtc=jtl+jtb
138 isc=pi(1)*itc+pi(2)*jtc+oi
139 jsc=pj(1)*itc+pj(2)*jtc+oj
140 isl=isc-isb
141 jsl=jsc-jsb
142 val1=sa1*array1(isl,jsl,ktl)
143 & +sa2*array2(isl,jsl,ktl)
144 e2Bufr1_RX(iBufr1)=val1
145 #ifdef W2_E2_DEBUG_ON
146 WRITE(messageBuffer,'(A,2I4)')
147 & 'EXCH2_SEND_RX2 target u(itl, jtl) = ', itl, jtl
148 CALL PRINT_MESSAGE(messageBuffer,
149 I standardMessageUnit,SQUEEZE_RIGHT,
150 I myThid)
151 IF ( pi(1) .EQ. 1 ) THEN
152 C i index aligns
153 WRITE(messageBuffer,'(A,2I4)')
154 & ' source +u(isl, jsl) = ', isl, jsl
155 ELSEIF ( pi(1) .EQ. -1 ) THEN
156 C reversed i index aligns
157 WRITE(messageBuffer,'(A,2I4)')
158 & ' source -u(isl, jsl) = ', isl, jsl
159 ELSEIF ( pj(1) .EQ. 1 ) THEN
160 WRITE(messageBuffer,'(A,2I4)')
161 & ' source +v(isl, jsl) = ', isl, jsl
162 ELSEIF ( pj(1) .EQ. -1 ) THEN
163 WRITE(messageBuffer,'(A,2I4)')
164 & ' source -v(isl, jsl) = ', isl, jsl
165 ENDIF
166 CALL PRINT_MESSAGE(messageBuffer,
167 I standardMessageUnit,SQUEEZE_RIGHT,
168 I myThid)
169 IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
170 WRITE(messageBuffer,'(A,2I4)')
171 & ' *** isl is out of bounds '
172 CALL PRINT_MESSAGE(messageBuffer,
173 I standardMessageUnit,SQUEEZE_RIGHT,
174 I myThid)
175 ENDIF
176 IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
177 WRITE(messageBuffer,'(A,2I4)')
178 & ' *** jsl is out of bounds '
179 CALL PRINT_MESSAGE(messageBuffer,
180 I standardMessageUnit,SQUEEZE_RIGHT,
181 I myThid)
182 ENDIF
183 #endif /* W2_E2_DEBUG_ON */
184 #ifdef W2_USE_E2_SAFEMODE
185 IF ( iBufr1 .GT. e2BufrRecSize ) THEN
186 C Ran off end of buffer. This should not happen
187 STOP 'EXCH2_SEND_RX2:: E2BUFR LIMIT EXCEEDED'
188 ENDIF
189 IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
190 C Forward mode send getting from points outside of the
191 C tiles exclusive domain bounds in X. This should not happen
192 WRITE(messageBuffer,'(A,I4,I4)')
193 & 'EXCH2_SEND_RX2 tIlo, tIhi =', tIlo, tIhi
194 CALL PRINT_MESSAGE(messageBuffer,
195 I standardMessageUnit,SQUEEZE_BOTH,
196 I myThid)
197 WRITE(messageBuffer,'(A,3I4)')
198 & 'EXCH2_SEND_RX2 itl, jtl, isl =', itl, jtl, isl
199 CALL PRINT_MESSAGE(messageBuffer,
200 I standardMessageUnit,SQUEEZE_BOTH,
201 I myThid)
202 STOP 'EXCH2_SEND_RX2:: ISL OUTSIDE TILE EXCLUSIVE DOMAIN'
203 ENDIF
204 IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
205 C Forward mode send getting from points outside of the
206 C tiles exclusive domain bounds in Y. This should not happen
207 WRITE(messageBuffer,'(A,I4,I4)')
208 & 'EXCH2_SEND_RX2 tJlo, tJhi =', tJlo, tJhi
209 CALL PRINT_MESSAGE(messageBuffer,
210 I standardMessageUnit,SQUEEZE_BOTH,
211 I myThid)
212 WRITE(messageBuffer,'(A,2I4)')
213 & 'EXCH2_SEND_RX2 itl, jtl =', itl, jtl
214 CALL PRINT_MESSAGE(messageBuffer,
215 I standardMessageUnit,SQUEEZE_BOTH,
216 I myThid)
217 WRITE(messageBuffer,'(A,2I4)')
218 & 'EXCH2_SEND_RX2 isl, jsl =', isl, jsl
219 CALL PRINT_MESSAGE(messageBuffer,
220 I standardMessageUnit,SQUEEZE_BOTH,
221 I myThid)
222
223 STOP 'EXCH2_SEND_RX2:: JSL OUTSIDE TILE EXCLUSIVE DOMAIN'
224 ENDIF
225 #endif /* W2_USE_E2_SAFEMODE */
226 ENDDO
227 ENDDO
228 ENDDO
229
230 C Extract values into bufr2
231 C if pi(2) is 1 then +j in target <=> +i in source so bufr1 should get +array1
232 C if pi(2) is -1 then +j in target <=> -i in source so bufr1 should get -array1
233 C if pj(2) is 1 then +j in target <=> +j in source so bufr1 should get +array2
234 C if pj(2) is -1 then +j in target <=> -j in source so bufr1 should get -array2
235 sa1 = pi(2)
236 sa2 = pj(2)
237 IF ( .NOT. withSigns ) THEN
238 sa1 = ABS(sa1)
239 sa2 = ABS(sa2)
240 ENDIF
241 oi = exch2_oi(nN,thisTile)
242 oj = exch2_oj(nN,thisTile)
243 C if pi(2) is 1 then +i in source aligns with +j in target
244 C if pj(2) is 1 then +j in source aligns with +j in target
245 itlreduce=0
246 jtlreduce=0
247 IF ( pi(2) .EQ. -1 ) THEN
248 jtlreduce=1
249 oi = exch2_oi(nN,thisTile)+1
250 ENDIF
251 IF ( pj(2) .EQ. -1 ) THEN
252 jtlreduce=1
253 oj = exch2_oj(nN,thisTile)+1
254 ENDIF
255 iBufr2=0
256 #ifdef W2_E2_DEBUG_ON
257 WRITE(messageBuffer,'(A,I4,A,I4)') 'EXCH2_SEND_RX2 sourceTile= ',
258 & thisTile,
259 & ' targetTile= ',tt
260 CALL PRINT_MESSAGE(messageBuffer,
261 I standardMessageUnit,SQUEEZE_BOTH,
262 I myThid)
263 #endif /* W2_E2_DEBUG_ON */
264 DO ktl=tKlo,tKhi,tKStride
265 DO jtl=tJLo+jtlreduce, tJHi, tjStride
266 DO itl=tILo+itlreduce, tIHi, tiStride
267 C DO jtl=1,32,31
268 C DO itl=1,32,31
269 iBufr2=iBufr2+1
270 itc=itl+itb
271 jtc=jtl+jtb
272 isc=pi(1)*itc+pi(2)*jtc+oi
273 jsc=pj(1)*itc+pj(2)*jtc+oj
274 isl=isc-isb
275 jsl=jsc-jsb
276 val2=sa1*array1(isl,jsl,ktl)
277 & +sa2*array2(isl,jsl,ktl)
278 e2Bufr2_RX(iBufr2)=val2
279 #ifdef W2_E2_DEBUG_ON
280 WRITE(messageBuffer,'(A,2I4)')
281 & 'EXCH2_SEND_RX2 target v(itl, jtl) = ', itl, jtl
282 CALL PRINT_MESSAGE(messageBuffer,
283 I standardMessageUnit,SQUEEZE_RIGHT,
284 I myThid)
285 IF ( pi(2) .EQ. 1 ) THEN
286 C i index aligns
287 WRITE(messageBuffer,'(A,2I4)')
288 & ' source +u(isl, jsl) = ', isl, jsl
289 ELSEIF ( pi(2) .EQ. -1 ) THEN
290 C reversed i index aligns
291 WRITE(messageBuffer,'(A,2I4)')
292 & ' source -u(isl, jsl) = ', isl, jsl
293 ELSEIF ( pj(2) .EQ. 1 ) THEN
294 WRITE(messageBuffer,'(A,2I4)')
295 & ' source +v(isl, jsl) = ', isl, jsl
296 ELSEIF ( pj(2) .EQ. -1 ) THEN
297 WRITE(messageBuffer,'(A,2I4)')
298 & ' source -v(isl, jsl) = ', isl, jsl
299 ENDIF
300 CALL PRINT_MESSAGE(messageBuffer,
301 I standardMessageUnit,SQUEEZE_RIGHT,
302 I myThid)
303 IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
304 WRITE(messageBuffer,'(A,2I4)')
305 & ' *** isl is out of bounds '
306 CALL PRINT_MESSAGE(messageBuffer,
307 I standardMessageUnit,SQUEEZE_RIGHT,
308 I myThid)
309 ENDIF
310 IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
311 WRITE(messageBuffer,'(A,2I4)')
312 & ' *** jsl is out of bounds '
313 CALL PRINT_MESSAGE(messageBuffer,
314 I standardMessageUnit,SQUEEZE_RIGHT,
315 I myThid)
316 ENDIF
317
318 #endif /* W2_E2_DEBUG_ON */
319 #ifdef W2_USE_E2_SAFEMODE
320 IF ( iBufr2 .GT. e2BufrRecSize ) THEN
321 C Ran off end of buffer. This should not happen
322 STOP 'EXCH2_SEND_RX2:: E2BUFR LIMIT EXCEEDED'
323 ENDIF
324 IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
325 C Forward mode send getting from points outside of the
326 C tiles exclusive domain bounds in X. This should not happen
327 WRITE(messageBuffer,'(A,I4,I4)')
328 & 'EXCH2_SEND_RX2 tIlo, tIhi =', tIlo, tIhi
329 CALL PRINT_MESSAGE(messageBuffer,
330 I standardMessageUnit,SQUEEZE_BOTH,
331 I myThid)
332 WRITE(messageBuffer,'(A,3I4)')
333 & 'EXCH2_SEND_RX2 itl, jtl, isl =', itl, jtl, isl
334 CALL PRINT_MESSAGE(messageBuffer,
335 I standardMessageUnit,SQUEEZE_BOTH,
336 I myThid)
337 STOP 'EXCH2_SEND_RX2:: ISL OUTSIDE TILE EXCLUSIVE DOMAIN'
338 ENDIF
339 IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
340 C Forward mode send getting from points outside of the
341 C tiles exclusive domain bounds in Y. This should not happen
342 WRITE(messageBuffer,'(A,I4,I4)')
343 & 'EXCH2_SEND_RX2 tJlo, tJhi =', tJlo, tJhi
344 CALL PRINT_MESSAGE(messageBuffer,
345 I standardMessageUnit,SQUEEZE_BOTH,
346 I myThid)
347 WRITE(messageBuffer,'(A,2I4)')
348 & 'EXCH2_SEND_RX2 itl, jtl =', itl, jtl
349 CALL PRINT_MESSAGE(messageBuffer,
350 I standardMessageUnit,SQUEEZE_BOTH,
351 I myThid)
352 WRITE(messageBuffer,'(A,2I4)')
353 & 'EXCH2_SEND_RX2 isl, jsl =', isl, jsl
354 CALL PRINT_MESSAGE(messageBuffer,
355 I standardMessageUnit,SQUEEZE_BOTH,
356 I myThid)
357
358 STOP 'EXCH2_SEND_RX2:: JSL OUTSIDE TILE EXCLUSIVE DOMAIN'
359 ENDIF
360 #endif /* W2_USE_E2_SAFEMODE */
361 ENDDO
362 ENDDO
363 ENDDO
364
365 C Do data transport depending on communication mechanism between source and target tile
366 IF ( commSetting .EQ. 'P' ) THEN
367 C Need to set data ready assertion (increment buffer
368 C synchronisation token) for multithreaded mode, for now do
369 C nothing i.e. assume only one thread per process.
370 ELSEIF ( commSetting .EQ. 'M' ) THEN
371 #ifdef ALLOW_USE_MPI
372 C Setup MPI stuff here
373 theTag1 = (thisTile-1)*MAX_NEIGHBOURS*2 + nN-1
374 & + 10000*(
375 & (tt-1)*MAX_NEIGHBOURS*2 + nN-1
376 & )
377 theTag2 = (thisTile-1)*MAX_NEIGHBOURS*2 + MAX_NEIGHBOURS + nN-1
378 & + 10000*(
379 & (tt-1)*MAX_NEIGHBOURS*2 + MAX_NEIGHBOURS + nN-1
380 & )
381 tProc = exch2_tProc(tt)-1
382 sProc = exch2_tProc(thisTile)-1
383 theType = MPI_REAL8
384 #ifdef W2_E2_DEBUG_ON
385 WRITE(messageBuffer,'(A,I4,A,I4,A)') ' SEND FROM TILE=', thisTile,
386 & ' (proc = ',sProc,')'
387 CALL PRINT_MESSAGE(messageBuffer,
388 I standardMessageUnit,SQUEEZE_RIGHT,
389 I myThid)
390 WRITE(messageBuffer,'(A,I4,A,I4,A)') ' TO TILE=', tt,
391 & ' (proc = ',tProc,')'
392 CALL PRINT_MESSAGE(messageBuffer,
393 I standardMessageUnit,SQUEEZE_RIGHT,
394 I myThid)
395 WRITE(messageBuffer,'(A,I10)') ' TAG1=', theTag1
396 CALL PRINT_MESSAGE(messageBuffer,
397 I standardMessageUnit,SQUEEZE_RIGHT,
398 I myThid)
399 WRITE(messageBuffer,'(A,I4)') ' NEL1=', iBufr1
400 CALL PRINT_MESSAGE(messageBuffer,
401 I standardMessageUnit,SQUEEZE_RIGHT,
402 I myThid)
403 WRITE(messageBuffer,'(A,I10)') ' TAG2=', theTag2
404 CALL PRINT_MESSAGE(messageBuffer,
405 I standardMessageUnit,SQUEEZE_RIGHT,
406 I myThid)
407 WRITE(messageBuffer,'(A,I4)') ' NEL2=', iBufr2
408 CALL PRINT_MESSAGE(messageBuffer,
409 I standardMessageUnit,SQUEEZE_RIGHT,
410 I myThid)
411 #endif /* W2_E2_DEBUG_ON */
412 CALL MPI_Isend( e2Bufr1_RX, iBufr1, theType,
413 I tProc, theTag1, MPI_COMM_MODEL,
414 O theHandle1, mpiRc )
415 CALL MPI_Isend( e2Bufr2_RX, iBufr2, theType,
416 I tProc, theTag2, MPI_COMM_MODEL,
417 O theHandle2, mpiRc )
418 C Store MPI_Wait token in messageHandle.
419 e2_msgHandle1(1) = theHandle1
420 e2_msgHandle2(1) = theHandle2
421 #endif
422 ELSE
423 STOP 'EXCH2_SEND_RX2:: commSetting VALUE IS INVALID'
424 ENDIF
425
426 RETURN
427 END
428
429 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
430
431 CEH3 ;;; Local Variables: ***
432 CEH3 ;;; mode:fortran ***
433 CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22