/[MITgcm]/MITgcm/pkg/flt/flt_exchg.F
ViewVC logotype

Contents of /MITgcm/pkg/flt/flt_exchg.F

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


Revision 1.17 - (show annotations) (download)
Thu Sep 6 16:13:53 2012 UTC (11 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint64, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65o, checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, HEAD
Changes since 1.16: +5 -5 lines
- finish to remove ALWAYS_USE_MPI in source code that TAF does not see.
- rename S/R EXCH_RL_SEND_PUT_VEC_[X,Y] -> EXCH_SEND_PUT_VEC_[X,Y]_RL
     and S/R EXCH_RL_RECV_GET_VEC_[X,Y] -> EXCH_RECV_GET_VEC_[X,Y]_RL
  so that it closer to file names (exch_send_put_vec.F, exch_recv_get_vec.F)
  and match the printed messages.

1 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_exchg.F,v 1.16 2012/08/30 22:32:48 jmc Exp $
2 C $Name: $
3
4 #include "FLT_OPTIONS.h"
5 #undef DBUG_EXCH_VEC
6
7 SUBROUTINE FLT_EXCHG (
8 I myTime, myIter, myThid )
9
10 C ==================================================================
11 C SUBROUTINE FLT_EXCHG
12 C ==================================================================
13 C o Exchange particles between tiles.
14 C started: Arne Biastoch
15 C changed: Antti Westerlund antti.westerlund@helsinki.fi 2004.06.10
16 C ==================================================================
17
18 C !USES:
19 IMPLICIT NONE
20
21 C == global variables ==
22 #include "SIZE.h"
23 #include "EEPARAMS.h"
24 #include "PARAMS.h"
25 #include "FLT_SIZE.h"
26 #include "FLT.h"
27
28 C == routine arguments ==
29 _RL myTime
30 INTEGER myIter, myThid
31
32 C == shared variables ==
33 C- buffer for sending/receiving variables (E/W are also used for S/N)
34 C (needs to be in common block for multi-threaded)
35 INTEGER imax, imax2
36 PARAMETER(imax=9)
37 PARAMETER(imax2=imax*max_npart_exch)
38 _RL fltbuf_sendE(imax2,nSx,nSy)
39 _RL fltbuf_sendW(imax2,nSx,nSy)
40 _RL fltbuf_recvE(imax2,nSx,nSy)
41 _RL fltbuf_recvW(imax2,nSx,nSy)
42 COMMON / FLT_EXCHG_BUFF /
43 & fltbuf_sendE, fltbuf_sendW, fltbuf_recvE, fltbuf_recvW
44
45 C == local variables ==
46 INTEGER bi, bj, ic
47 INTEGER ip, jp, jl, m, npNew
48 INTEGER icountE, icountW, icountN, icountS
49 INTEGER deleteList(max_npart_exch*2)
50 _RL ilo, ihi, jlo, jhi, iNew, jNew
51 CHARACTER*(MAX_LEN_MBUF) msgBuf
52 #ifdef FLT_WITHOUT_X_PERIODICITY
53 LOGICAL wSide, eSide
54 #endif /* FLT_WITHOUT_X_PERIODICITY */
55 #ifdef FLT_WITHOUT_Y_PERIODICITY
56 LOGICAL sSide, nSide
57 #endif /* FLT_WITHOUT_Y_PERIODICITY */
58 _RL flt_stopped
59
60 C == end of interface ==
61
62 C-- set the "end-time" of a stopped float
63 flt_stopped = -2.
64 flt_stopped = MIN( baseTime, flt_stopped )
65
66 Caw Check if there are eastern/western tiles
67 c IF ( Nx.NE.sNx ) THEN
68 C-- for periodic domain, condition above is wrong ; needs a better test
69 IF ( .TRUE. ) THEN
70
71 C-- Choose floats that have to exchanged with eastern and western tiles
72 C and pack to arrays
73
74 DO bj=myByLo(myThid),myByHi(myThid)
75 DO bi=myBxLo(myThid),myBxHi(myThid)
76
77 C initialize buffers
78 DO m=1,imax2
79 fltbuf_sendE(m,bi,bj) = 0.
80 fltbuf_sendW(m,bi,bj) = 0.
81 fltbuf_recvE(m,bi,bj) = 0.
82 fltbuf_recvW(m,bi,bj) = 0.
83 ENDDO
84
85 icountE=0
86 icountW=0
87 jl = 0
88
89 ilo = 0.5 _d 0
90 ihi = 0.5 _d 0 + DFLOAT(sNx)
91 #ifdef FLT_WITHOUT_X_PERIODICITY
92 wSide = myXGlobalLo+bi .LE.2
93 eSide = myXGlobalLo+bi*sNx.GT.Nx
94 #endif /* FLT_WITHOUT_X_PERIODICITY */
95
96 DO ip=1,npart_tile(bi,bj)
97
98 #ifdef FLT_WITHOUT_X_PERIODICITY
99 IF ( eSide .AND.
100 & (myTime.LE.tend(ip,bi,bj) .OR. tend(ip,bi,bj).EQ.-1.)
101 & .AND. ipart(ip,bi,bj).GE.ihi ) THEN
102 C stop the float:
103 tend(ip,bi,bj) = flt_stopped
104 ELSEIF ( ipart(ip,bi,bj).GE.ihi ) THEN
105 #else /* FLT_WITHOUT_X_PERIODICITY */
106 IF ( ipart(ip,bi,bj).GE.ihi ) THEN
107 #endif /* FLT_WITHOUT_X_PERIODICITY */
108 icountE=icountE+1
109 IF ( icountE.LE.max_npart_exch ) THEN
110
111 ic = (icountE-1)*imax
112 iNew = ipart(ip,bi,bj) - DFLOAT(sNx)
113 fltbuf_sendE(ic+1,bi,bj) = npart(ip,bi,bj)
114 fltbuf_sendE(ic+2,bi,bj) = tstart(ip,bi,bj)
115 fltbuf_sendE(ic+3,bi,bj) = iNew
116 fltbuf_sendE(ic+4,bi,bj) = jpart(ip,bi,bj)
117 fltbuf_sendE(ic+5,bi,bj) = kpart(ip,bi,bj)
118 fltbuf_sendE(ic+6,bi,bj) = kfloat(ip,bi,bj)
119 fltbuf_sendE(ic+7,bi,bj) = iup(ip,bi,bj)
120 fltbuf_sendE(ic+8,bi,bj) = itop(ip,bi,bj)
121 fltbuf_sendE(ic+9,bi,bj) = tend(ip,bi,bj)
122
123 C tag this float to be removed:
124 jl = jl + 1
125 deleteList(jl) = ip
126 npart(ip,bi,bj) = 0.
127
128 ENDIF
129 ENDIF
130
131 #ifdef FLT_WITHOUT_X_PERIODICITY
132 IF ( wSide .AND.
133 & (myTime.LE.tend(ip,bi,bj) .OR. tend(ip,bi,bj).EQ.-1.)
134 & .AND. ipart(ip,bi,bj).LT.ilo ) THEN
135 C stop the float:
136 tend(ip,bi,bj) = flt_stopped
137 ELSEIF ( ipart(ip,bi,bj).LT.ilo ) THEN
138 #else /* FLT_WITHOUT_X_PERIODICITY */
139 IF ( ipart(ip,bi,bj).LT.ilo ) THEN
140 #endif /* FLT_WITHOUT_X_PERIODICITY */
141 icountW=icountW+1
142 IF ( icountW.LE.max_npart_exch ) THEN
143
144 ic = (icountW-1)*imax
145 iNew = ipart(ip,bi,bj) + DFLOAT(sNx)
146 fltbuf_sendW(ic+1,bi,bj) = npart(ip,bi,bj)
147 fltbuf_sendW(ic+2,bi,bj) = tstart(ip,bi,bj)
148 fltbuf_sendW(ic+3,bi,bj) = iNew
149 fltbuf_sendW(ic+4,bi,bj) = jpart(ip,bi,bj)
150 fltbuf_sendW(ic+5,bi,bj) = kpart(ip,bi,bj)
151 fltbuf_sendW(ic+6,bi,bj) = kfloat(ip,bi,bj)
152 fltbuf_sendW(ic+7,bi,bj) = iup(ip,bi,bj)
153 fltbuf_sendW(ic+8,bi,bj) = itop(ip,bi,bj)
154 fltbuf_sendW(ic+9,bi,bj) = tend(ip,bi,bj)
155
156 C tag this float to be removed:
157 jl = jl + 1
158 deleteList(jl) = ip
159 npart(ip,bi,bj) = 0.
160
161 ENDIF
162 ENDIF
163
164 ENDDO
165 IF ( icountE.GT.max_npart_exch ) THEN
166 WRITE(msgBuf,'(2A,2I4,2(A,I8))') ' FLT_EXCHG:',
167 & ' bi,bj=', bi, bj,
168 & ' icountE=', icountE,
169 & ' > max_npart_exch=', max_npart_exch
170 CALL PRINT_ERROR( msgBuf, myThid )
171 ENDIF
172 IF ( icountW.GT.max_npart_exch ) THEN
173 WRITE(msgBuf,'(2A,2I4,2(A,I8))') ' FLT_EXCHG:',
174 & ' bi,bj=', bi, bj,
175 & ' icountW=', icountW,
176 & ' > max_npart_exch=', max_npart_exch
177 CALL PRINT_ERROR( msgBuf, myThid )
178 ENDIF
179 IF ( icountE.GT.max_npart_exch
180 & .OR. icountW.GT.max_npart_exch ) THEN
181 STOP 'ABNORMAL END: S/R FLT_EXCHG'
182 ENDIF
183 IF ( (icountE+icountW).GT.0 ) THEN
184 C Remove from this tile-list, floats which have been sent to an other tile
185 npNew = npart_tile(bi,bj) - (icountE+icountW)
186 jl = 0
187 DO jp = npNew+1,npart_tile(bi,bj)
188 IF ( npart(jp,bi,bj).NE.0. _d 0 ) THEN
189 jl = jl + 1
190 ip = deleteList(jl)
191 C copy: ip <-- jp
192 npart (ip,bi,bj) = npart (jp,bi,bj)
193 tstart(ip,bi,bj) = tstart(jp,bi,bj)
194 ipart (ip,bi,bj) = ipart (jp,bi,bj)
195 jpart (ip,bi,bj) = jpart (jp,bi,bj)
196 kpart (ip,bi,bj) = kpart (jp,bi,bj)
197 kfloat(ip,bi,bj) = kfloat(jp,bi,bj)
198 iup (ip,bi,bj) = iup (jp,bi,bj)
199 itop (ip,bi,bj) = itop (jp,bi,bj)
200 tend (ip,bi,bj) = tend (jp,bi,bj)
201 ENDIF
202 ENDDO
203 npart_tile(bi,bj) = npNew
204 ENDIF
205
206 ENDDO
207 ENDDO
208
209 C-- Send or Put east and west edges.
210
211 #ifdef DBUG_EXCH_VEC
212 WRITE(errorMessageUnit,'(A,I8)') 'FLT_EXCH: 0x', myIter
213 #endif
214 CALL EXCH_SEND_PUT_VEC_X_RL(
215 I fltbuf_sendE, fltbuf_sendW,
216 O fltbuf_recvE, fltbuf_recvW,
217 I imax2, myThid )
218 #ifdef DBUG_EXCH_VEC
219 WRITE(errorMessageUnit,'(A,I8)') 'FLT_EXCH: 1x', myIter
220 #endif
221 C-- Receive east/west arrays
222 CALL EXCH_RECV_GET_VEC_X_RL(
223 U fltbuf_recvE, fltbuf_recvW,
224 I imax2, myThid )
225 #ifdef DBUG_EXCH_VEC
226 WRITE(errorMessageUnit,'(A,I8)') 'FLT_EXCH: 2x', myIter
227 #endif
228
229 C-- Unpack arrays on new tiles
230
231 DO bj=myByLo(myThid),myByHi(myThid)
232 DO bi=myBxLo(myThid),myBxHi(myThid)
233
234 DO ip=1,max_npart_exch
235
236 ic=(ip-1)*imax
237 IF ( fltbuf_recvE(ic+1,bi,bj).NE.0. ) THEN
238 npart_tile(bi,bj) = npart_tile(bi,bj) + 1
239 IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
240 jp = npart_tile(bi,bj)
241 npart( jp,bi,bj) = fltbuf_recvE(ic+1,bi,bj)
242 tstart(jp,bi,bj) = fltbuf_recvE(ic+2,bi,bj)
243 ipart( jp,bi,bj) = fltbuf_recvE(ic+3,bi,bj)
244 jpart( jp,bi,bj) = fltbuf_recvE(ic+4,bi,bj)
245 kpart( jp,bi,bj) = fltbuf_recvE(ic+5,bi,bj)
246 kfloat(jp,bi,bj) = fltbuf_recvE(ic+6,bi,bj)
247 iup( jp,bi,bj) = fltbuf_recvE(ic+7,bi,bj)
248 itop( jp,bi,bj) = fltbuf_recvE(ic+8,bi,bj)
249 tend( jp,bi,bj) = fltbuf_recvE(ic+9,bi,bj)
250 ENDIF
251 ENDIF
252
253 ENDDO
254 IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
255 WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_EXCHG:+E',
256 & ' bi,bj=', bi, bj,
257 & ' npart_tile=', npart_tile(bi,bj),
258 & ' > max_npart_tile=', max_npart_tile
259 CALL PRINT_ERROR( msgBuf, myThid )
260 STOP 'ABNORMAL END: S/R FLT_EXCHG'
261 ENDIF
262
263 DO ip=1,max_npart_exch
264
265 ic=(ip-1)*imax
266 IF ( fltbuf_recvW(ic+1,bi,bj).NE.0. ) THEN
267 npart_tile(bi,bj) = npart_tile(bi,bj) + 1
268 IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
269 jp = npart_tile(bi,bj)
270 npart( jp,bi,bj) = fltbuf_recvW(ic+1,bi,bj)
271 tstart(jp,bi,bj) = fltbuf_recvW(ic+2,bi,bj)
272 ipart( jp,bi,bj) = fltbuf_recvW(ic+3,bi,bj)
273 jpart( jp,bi,bj) = fltbuf_recvW(ic+4,bi,bj)
274 kpart( jp,bi,bj) = fltbuf_recvW(ic+5,bi,bj)
275 kfloat(jp,bi,bj) = fltbuf_recvW(ic+6,bi,bj)
276 iup( jp,bi,bj) = fltbuf_recvW(ic+7,bi,bj)
277 itop( jp,bi,bj) = fltbuf_recvW(ic+8,bi,bj)
278 tend( jp,bi,bj) = fltbuf_recvW(ic+9,bi,bj)
279 ENDIF
280 ENDIF
281
282 ENDDO
283 IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
284 WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_EXCHG:+W',
285 & ' bi,bj=', bi, bj,
286 & ' npart_tile=', npart_tile(bi,bj),
287 & ' > max_npart_tile=', max_npart_tile
288 CALL PRINT_ERROR( msgBuf, myThid )
289 STOP 'ABNORMAL END: S/R FLT_EXCHG'
290 ENDIF
291
292 ENDDO
293 ENDDO
294
295 Caw end tile check
296 ENDIF
297
298 C-- Choose floats that have to exchanged with northern and southern tiles
299 C and pack to arrays
300
301 Caw Check if there are northern/southern tiles
302 c IF ( Ny.NE.sNy ) THEN
303 C-- for periodic domain, condition above is wrong ; needs a better test
304 IF ( .TRUE. ) THEN
305
306 DO bj=myByLo(myThid),myByHi(myThid)
307 DO bi=myBxLo(myThid),myBxHi(myThid)
308
309 C initialize buffers
310
311 DO m=1,imax2
312 fltbuf_sendE(m,bi,bj) = 0.
313 fltbuf_sendW(m,bi,bj) = 0.
314 fltbuf_recvE(m,bi,bj) = 0.
315 fltbuf_recvW(m,bi,bj) = 0.
316 ENDDO
317
318 icountN=0
319 icountS=0
320 jl = 0
321
322 jlo = 0.5 _d 0
323 jhi = 0.5 _d 0 + DFLOAT(sNy)
324 #ifdef FLT_WITHOUT_Y_PERIODICITY
325 sSide = myYGlobalLo+bj .LE.2
326 nSide = myYGlobalLo+bj*sNy.GT.Ny
327 #endif /* FLT_WITHOUT_Y_PERIODICITY */
328
329 DO ip=1,npart_tile(bi,bj)
330
331 #ifdef FLT_WITHOUT_Y_PERIODICITY
332 IF ( nSide .AND.
333 & (myTime.LE.tend(ip,bi,bj) .OR. tend(ip,bi,bj).EQ.-1.)
334 & .AND. jpart(ip,bi,bj).GE.jhi ) THEN
335 C stop the float:
336 tend(ip,bi,bj) = flt_stopped
337 ELSEIF ( jpart(ip,bi,bj).GE.jhi ) THEN
338 #else /* FLT_WITHOUT_Y_PERIODICITY */
339 IF ( jpart(ip,bi,bj).GE.jhi ) THEN
340 #endif /* FLT_WITHOUT_Y_PERIODICITY */
341 icountN=icountN+1
342 IF ( icountN.LE.max_npart_exch ) THEN
343
344 ic = (icountN-1)*imax
345 jNew = jpart(ip,bi,bj) - DFLOAT(sNy)
346 fltbuf_sendE(ic+1,bi,bj) = npart(ip,bi,bj)
347 fltbuf_sendE(ic+2,bi,bj) = tstart(ip,bi,bj)
348 fltbuf_sendE(ic+3,bi,bj) = ipart(ip,bi,bj)
349 fltbuf_sendE(ic+4,bi,bj) = jNew
350 fltbuf_sendE(ic+5,bi,bj) = kpart(ip,bi,bj)
351 fltbuf_sendE(ic+6,bi,bj) = kfloat(ip,bi,bj)
352 fltbuf_sendE(ic+7,bi,bj) = iup(ip,bi,bj)
353 fltbuf_sendE(ic+8,bi,bj) = itop(ip,bi,bj)
354 fltbuf_sendE(ic+9,bi,bj) = tend(ip,bi,bj)
355
356 C tag this float to be removed:
357 jl = jl + 1
358 deleteList(jl) = ip
359 npart(ip,bi,bj) = 0.
360
361 c ELSE
362 c WRITE(msgBuf,'(2A,2I4,I6,A,2F17.6))') ' FLT_EXCHG,N:',
363 c & ' bi,bj,ip=', bi, bj, ip,
364 c & ' yp,yHi=', jpart(ip,bi,bj), jhi
365 c CALL PRINT_ERROR( msgBuf, myThid )
366 ENDIF
367 ENDIF
368
369 #ifdef FLT_WITHOUT_Y_PERIODICITY
370 IF ( sSide .AND.
371 & (myTime.LE.tend(ip,bi,bj) .OR. tend(ip,bi,bj).EQ.-1.)
372 & .AND. jpart(ip,bi,bj).LT.jlo ) THEN
373 C stop the float:
374 tend(ip,bi,bj) = flt_stopped
375 ELSEIF ( jpart(ip,bi,bj).LT.jlo ) THEN
376 #else /* FLT_WITHOUT_Y_PERIODICITY */
377 IF ( jpart(ip,bi,bj).LT.jlo ) THEN
378 #endif /* FLT_WITHOUT_Y_PERIODICITY */
379 icountS=icountS+1
380 IF ( icountS.LE.max_npart_exch ) THEN
381
382 ic = (icountS-1)*imax
383 jNew = jpart(ip,bi,bj) + DFLOAT(sNy)
384 fltbuf_sendW(ic+1,bi,bj) = npart(ip,bi,bj)
385 fltbuf_sendW(ic+2,bi,bj) = tstart(ip,bi,bj)
386 fltbuf_sendW(ic+3,bi,bj) = ipart(ip,bi,bj)
387 fltbuf_sendW(ic+4,bi,bj) = jNew
388 fltbuf_sendW(ic+5,bi,bj) = kpart(ip,bi,bj)
389 fltbuf_sendW(ic+6,bi,bj) = kfloat(ip,bi,bj)
390 fltbuf_sendW(ic+7,bi,bj) = iup(ip,bi,bj)
391 fltbuf_sendW(ic+8,bi,bj) = itop(ip,bi,bj)
392 fltbuf_sendW(ic+9,bi,bj) = tend(ip,bi,bj)
393
394 C tag this float to be removed:
395 jl = jl + 1
396 deleteList(jl) = ip
397 npart(ip,bi,bj) = 0.
398
399 c ELSE
400 c WRITE(msgBuf,'(2A,2I4,I6,A,2F17.6))') ' FLT_EXCHG,S:',
401 c & ' bi,bj,ip=', bi, bj, ip,
402 c & ' yp,yLo=', jpart(ip,bi,bj), jlo
403 c CALL PRINT_ERROR( msgBuf, myThid )
404 ENDIF
405 ENDIF
406
407 ENDDO
408 IF ( icountN.GT.max_npart_exch ) THEN
409 WRITE(msgBuf,'(2A,2I4,2(A,I8))') ' FLT_EXCHG:',
410 & ' bi,bj=', bi, bj,
411 & ' icountN=', icountN,
412 & ' > max_npart_exch=', max_npart_exch
413 CALL PRINT_ERROR( msgBuf, myThid )
414 ENDIF
415 IF ( icountS.GT.max_npart_exch ) THEN
416 WRITE(msgBuf,'(2A,2I4,2(A,I8))') ' FLT_EXCHG:',
417 & ' bi,bj=', bi, bj,
418 & ' icountS=', icountS,
419 & ' > max_npart_exch=', max_npart_exch
420 CALL PRINT_ERROR( msgBuf, myThid )
421 ENDIF
422 IF ( icountN.GT.max_npart_exch
423 & .OR. icountS.GT.max_npart_exch ) THEN
424 STOP 'ABNORMAL END: S/R FLT_EXCHG'
425 ENDIF
426 IF ( (icountN+icountS).GT.0 ) THEN
427 C Remove from this tile-list, floats which have been sent to an other tile
428 npNew = npart_tile(bi,bj) - (icountN+icountS)
429 jl = 0
430 DO jp = npNew+1,npart_tile(bi,bj)
431 IF ( npart(jp,bi,bj).NE.0. _d 0 ) THEN
432 jl = jl + 1
433 ip = deleteList(jl)
434 C copy: ip <-- jp
435 npart (ip,bi,bj) = npart (jp,bi,bj)
436 tstart(ip,bi,bj) = tstart(jp,bi,bj)
437 ipart (ip,bi,bj) = ipart (jp,bi,bj)
438 jpart (ip,bi,bj) = jpart (jp,bi,bj)
439 kpart (ip,bi,bj) = kpart (jp,bi,bj)
440 kfloat(ip,bi,bj) = kfloat(jp,bi,bj)
441 iup (ip,bi,bj) = iup (jp,bi,bj)
442 itop (ip,bi,bj) = itop (jp,bi,bj)
443 tend (ip,bi,bj) = tend (jp,bi,bj)
444 ENDIF
445 ENDDO
446 npart_tile(bi,bj) = npNew
447 ENDIF
448
449 ENDDO
450 ENDDO
451
452 C Send or Put north and south arrays.
453 #ifdef DBUG_EXCH_VEC
454 WRITE(errorMessageUnit,'(A,I8)') 'FLT_EXCH: 0y', myIter
455 #endif
456 CALL EXCH_SEND_PUT_VEC_Y_RL(
457 I fltbuf_sendE, fltbuf_sendW,
458 O fltbuf_recvE, fltbuf_recvW,
459 I imax2, myThid )
460 #ifdef DBUG_EXCH_VEC
461 WRITE(errorMessageUnit,'(A,I8)') 'FLT_EXCH: 1y', myIter
462 #endif
463 C Receive north and south arrays
464 CALL EXCH_RECV_GET_VEC_Y_RL(
465 U fltbuf_recvE, fltbuf_recvW,
466 I imax2, myThid )
467 #ifdef DBUG_EXCH_VEC
468 WRITE(errorMessageUnit,'(A,I8)') 'FLT_EXCH: 2y', myIter
469 c STOP 'FLT_EXCHG: Normal End'
470 #endif
471
472 C-- Unpack arrays on new tiles
473
474 DO bj=myByLo(myThid),myByHi(myThid)
475 DO bi=myBxLo(myThid),myBxHi(myThid)
476
477 DO ip=1,max_npart_exch
478
479 ic=(ip-1)*imax
480 IF ( fltbuf_recvE(ic+1,bi,bj).NE.0. ) THEN
481 npart_tile(bi,bj) = npart_tile(bi,bj) + 1
482 IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
483 jp = npart_tile(bi,bj)
484 npart( jp,bi,bj) = fltbuf_recvE(ic+1,bi,bj)
485 tstart(jp,bi,bj) = fltbuf_recvE(ic+2,bi,bj)
486 ipart( jp,bi,bj) = fltbuf_recvE(ic+3,bi,bj)
487 jpart( jp,bi,bj) = fltbuf_recvE(ic+4,bi,bj)
488 kpart( jp,bi,bj) = fltbuf_recvE(ic+5,bi,bj)
489 kfloat(jp,bi,bj) = fltbuf_recvE(ic+6,bi,bj)
490 iup( jp,bi,bj) = fltbuf_recvE(ic+7,bi,bj)
491 itop( jp,bi,bj) = fltbuf_recvE(ic+8,bi,bj)
492 tend( jp,bi,bj) = fltbuf_recvE(ic+9,bi,bj)
493 ENDIF
494 ENDIF
495
496 ENDDO
497 IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
498 WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_EXCHG:+N',
499 & ' bi,bj=', bi, bj,
500 & ' npart_tile=', npart_tile(bi,bj),
501 & ' > max_npart_tile=', max_npart_tile
502 CALL PRINT_ERROR( msgBuf, myThid )
503 STOP 'ABNORMAL END: S/R FLT_EXCHG'
504 ENDIF
505
506 DO ip=1,max_npart_exch
507
508 ic=(ip-1)*imax
509 IF ( fltbuf_recvW(ic+1,bi,bj).NE.0. ) THEN
510 npart_tile(bi,bj) = npart_tile(bi,bj) + 1
511 IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
512 jp = npart_tile(bi,bj)
513 npart( jp,bi,bj) = fltbuf_recvW(ic+1,bi,bj)
514 tstart(jp,bi,bj) = fltbuf_recvW(ic+2,bi,bj)
515 ipart( jp,bi,bj) = fltbuf_recvW(ic+3,bi,bj)
516 jpart( jp,bi,bj) = fltbuf_recvW(ic+4,bi,bj)
517 kpart( jp,bi,bj) = fltbuf_recvW(ic+5,bi,bj)
518 kfloat(jp,bi,bj) = fltbuf_recvW(ic+6,bi,bj)
519 iup( jp,bi,bj) = fltbuf_recvW(ic+7,bi,bj)
520 itop( jp,bi,bj) = fltbuf_recvW(ic+8,bi,bj)
521 tend( jp,bi,bj) = fltbuf_recvW(ic+9,bi,bj)
522 ENDIF
523 ENDIF
524
525 ENDDO
526 IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
527 WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_EXCHG:+S',
528 & ' bi,bj=', bi, bj,
529 & ' npart_tile=', npart_tile(bi,bj),
530 & ' > max_npart_tile=', max_npart_tile
531 CALL PRINT_ERROR( msgBuf, myThid )
532 STOP 'ABNORMAL END: S/R FLT_EXCHG'
533 ENDIF
534
535 ENDDO
536 ENDDO
537
538 Caw end tile check
539 ENDIF
540
541 RETURN
542 END

  ViewVC Help
Powered by ViewVC 1.1.22