/[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.2 - (show annotations) (download)
Mon Jan 19 18:59:19 2004 UTC (20 years, 4 months ago) by afe
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube4, checkpoint52j_post, checkpoint52l_post, checkpoint52k_post, hrcube5, checkpoint52i_post, checkpoint52j_pre, checkpoint52i_pre, checkpoint52h_pre, hrcube_2, hrcube_3
Changes since 1.1: +28 -14 lines
shortened offending lines in exch2_send_rx?.template

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

  ViewVC Help
Powered by ViewVC 1.1.22