/[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.14 - (show annotations) (download)
Tue Feb 1 17:08:30 2011 UTC (13 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62s, checkpoint62w, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint63, checkpoint63a, checkpoint63b
Changes since 1.13: +55 -0 lines
add CPP options to prevent floats to re-enter the opposite side of a periodic domain

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

  ViewVC Help
Powered by ViewVC 1.1.22