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

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

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


Revision 1.3 - (hide annotations) (download)
Mon Sep 3 19:40:33 2012 UTC (11 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63s
Changes since 1.2: +1 -7 lines
remove unused variables

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_put_rx2.template,v 1.2 2010/04/23 20:21:07 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5     #include "W2_OPTIONS.h"
6    
7     CBOP 0
8     C !ROUTINE: EXCH2_PUT_RX2
9    
10     C !INTERFACE:
11     SUBROUTINE EXCH2_PUT_RX2 (
12     I tIlo1, tIhi1, tIlo2, tIhi2, tiStride,
13     I tJlo1, tJhi1, tJlo2, tJhi2, tjStride,
14     I tKlo, tKhi, tkStride,
15     I oIs1, oJs1, oIs2, oJs2,
16     I thisTile, nN,
17     I e2BufrRecSize,
18     O iBufr1, iBufr2,
19     O e2Bufr1_RX, e2Bufr2_RX,
20     I array1,
21     I array2,
22     I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
23     I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
24     O e2_msgHandle,
25     I commSetting, withSigns, myThid )
26    
27     C !DESCRIPTION:
28     C Two components vector field Exchange:
29     C Put into buffer exchanged data from this source tile.
30     C Those data are intended to fill-in the
31     C target-neighbour-edge overlap region.
32    
33     C !USES:
34     IMPLICIT NONE
35    
36     #include "SIZE.h"
37     #include "EEPARAMS.h"
38     #include "W2_EXCH2_SIZE.h"
39     #include "W2_EXCH2_TOPOLOGY.h"
40    
41     C !INPUT/OUTPUT PARAMETERS:
42     C === Routine arguments ===
43     C tIlo1, tIhi1 :: index range in I that will be filled in target "array1"
44     C tIlo2, tIhi2 :: index range in I that will be filled in target "array2"
45     C tIstride :: index step in I that will be filled in target arrays
46     C tJlo1, tJhi1 :: index range in J that will be filled in target "array1"
47     C tJlo2, tJhi2 :: index range in J that will be filled in target "array2"
48     C tJstride :: index step in J that will be filled in target arrays
49     C tKlo, tKhi :: index range in K that will be filled in target arrays
50     C tKstride :: index step in K that will be filled in target arrays
51     C oIs1, oJs1 :: I,J index offset in target to source-1 connection
52     C oIs2, oJs2 :: I,J index offset in target to source-2 connection
53     C thisTile :: sending tile Id. number
54     C nN :: Neighbour entry that we are processing
55     C e2BufrRecSize :: Number of elements in each entry of e2Bufr[1,2]_RX
56     C iBufr1 :: number of buffer-1 elements filled in
57     C iBufr2 :: number of buffer-2 elements filled in
58     C e2Bufr1_RX :: Data transport buffer array. This array is used in one of
59     C e2Bufr2_RX :: two ways. For PUT communication the entry in the buffer
60     C :: associated with the source for this receive (determined
61     C :: from the opposing_send index) is read.
62     C :: For MSG communication the entry in the buffer associated
63     C :: with this neighbor of this tile is used as a receive
64     C :: location for loading a linear stream of bytes.
65     C array1 :: 1rst Component target array that this receive writes to.
66     C array2 :: 2nd Component target array that this receive writes to.
67     C i1Lo, i1Hi :: I coordinate bounds of target array1
68     C j1Lo, j1Hi :: J coordinate bounds of target array1
69     C k1Lo, k1Hi :: K coordinate bounds of target array1
70     C i2Lo, i2Hi :: I coordinate bounds of target array2
71     C j2Lo, j2Hi :: J coordinate bounds of target array2
72     C k2Lo, k2Hi :: K coordinate bounds of target array2
73     C e2_msgHandles :: Synchronization and coordination data structure used to
74     C :: coordinate access to e2Bufr1_RX or to regulate message
75     C :: buffering. In PUT communication sender will increment
76     C :: handle entry once data is ready in buffer. Receiver will
77     C :: decrement handle once data is consumed from buffer.
78 jmc 1.2 C :: For MPI MSG communication MPI_Wait uses handle to check
79 jmc 1.1 C :: Isend has cleared. This is done in routine after receives.
80     C commSetting :: Mode of communication used to exchange with this neighbor
81     C withSigns :: Flag controlling whether vector field is signed.
82     C myThid :: my Thread Id. number
83    
84     INTEGER tIlo1, tIhi1, tIlo2, tIhi2, tiStride
85     INTEGER tJlo1, tJhi1, tJlo2, tJhi2, tjStride
86     INTEGER tKlo, tKhi, tkStride
87     INTEGER oIs1, oJs1, oIs2, oJs2
88     INTEGER thisTile, nN
89     INTEGER e2BufrRecSize
90     INTEGER iBufr1, iBufr2
91     _RX e2Bufr1_RX( e2BufrRecSize )
92     _RX e2Bufr2_RX( e2BufrRecSize )
93     INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
94     INTEGER i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi
95     _RX array1(i1Lo:i1Hi,j1Lo:j1Hi,k1Lo:k1Hi)
96     _RX array2(i2Lo:i2Hi,j2Lo:j2Hi,k2Lo:k2Hi)
97     INTEGER e2_msgHandle(2)
98     CHARACTER commSetting
99     LOGICAL withSigns
100     INTEGER myThid
101     CEOP
102    
103     C !LOCAL VARIABLES:
104     C == Local variables ==
105     C itl,jtl,ktl :: Loop counters
106     C :: itl etc... target local
107     C :: itc etc... target canonical
108     C :: isl etc... source local
109     C :: isc etc... source canonical
110     C tgT :: Target tile
111     C itb, jtb :: Target local to canonical offsets
112     INTEGER itl, jtl, ktl
113     INTEGER itc, jtc
114     INTEGER isc, jsc
115     INTEGER isl, jsl
116     INTEGER tgT
117     INTEGER itb, jtb
118     INTEGER isb, jsb
119     INTEGER pi(2), pj(2)
120     _RX sa1, sa2, val1, val2
121    
122     #if ( (defined W2_E2_DEBUG_ON) || (defined W2_USE_E2_SAFEMODE) )
123     CHARACTER*(MAX_LEN_MBUF) msgBuf
124     #endif
125    
126     IF ( commSetting .EQ. 'P' ) THEN
127     C Need to check that buffer synchronisation token is decremented
128     C before filling buffer. This is needed for parallel processing
129     C shared memory modes only.
130     ENDIF
131    
132     tgT = exch2_neighbourId(nN, thisTile )
133     itb = exch2_tBasex(tgT)
134     jtb = exch2_tBasey(tgT)
135     isb = exch2_tBasex(thisTile)
136     jsb = exch2_tBasey(thisTile)
137     pi(1)=exch2_pij(1,nN,thisTile)
138     pi(2)=exch2_pij(2,nN,thisTile)
139     pj(1)=exch2_pij(3,nN,thisTile)
140     pj(2)=exch2_pij(4,nN,thisTile)
141    
142     C Extract into bufr1 (target i-index array)
143     C if pi(1) is 1 then +i in target <=> +i in source so bufr1 should get +array1
144     C if pi(1) is -1 then +i in target <=> -i in source so bufr1 should get -array1
145     C if pj(1) is 1 then +i in target <=> +j in source so bufr1 should get +array2
146     C if pj(1) is -1 then +i in target <=> -j in source so bufr1 should get -array2
147     sa1 = pi(1)
148     sa2 = pj(1)
149     IF ( .NOT. withSigns ) THEN
150     sa1 = ABS(sa1)
151     sa2 = ABS(sa2)
152     ENDIF
153     C if pi(1) is 1 then +i in source aligns with +i in target
154     C if pj(1) is 1 then +i in source aligns with +j in target
155     #ifdef W2_E2_DEBUG_ON
156     WRITE(msgBuf,'(A,I5,A,I5)')
157     & 'EXCH2_PUT_RX2 sourceTile=', thisTile, ' targetTile=', tgT
158     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
159     I SQUEEZE_BOTH, myThid )
160     #endif /* W2_E2_DEBUG_ON */
161     iBufr1=0
162     DO ktl=tKlo,tKhi,tkStride
163     DO jtl=tJlo1, tJhi1, tjStride
164     DO itl=tIlo1, tIhi1, tiStride
165     iBufr1=iBufr1+1
166     itc = itl+itb
167     jtc = jtl+jtb
168     isc = pi(1)*itc+pi(2)*jtc+oIs1
169     jsc = pj(1)*itc+pj(2)*jtc+oJs1
170     isl = isc-isb
171     jsl = jsc-jsb
172     #ifdef W2_E2_DEBUG_ON
173     WRITE(msgBuf,'(A,2I4)')
174     & 'EXCH2_PUT_RX2 target u(itl, jtl) = ', itl, jtl
175     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
176     I SQUEEZE_RIGHT, myThid )
177     IF ( pi(1) .EQ. 1 ) THEN
178     C i index aligns
179     WRITE(msgBuf,'(A,2I4)')
180     & ' source +u(isl, jsl) = ', isl, jsl
181     ELSEIF ( pi(1) .EQ. -1 ) THEN
182     C reversed i index aligns
183     WRITE(msgBuf,'(A,2I4)')
184     & ' source -u(isl, jsl) = ', isl, jsl
185     ELSEIF ( pj(1) .EQ. 1 ) THEN
186     WRITE(msgBuf,'(A,2I4)')
187     & ' source +v(isl, jsl) = ', isl, jsl
188     ELSEIF ( pj(1) .EQ. -1 ) THEN
189     WRITE(msgBuf,'(A,2I4)')
190     & ' source -v(isl, jsl) = ', isl, jsl
191     ENDIF
192     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
193     I SQUEEZE_RIGHT, myThid )
194     IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
195     WRITE(msgBuf,'(A,2I4)')
196     & ' *** isl is out of bounds '
197     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
198     I SQUEEZE_RIGHT, myThid )
199     ENDIF
200     IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
201     WRITE(msgBuf,'(A,2I4)')
202     & ' *** jsl is out of bounds '
203     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
204     I SQUEEZE_RIGHT, myThid )
205     ENDIF
206     #endif /* W2_E2_DEBUG_ON */
207     #ifdef W2_USE_E2_SAFEMODE
208     IF ( iBufr1 .GT. e2BufrRecSize ) THEN
209     C Ran off end of buffer. This should not happen
210     STOP 'EXCH2_PUT_RX2:: E2BUFR LIMIT EXCEEDED'
211     ENDIF
212     IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
213     C Forward mode send getting from points outside of the
214     C tiles exclusive domain bounds in X. This should not happen
215     WRITE(msgBuf,'(A,I4,I4)')
216     & 'EXCH2_PUT_RX2 tIlo1,tIhi1=', tIlo1, tIhi1
217     CALL PRINT_ERROR (msgBuf, myThid )
218     WRITE(msgBuf,'(A,3I4)')
219     & 'EXCH2_PUT_RX2 itl, jtl, isl =', itl, jtl, isl
220     CALL PRINT_ERROR (msgBuf, myThid )
221     STOP 'EXCH2_PUT_RX2:: ISL OUTSIDE TILE EXCLUSIVE DOMAIN'
222     ENDIF
223     IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
224     C Forward mode send getting from points outside of the
225     C tiles exclusive domain bounds in Y. This should not happen
226     WRITE(msgBuf,'(A,I4,I4)')
227     & 'EXCH2_PUT_RX2 tJlo1,tJhi1=', tJlo1, tJhi1
228     CALL PRINT_ERROR (msgBuf, myThid )
229     WRITE(msgBuf,'(A,2I4)')
230     & 'EXCH2_PUT_RX2 itl, jtl =', itl, jtl
231     CALL PRINT_ERROR (msgBuf, myThid )
232     WRITE(msgBuf,'(A,2I4)')
233     & 'EXCH2_PUT_RX2 isl, jsl =', isl, jsl
234     CALL PRINT_ERROR (msgBuf, myThid )
235     STOP 'EXCH2_PUT_RX2:: JSL OUTSIDE TILE EXCLUSIVE DOMAIN'
236     ENDIF
237     #endif /* W2_USE_E2_SAFEMODE */
238     val1 = sa1*array1(isl,jsl,ktl)
239     & + sa2*array2(isl,jsl,ktl)
240     e2Bufr1_RX(iBufr1) = val1
241     ENDDO
242     ENDDO
243     ENDDO
244    
245     C Extract values into bufr2
246     C if pi(2) is 1 then +j in target <=> +i in source so bufr1 should get +array1
247     C if pi(2) is -1 then +j in target <=> -i in source so bufr1 should get -array1
248     C if pj(2) is 1 then +j in target <=> +j in source so bufr1 should get +array2
249     C if pj(2) is -1 then +j in target <=> -j in source so bufr1 should get -array2
250     sa1 = pi(2)
251     sa2 = pj(2)
252     IF ( .NOT. withSigns ) THEN
253     sa1 = ABS(sa1)
254     sa2 = ABS(sa2)
255     ENDIF
256     iBufr2=0
257     DO ktl=tKlo,tKhi,tkStride
258     DO jtl=tJlo2, tJhi2, tjStride
259     DO itl=tIlo2, tIhi2, tiStride
260     iBufr2=iBufr2+1
261     itc = itl+itb
262     jtc = jtl+jtb
263     isc = pi(1)*itc+pi(2)*jtc+oIs2
264     jsc = pj(1)*itc+pj(2)*jtc+oJs2
265     isl = isc-isb
266     jsl = jsc-jsb
267     #ifdef W2_E2_DEBUG_ON
268     WRITE(msgBuf,'(A,2I4)')
269     & 'EXCH2_PUT_RX2 target v(itl, jtl) = ', itl, jtl
270     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
271     I SQUEEZE_RIGHT, myThid )
272     IF ( pi(2) .EQ. 1 ) THEN
273     C i index aligns
274     WRITE(msgBuf,'(A,2I4)')
275     & ' source +u(isl, jsl) = ', isl, jsl
276     ELSEIF ( pi(2) .EQ. -1 ) THEN
277     C reversed i index aligns
278     WRITE(msgBuf,'(A,2I4)')
279     & ' source -u(isl, jsl) = ', isl, jsl
280     ELSEIF ( pj(2) .EQ. 1 ) THEN
281     WRITE(msgBuf,'(A,2I4)')
282     & ' source +v(isl, jsl) = ', isl, jsl
283     ELSEIF ( pj(2) .EQ. -1 ) THEN
284     WRITE(msgBuf,'(A,2I4)')
285     & ' source -v(isl, jsl) = ', isl, jsl
286     ENDIF
287     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
288     I SQUEEZE_RIGHT, myThid )
289     IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
290     WRITE(msgBuf,'(A,2I4)')
291     & ' *** isl is out of bounds '
292     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
293     I SQUEEZE_RIGHT, myThid )
294     ENDIF
295     IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
296     WRITE(msgBuf,'(A,2I4)')
297     & ' *** jsl is out of bounds '
298     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
299     I SQUEEZE_RIGHT, myThid )
300     ENDIF
301     #endif /* W2_E2_DEBUG_ON */
302     #ifdef W2_USE_E2_SAFEMODE
303     IF ( iBufr2 .GT. e2BufrRecSize ) THEN
304     C Ran off end of buffer. This should not happen
305     STOP 'EXCH2_PUT_RX2:: E2BUFR LIMIT EXCEEDED'
306     ENDIF
307     IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
308     C Forward mode send getting from points outside of the
309     C tiles exclusive domain bounds in X. This should not happen
310     WRITE(msgBuf,'(A,I4,I4)')
311     & 'EXCH2_PUT_RX2 tIlo2,tIhi2=', tIlo2, tIhi2
312     CALL PRINT_ERROR (msgBuf, myThid )
313     WRITE(msgBuf,'(A,3I4)')
314     & 'EXCH2_PUT_RX2 itl, jtl, isl =', itl, jtl, isl
315     CALL PRINT_ERROR (msgBuf, myThid )
316     STOP 'EXCH2_PUT_RX2:: ISL OUTSIDE TILE EXCLUSIVE DOMAIN'
317     ENDIF
318     IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
319     C Forward mode send getting from points outside of the
320     C tiles exclusive domain bounds in Y. This should not happen
321     WRITE(msgBuf,'(A,I4,I4)')
322     & 'EXCH2_PUT_RX2 tJlo2,tJhi2=', tJlo2, tJhi2
323     CALL PRINT_ERROR (msgBuf, myThid )
324     WRITE(msgBuf,'(A,2I4)')
325     & 'EXCH2_PUT_RX2 itl, jtl =', itl, jtl
326     CALL PRINT_ERROR (msgBuf, myThid )
327     WRITE(msgBuf,'(A,2I4)')
328     & 'EXCH2_PUT_RX2 isl, jsl =', isl, jsl
329     CALL PRINT_ERROR (msgBuf, myThid )
330     STOP 'EXCH2_PUT_RX2:: JSL OUTSIDE TILE EXCLUSIVE DOMAIN'
331     ENDIF
332     #endif /* W2_USE_E2_SAFEMODE */
333     val2 = sa1*array1(isl,jsl,ktl)
334     & + sa2*array2(isl,jsl,ktl)
335     e2Bufr2_RX(iBufr2) = val2
336     ENDDO
337     ENDDO
338     ENDDO
339    
340     RETURN
341     END
342    
343     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
344    
345     CEH3 ;;; Local Variables: ***
346     CEH3 ;;; mode:fortran ***
347     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22