/[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.3 - (show annotations) (download)
Mon Apr 5 15:27:06 2004 UTC (20 years, 1 month ago) by edhill
Branch: MAIN
CVS Tags: checkpoint52n_post, checkpoint53d_post, checkpoint54a_pre, checkpoint55c_post, checkpoint54e_post, checkpoint54a_post, checkpoint53c_post, checkpoint57k_post, checkpoint55d_pre, checkpoint57d_post, checkpoint57g_post, checkpoint57b_post, checkpoint57c_pre, checkpoint55j_post, checkpoint56b_post, checkpoint57i_post, checkpoint57e_post, checkpoint55h_post, checkpoint53b_post, checkpoint57g_pre, checkpoint54b_post, checkpoint53b_pre, checkpoint55b_post, checkpoint54d_post, checkpoint56c_post, checkpoint52m_post, checkpoint55, checkpoint53a_post, checkpoint57f_pre, checkpoint57a_post, checkpoint54, checkpoint54f_post, checkpoint55g_post, checkpoint55f_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, checkpoint53, eckpoint57e_pre, checkpoint57h_done, checkpoint53g_post, checkpoint57f_post, checkpoint57c_post, checkpoint55e_post, checkpoint53f_post, checkpoint55a_post, checkpoint53d_pre, checkpoint54c_post, checkpoint57j_post, checkpoint57h_pre, checkpoint57l_post, checkpoint57h_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.2: +9 -0 lines
 o fix "make clean"
 o add CVS Header: and Name:

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

  ViewVC Help
Powered by ViewVC 1.1.22