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

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

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


Revision 1.2 - (show annotations) (download)
Fri Apr 23 20:21:07 2010 UTC (14 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62g, checkpoint62f, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.1: +2 -2 lines
fix propagating typo (& others) in variable description

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

  ViewVC Help
Powered by ViewVC 1.1.22