/[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.1 - (show annotations) (download)
Fri Jan 9 20:46:09 2004 UTC (20 years, 4 months ago) by afe
Branch: MAIN
CVS Tags: checkpoint52f_post
Added exch2 routines and pointed hs94.cs-32x32x5 at them

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)') '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)') ' source +u(isl, jsl) = ', isl, jsl
154 ELSEIF ( pi(1) .EQ. -1 ) THEN
155 C reversed i index aligns
156 WRITE(messageBuffer,'(A,2I4)') ' source -u(isl, jsl) = ', isl, jsl
157 ELSEIF ( pj(1) .EQ. 1 ) THEN
158 WRITE(messageBuffer,'(A,2I4)') ' source +v(isl, jsl) = ', isl, jsl
159 ELSEIF ( pj(1) .EQ. -1 ) THEN
160 WRITE(messageBuffer,'(A,2I4)') ' source -v(isl, jsl) = ', isl, jsl
161 ENDIF
162 CALL PRINT_MESSAGE(messageBuffer,
163 I standardMessageUnit,SQUEEZE_RIGHT,
164 I myThid)
165 IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
166 WRITE(messageBuffer,'(A,2I4)') ' *** isl is out of bounds '
167 CALL PRINT_MESSAGE(messageBuffer,
168 I standardMessageUnit,SQUEEZE_RIGHT,
169 I myThid)
170 ENDIF
171 IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
172 WRITE(messageBuffer,'(A,2I4)') ' *** jsl is out of bounds '
173 CALL PRINT_MESSAGE(messageBuffer,
174 I standardMessageUnit,SQUEEZE_RIGHT,
175 I myThid)
176 ENDIF
177 #endif /* W2_E2_DEBUG_ON */
178 #ifdef W2_USE_E2_SAFEMODE
179 IF ( iBufr1 .GT. e2BufrRecSize ) THEN
180 C Ran off end of buffer. This should not happen
181 STOP 'EXCH2_SEND_RX2:: E2BUFR LIMIT EXCEEDED'
182 ENDIF
183 IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
184 C Forward mode send getting from points outside of the
185 C tiles exclusive domain bounds in X. This should not happen
186 WRITE(messageBuffer,'(A,I4,I4)')
187 & 'EXCH2_SEND_RX2 tIlo, tIhi =', tIlo, tIhi
188 CALL PRINT_MESSAGE(messageBuffer,
189 I standardMessageUnit,SQUEEZE_BOTH,
190 I myThid)
191 WRITE(messageBuffer,'(A,3I4)')
192 & 'EXCH2_SEND_RX2 itl, jtl, isl =', itl, jtl, isl
193 CALL PRINT_MESSAGE(messageBuffer,
194 I standardMessageUnit,SQUEEZE_BOTH,
195 I myThid)
196 STOP 'EXCH2_SEND_RX2:: ISL OUTSIDE TILE EXCLUSIVE DOMAIN'
197 ENDIF
198 IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
199 C Forward mode send getting from points outside of the
200 C tiles exclusive domain bounds in Y. This should not happen
201 WRITE(messageBuffer,'(A,I4,I4)')
202 & 'EXCH2_SEND_RX2 tJlo, tJhi =', tJlo, tJhi
203 CALL PRINT_MESSAGE(messageBuffer,
204 I standardMessageUnit,SQUEEZE_BOTH,
205 I myThid)
206 WRITE(messageBuffer,'(A,2I4)')
207 & 'EXCH2_SEND_RX2 itl, jtl =', itl, jtl
208 CALL PRINT_MESSAGE(messageBuffer,
209 I standardMessageUnit,SQUEEZE_BOTH,
210 I myThid)
211 WRITE(messageBuffer,'(A,2I4)')
212 & 'EXCH2_SEND_RX2 isl, jsl =', isl, jsl
213 CALL PRINT_MESSAGE(messageBuffer,
214 I standardMessageUnit,SQUEEZE_BOTH,
215 I myThid)
216
217 STOP 'EXCH2_SEND_RX2:: JSL OUTSIDE TILE EXCLUSIVE DOMAIN'
218 ENDIF
219 #endif /* W2_USE_E2_SAFEMODE */
220 ENDDO
221 ENDDO
222 ENDDO
223
224 C Extract values into bufr2
225 C if pi(2) is 1 then +j in target <=> +i in source so bufr1 should get +array1
226 C if pi(2) is -1 then +j in target <=> -i in source so bufr1 should get -array1
227 C if pj(2) is 1 then +j in target <=> +j in source so bufr1 should get +array2
228 C if pj(2) is -1 then +j in target <=> -j in source so bufr1 should get -array2
229 sa1 = pi(2)
230 sa2 = pj(2)
231 IF ( .NOT. withSigns ) THEN
232 sa1 = ABS(sa1)
233 sa2 = ABS(sa2)
234 ENDIF
235 oi_c=exch2_oi(nN,thisTile)
236 oi_f=exch2_oi_f(nN,thisTile)
237 oi=oi_c
238 oj_c=exch2_oj(nN,thisTile)
239 oj_f=exch2_oj_f(nN,thisTile)
240 oj=oj_c
241 C if pi(2) is 1 then +i in source aligns with +j in target
242 C if pj(2) is 1 then +j in source aligns with +j in target
243 itlreduce=0
244 jtlreduce=0
245 IF ( pi(2) .EQ. -1 ) THEN
246 jtlreduce=1
247 oi=oi_f
248 ENDIF
249 IF ( pj(2) .EQ. -1 ) THEN
250 jtlreduce=1
251 oj=oj_f
252 ENDIF
253 iBufr2=0
254 #ifdef W2_E2_DEBUG_ON
255 WRITE(messageBuffer,'(A,I4,A,I4)') 'EXCH2_SEND_RX2 sourceTile= ',
256 & thisTile,
257 & ' targetTile= ',tt
258 CALL PRINT_MESSAGE(messageBuffer,
259 I standardMessageUnit,SQUEEZE_BOTH,
260 I myThid)
261 #endif /* W2_E2_DEBUG_ON */
262 DO ktl=tKlo,tKhi,tKStride
263 DO jtl=tJLo+jtlreduce, tJHi, tjStride
264 DO itl=tILo+itlreduce, tIHi, tiStride
265 C DO jtl=1,32,31
266 C DO itl=1,32,31
267 iBufr2=iBufr2+1
268 itc=itl+itb
269 jtc=jtl+jtb
270 isc=pi(1)*itc+pi(2)*jtc+oi
271 jsc=pj(1)*itc+pj(2)*jtc+oj
272 isl=isc-isb
273 jsl=jsc-jsb
274 val2=sa1*array1(isl,jsl,ktl)
275 & +sa2*array2(isl,jsl,ktl)
276 e2Bufr2_RX(iBufr2)=val2
277 #ifdef W2_E2_DEBUG_ON
278 WRITE(messageBuffer,'(A,2I4)') 'EXCH2_SEND_RX2 target v(itl, jtl) = ', itl, jtl
279 CALL PRINT_MESSAGE(messageBuffer,
280 I standardMessageUnit,SQUEEZE_RIGHT,
281 I myThid)
282 IF ( pi(2) .EQ. 1 ) THEN
283 C i index aligns
284 WRITE(messageBuffer,'(A,2I4)') ' source +u(isl, jsl) = ', isl, jsl
285 ELSEIF ( pi(2) .EQ. -1 ) THEN
286 C reversed i index aligns
287 WRITE(messageBuffer,'(A,2I4)') ' source -u(isl, jsl) = ', isl, jsl
288 ELSEIF ( pj(2) .EQ. 1 ) THEN
289 WRITE(messageBuffer,'(A,2I4)') ' source +v(isl, jsl) = ', isl, jsl
290 ELSEIF ( pj(2) .EQ. -1 ) THEN
291 WRITE(messageBuffer,'(A,2I4)') ' source -v(isl, jsl) = ', isl, jsl
292 ENDIF
293 CALL PRINT_MESSAGE(messageBuffer,
294 I standardMessageUnit,SQUEEZE_RIGHT,
295 I myThid)
296 IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
297 WRITE(messageBuffer,'(A,2I4)') ' *** isl is out of bounds '
298 CALL PRINT_MESSAGE(messageBuffer,
299 I standardMessageUnit,SQUEEZE_RIGHT,
300 I myThid)
301 ENDIF
302 IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
303 WRITE(messageBuffer,'(A,2I4)') ' *** jsl is out of bounds '
304 CALL PRINT_MESSAGE(messageBuffer,
305 I standardMessageUnit,SQUEEZE_RIGHT,
306 I myThid)
307 ENDIF
308
309 #endif /* W2_E2_DEBUG_ON */
310 #ifdef W2_USE_E2_SAFEMODE
311 IF ( iBufr2 .GT. e2BufrRecSize ) THEN
312 C Ran off end of buffer. This should not happen
313 STOP 'EXCH2_SEND_RX2:: E2BUFR LIMIT EXCEEDED'
314 ENDIF
315 IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
316 C Forward mode send getting from points outside of the
317 C tiles exclusive domain bounds in X. This should not happen
318 WRITE(messageBuffer,'(A,I4,I4)')
319 & 'EXCH2_SEND_RX2 tIlo, tIhi =', tIlo, tIhi
320 CALL PRINT_MESSAGE(messageBuffer,
321 I standardMessageUnit,SQUEEZE_BOTH,
322 I myThid)
323 WRITE(messageBuffer,'(A,3I4)')
324 & 'EXCH2_SEND_RX2 itl, jtl, isl =', itl, jtl, isl
325 CALL PRINT_MESSAGE(messageBuffer,
326 I standardMessageUnit,SQUEEZE_BOTH,
327 I myThid)
328 STOP 'EXCH2_SEND_RX2:: ISL OUTSIDE TILE EXCLUSIVE DOMAIN'
329 ENDIF
330 IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
331 C Forward mode send getting from points outside of the
332 C tiles exclusive domain bounds in Y. This should not happen
333 WRITE(messageBuffer,'(A,I4,I4)')
334 & 'EXCH2_SEND_RX2 tJlo, tJhi =', tJlo, tJhi
335 CALL PRINT_MESSAGE(messageBuffer,
336 I standardMessageUnit,SQUEEZE_BOTH,
337 I myThid)
338 WRITE(messageBuffer,'(A,2I4)')
339 & 'EXCH2_SEND_RX2 itl, jtl =', itl, jtl
340 CALL PRINT_MESSAGE(messageBuffer,
341 I standardMessageUnit,SQUEEZE_BOTH,
342 I myThid)
343 WRITE(messageBuffer,'(A,2I4)')
344 & 'EXCH2_SEND_RX2 isl, jsl =', isl, jsl
345 CALL PRINT_MESSAGE(messageBuffer,
346 I standardMessageUnit,SQUEEZE_BOTH,
347 I myThid)
348
349 STOP 'EXCH2_SEND_RX2:: JSL OUTSIDE TILE EXCLUSIVE DOMAIN'
350 ENDIF
351 #endif /* W2_USE_E2_SAFEMODE */
352 ENDDO
353 ENDDO
354 ENDDO
355
356 C Do data transport depending on communication mechanism between source and target tile
357 IF ( commSetting .EQ. 'P' ) THEN
358 C Need to set data ready assertion (increment buffer
359 C synchronisation token) for multithreaded mode, for now do
360 C nothing i.e. assume only one thread per process.
361 ELSEIF ( commSetting .EQ. 'M' ) THEN
362 #ifdef ALLOW_USE_MPI
363 C Setup MPI stuff here
364 theTag1 = (thisTile-1)*MAX_NEIGHBOURS*2 + nN-1
365 & + 10000*(
366 & (tt-1)*MAX_NEIGHBOURS*2 + nN-1
367 & )
368 theTag2 = (thisTile-1)*MAX_NEIGHBOURS*2 + MAX_NEIGHBOURS + nN-1
369 & + 10000*(
370 & (tt-1)*MAX_NEIGHBOURS*2 + MAX_NEIGHBOURS + nN-1
371 & )
372 tProc = exch2_tProc(tt)-1
373 sProc = exch2_tProc(thisTile)-1
374 theType = MPI_REAL8
375 #ifdef W2_E2_DEBUG_ON
376 WRITE(messageBuffer,'(A,I4,A,I4,A)') ' SEND FROM TILE=', thisTile,
377 & ' (proc = ',sProc,')'
378 CALL PRINT_MESSAGE(messageBuffer,
379 I standardMessageUnit,SQUEEZE_RIGHT,
380 I myThid)
381 WRITE(messageBuffer,'(A,I4,A,I4,A)') ' TO TILE=', tt,
382 & ' (proc = ',tProc,')'
383 CALL PRINT_MESSAGE(messageBuffer,
384 I standardMessageUnit,SQUEEZE_RIGHT,
385 I myThid)
386 WRITE(messageBuffer,'(A,I10)') ' TAG1=', theTag1
387 CALL PRINT_MESSAGE(messageBuffer,
388 I standardMessageUnit,SQUEEZE_RIGHT,
389 I myThid)
390 WRITE(messageBuffer,'(A,I4)') ' NEL1=', iBufr1
391 CALL PRINT_MESSAGE(messageBuffer,
392 I standardMessageUnit,SQUEEZE_RIGHT,
393 I myThid)
394 WRITE(messageBuffer,'(A,I10)') ' TAG2=', theTag2
395 CALL PRINT_MESSAGE(messageBuffer,
396 I standardMessageUnit,SQUEEZE_RIGHT,
397 I myThid)
398 WRITE(messageBuffer,'(A,I4)') ' NEL2=', iBufr2
399 CALL PRINT_MESSAGE(messageBuffer,
400 I standardMessageUnit,SQUEEZE_RIGHT,
401 I myThid)
402 #endif /* W2_E2_DEBUG_ON */
403 CALL MPI_Isend( e2Bufr1_RX, iBufr1, theType,
404 I tProc, theTag1, MPI_COMM_MODEL,
405 O theHandle1, mpiRc )
406 CALL MPI_Isend( e2Bufr2_RX, iBufr2, theType,
407 I tProc, theTag2, MPI_COMM_MODEL,
408 O theHandle2, mpiRc )
409 C Store MPI_Wait token in messageHandle.
410 e2_msgHandle1(1) = theHandle1
411 e2_msgHandle2(1) = theHandle2
412 #endif
413 ELSE
414 STOP 'EXCH2_SEND_RX2:: commSetting VALUE IS INVALID'
415 ENDIF
416
417 RETURN
418 END

  ViewVC Help
Powered by ViewVC 1.1.22