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

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

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


Revision 1.4 - (hide annotations) (download)
Fri Jul 22 18:21:55 2005 UTC (18 years, 10 months ago) by jmc
Branch: MAIN
Changes since 1.3: +8 -5 lines
comment out unused variable declaration (get less warnings for unused var)

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

  ViewVC Help
Powered by ViewVC 1.1.22