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

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

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


Revision 1.1 - (show annotations) (download)
Wed Dec 22 21:24:58 2010 UTC (13 years, 5 months ago) by jahn
Branch: MAIN
add exch2 support (1 facet only so far)

1 C $Header$
2 C $Name$
3
4 #include "FLT_OPTIONS.h"
5 #undef DBUG_EXCH_VEC
6 #define FLT_WITHOUT_X_PERIODICITY
7
8 SUBROUTINE FLT_EXCH2 (
9 I myTime, myIter, myThid )
10
11 C ==================================================================
12 C SUBROUTINE FLT_EXCH2
13 C ==================================================================
14 C o Exchange particles between tiles.
15 C started: Arne Biastoch
16 C changed: Antti Westerlund antti.westerlund@helsinki.fi 2004.06.10
17 C adapted to exch2: Oliver Jahn 2010.09
18 C ==================================================================
19
20 C !USES:
21 IMPLICIT NONE
22
23 C == global variables ==
24 #include "SIZE.h"
25 #include "EEPARAMS.h"
26 #include "EESUPPORT.h"
27 #include "PARAMS.h"
28 #include "FLT.h"
29 #ifdef ALLOW_EXCH2
30 #include "W2_EXCH2_SIZE.h"
31 #include "W2_EXCH2_PARAMS.h"
32 #include "W2_EXCH2_TOPOLOGY.h"
33 #include "W2_EXCH2_BUFFER.h"
34 #endif
35
36 C == routine arguments ==
37 _RL myTime
38 INTEGER myIter, myThid
39
40 #ifdef ALLOW_EXCH2
41
42 C == local variables ==
43 INTEGER bi, bj, ic
44 INTEGER ip, jp, jl, npNew
45 INTEGER icountE, icountW, icountN, icountS
46 INTEGER deleteList(max_npart_exch*2)
47 INTEGER imax, imax2, m
48 INTEGER nT, ipass, myFace
49 INTEGER e2_msgHandles( 2, W2_maxNeighbours, nSx, nSy )
50 _RL ilo, ihi, jlo, jhi, iNew, jNew
51 PARAMETER(imax=9)
52 PARAMETER(imax2=imax*max_npart_exch)
53 CHARACTER*(MAX_LEN_MBUF) msgBuf
54 #ifdef ALLOW_USE_MPI
55 C MPI stuff (should be in a routine call)
56 INTEGER mpiStatus(MPI_STATUS_SIZE)
57 INTEGER mpiRc
58 INTEGER wHandle
59 INTEGER nN, N, farTile
60 #endif
61
62
63 C buffer for sending/receiving variables (E/W are also used for S/N)
64 COMMON/FLTBUF/fltbuf_send,fltbuf_recv
65 _RL fltbuf_send(imax2,nSx,nSy,4)
66 _RL fltbuf_recv(imax2,nSx,nSy,4)
67 LOGICAL wSide, eSide, sSide, nSide
68 _RL flt_stopped
69
70 C == end of interface ==
71
72 C have to do 2 passes to get into tiles diagonally across
73 DO ipass=1,2
74
75 C Prevent anyone to access shared buffer while an other thread modifies it
76 CALL BAR2( myThid )
77
78 C-- Choose floats that have to exchanged with eastern and western tiles
79 C and pack to arrays
80
81 DO bj=myByLo(myThid),myByHi(myThid)
82 DO bi=myBxLo(myThid),myBxHi(myThid)
83 nT = W2_myTileList(bi,bj)
84 myFace = exch2_myFace(nT)
85
86 C initialize buffers
87 DO N=1,4
88 DO m=1,imax2
89 fltbuf_send(m,bi,bj,N) = 0.
90 fltbuf_recv(m,bi,bj,N) = 0.
91 ENDDO
92 ENDDO
93
94 icountE=0
95 icountW=0
96 jl = 0
97
98 ilo = 0.5 _d 0
99 ihi = 0.5 _d 0 + DFLOAT(sNx)
100 wSide=exch2_isWedge(nT).AND.facet_link(W2_WEST,myFace).EQ.0.
101 eSide=exch2_isEedge(nT).AND.facet_link(W2_EAST,myFace).EQ.0.
102 flt_stopped = -2.
103 flt_stopped = MIN( baseTime, flt_stopped )
104
105 DO ip=1,npart_tile(bi,bj)
106
107 IF ( eSide .AND.
108 & (myTime.LE.tend(ip,bi,bj) .OR. tend(ip,bi,bj).EQ.-1.)
109 & .AND. ipart(ip,bi,bj).GE.ihi ) THEN
110 C stop the float:
111 tend(ip,bi,bj) = flt_stopped
112 ELSEIF ( ipart(ip,bi,bj).GE.ihi ) THEN
113 icountE=icountE+1
114 IF ( icountE.LE.max_npart_exch ) THEN
115
116 ic = (icountE-1)*imax
117 iNew = ipart(ip,bi,bj) - DFLOAT(sNx)
118 fltbuf_send(ic+1,bi,bj,W2_EAST) = npart(ip,bi,bj)
119 fltbuf_send(ic+2,bi,bj,W2_EAST) = tstart(ip,bi,bj)
120 fltbuf_send(ic+3,bi,bj,W2_EAST) = iNew
121 fltbuf_send(ic+4,bi,bj,W2_EAST) = jpart(ip,bi,bj)
122 fltbuf_send(ic+5,bi,bj,W2_EAST) = kpart(ip,bi,bj)
123 fltbuf_send(ic+6,bi,bj,W2_EAST) = kfloat(ip,bi,bj)
124 fltbuf_send(ic+7,bi,bj,W2_EAST) = iup(ip,bi,bj)
125 fltbuf_send(ic+8,bi,bj,W2_EAST) = itop(ip,bi,bj)
126 fltbuf_send(ic+9,bi,bj,W2_EAST) = tend(ip,bi,bj)
127
128 C tag this float to be removed:
129 jl = jl + 1
130 deleteList(jl) = ip
131 npart(ip,bi,bj) = 0.
132
133 ENDIF
134 ENDIF
135
136 IF ( wSide .AND.
137 & (myTime.LE.tend(ip,bi,bj) .OR. tend(ip,bi,bj).EQ.-1.)
138 & .AND. ipart(ip,bi,bj).LT.ilo ) THEN
139 C stop the float:
140 tend(ip,bi,bj) = flt_stopped
141 ELSEIF ( ipart(ip,bi,bj).LT.ilo ) THEN
142 icountW=icountW+1
143 IF ( icountW.LE.max_npart_exch ) THEN
144
145 ic = (icountW-1)*imax
146 iNew = ipart(ip,bi,bj) + DFLOAT(sNx)
147 fltbuf_send(ic+1,bi,bj,W2_WEST) = npart(ip,bi,bj)
148 fltbuf_send(ic+2,bi,bj,W2_WEST) = tstart(ip,bi,bj)
149 fltbuf_send(ic+3,bi,bj,W2_WEST) = iNew
150 fltbuf_send(ic+4,bi,bj,W2_WEST) = jpart(ip,bi,bj)
151 fltbuf_send(ic+5,bi,bj,W2_WEST) = kpart(ip,bi,bj)
152 fltbuf_send(ic+6,bi,bj,W2_WEST) = kfloat(ip,bi,bj)
153 fltbuf_send(ic+7,bi,bj,W2_WEST) = iup(ip,bi,bj)
154 fltbuf_send(ic+8,bi,bj,W2_WEST) = itop(ip,bi,bj)
155 fltbuf_send(ic+9,bi,bj,W2_WEST) = tend(ip,bi,bj)
156
157 C tag this float to be removed:
158 jl = jl + 1
159 deleteList(jl) = ip
160 npart(ip,bi,bj) = 0.
161
162 ENDIF
163 ENDIF
164
165 ENDDO
166 IF ( icountE.GT.max_npart_exch ) THEN
167 WRITE(msgBuf,'(2A,2I4,2(A,I8))') ' FLT_EXCH2:',
168 & ' bi,bj=', bi, bj,
169 & ' icountE=', icountE,
170 & ' > max_npart_exch=', max_npart_exch
171 CALL PRINT_ERROR( msgBuf, myThid )
172 ENDIF
173 IF ( icountW.GT.max_npart_exch ) THEN
174 WRITE(msgBuf,'(2A,2I4,2(A,I8))') ' FLT_EXCH2:',
175 & ' bi,bj=', bi, bj,
176 & ' icountW=', icountW,
177 & ' > max_npart_exch=', max_npart_exch
178 CALL PRINT_ERROR( msgBuf, myThid )
179 ENDIF
180 IF ( icountE.GT.max_npart_exch
181 & .OR. icountW.GT.max_npart_exch ) THEN
182 STOP 'ABNORMAL END: S/R FLT_EXCH2'
183 ENDIF
184 IF ( (icountE+icountW).GT.0 ) THEN
185 C Remove from this tile-list, floats which have been sent to an other tile
186 npNew = npart_tile(bi,bj) - (icountE+icountW)
187 jl = 0
188 DO jp = npNew+1,npart_tile(bi,bj)
189 IF ( npart(jp,bi,bj).NE.0. _d 0 ) THEN
190 jl = jl + 1
191 ip = deleteList(jl)
192 C copy: ip <-- jp
193 npart (ip,bi,bj) = npart (jp,bi,bj)
194 tstart(ip,bi,bj) = tstart(jp,bi,bj)
195 ipart (ip,bi,bj) = ipart (jp,bi,bj)
196 jpart (ip,bi,bj) = jpart (jp,bi,bj)
197 kpart (ip,bi,bj) = kpart (jp,bi,bj)
198 kfloat(ip,bi,bj) = kfloat(jp,bi,bj)
199 iup (ip,bi,bj) = iup (jp,bi,bj)
200 itop (ip,bi,bj) = itop (jp,bi,bj)
201 tend (ip,bi,bj) = tend (jp,bi,bj)
202 ENDIF
203 ENDDO
204 npart_tile(bi,bj) = npNew
205 ENDIF
206
207 icountN=0
208 icountS=0
209 jl = 0
210
211 jlo = 0.5 _d 0
212 jhi = 0.5 _d 0 + DFLOAT(sNy)
213 sSide=exch2_isSedge(nT).AND.facet_link(W2_SOUTH,myFace).EQ.0.
214 nSide=exch2_isNedge(nT).AND.facet_link(W2_NORTH,myFace).EQ.0.
215 flt_stopped = -2.
216 flt_stopped = MIN( baseTime, flt_stopped )
217
218 DO ip=1,npart_tile(bi,bj)
219
220 IF ( npart(ip,bi,bj).NE.0 ) THEN
221
222 IF ( nSide .AND.
223 & (myTime.LE.tend(ip,bi,bj) .OR. tend(ip,bi,bj).EQ.-1.)
224 & .AND. jpart(ip,bi,bj).GE.jhi ) THEN
225 C stop the float:
226 tend(ip,bi,bj) = flt_stopped
227 ELSEIF ( jpart(ip,bi,bj).GE.jhi ) THEN
228 icountN=icountN+1
229 IF ( icountN.LE.max_npart_exch ) THEN
230
231 ic = (icountN-1)*imax
232 jNew = jpart(ip,bi,bj) - DFLOAT(sNy)
233 fltbuf_send(ic+1,bi,bj,W2_NORTH) = npart(ip,bi,bj)
234 fltbuf_send(ic+2,bi,bj,W2_NORTH) = tstart(ip,bi,bj)
235 fltbuf_send(ic+3,bi,bj,W2_NORTH) = ipart(ip,bi,bj)
236 fltbuf_send(ic+4,bi,bj,W2_NORTH) = jNew
237 fltbuf_send(ic+5,bi,bj,W2_NORTH) = kpart(ip,bi,bj)
238 fltbuf_send(ic+6,bi,bj,W2_NORTH) = kfloat(ip,bi,bj)
239 fltbuf_send(ic+7,bi,bj,W2_NORTH) = iup(ip,bi,bj)
240 fltbuf_send(ic+8,bi,bj,W2_NORTH) = itop(ip,bi,bj)
241 fltbuf_send(ic+9,bi,bj,W2_NORTH) = tend(ip,bi,bj)
242
243 C tag this float to be removed:
244 jl = jl + 1
245 deleteList(jl) = ip
246 npart(ip,bi,bj) = 0.
247
248 c ELSE
249 c WRITE(msgBuf,'(2A,2I4,I6,A,2F17.6))') ' FLT_EXCH2,N:',
250 c & ' bi,bj,ip=', bi, bj, ip,
251 c & ' yp,yHi=', jpart(ip,bi,bj), jhi
252 c CALL PRINT_ERROR( msgBuf, myThid )
253 ENDIF
254 ENDIF
255
256 IF ( sSide .AND.
257 & (myTime.LE.tend(ip,bi,bj) .OR. tend(ip,bi,bj).EQ.-1.)
258 & .AND. jpart(ip,bi,bj).LT.jlo ) THEN
259 C stop the float:
260 tend(ip,bi,bj) = flt_stopped
261 ELSEIF ( jpart(ip,bi,bj).LT.jlo ) THEN
262 icountS=icountS+1
263 IF ( icountS.LE.max_npart_exch ) THEN
264
265 ic = (icountS-1)*imax
266 jNew = jpart(ip,bi,bj) + DFLOAT(sNy)
267 fltbuf_send(ic+1,bi,bj,W2_SOUTH) = npart(ip,bi,bj)
268 fltbuf_send(ic+2,bi,bj,W2_SOUTH) = tstart(ip,bi,bj)
269 fltbuf_send(ic+3,bi,bj,W2_SOUTH) = ipart(ip,bi,bj)
270 fltbuf_send(ic+4,bi,bj,W2_SOUTH) = jNew
271 fltbuf_send(ic+5,bi,bj,W2_SOUTH) = kpart(ip,bi,bj)
272 fltbuf_send(ic+6,bi,bj,W2_SOUTH) = kfloat(ip,bi,bj)
273 fltbuf_send(ic+7,bi,bj,W2_SOUTH) = iup(ip,bi,bj)
274 fltbuf_send(ic+8,bi,bj,W2_SOUTH) = itop(ip,bi,bj)
275 fltbuf_send(ic+9,bi,bj,W2_SOUTH) = tend(ip,bi,bj)
276
277 C tag this float to be removed:
278 jl = jl + 1
279 deleteList(jl) = ip
280 npart(ip,bi,bj) = 0.
281
282 c ELSE
283 c WRITE(msgBuf,'(2A,2I4,I6,A,2F17.6))') ' FLT_EXCH2,S:',
284 c & ' bi,bj,ip=', bi, bj, ip,
285 c & ' yp,yLo=', jpart(ip,bi,bj), jlo
286 c CALL PRINT_ERROR( msgBuf, myThid )
287 ENDIF
288 ENDIF
289
290 ENDIF
291
292 ENDDO
293 IF ( icountN.GT.max_npart_exch ) THEN
294 WRITE(msgBuf,'(2A,2I4,2(A,I8))') ' FLT_EXCH2:',
295 & ' bi,bj=', bi, bj,
296 & ' icountN=', icountN,
297 & ' > max_npart_exch=', max_npart_exch
298 CALL PRINT_ERROR( msgBuf, myThid )
299 ENDIF
300 IF ( icountS.GT.max_npart_exch ) THEN
301 WRITE(msgBuf,'(2A,2I4,2(A,I8))') ' FLT_EXCH2:',
302 & ' bi,bj=', bi, bj,
303 & ' icountS=', icountS,
304 & ' > max_npart_exch=', max_npart_exch
305 CALL PRINT_ERROR( msgBuf, myThid )
306 ENDIF
307 IF ( icountN.GT.max_npart_exch
308 & .OR. icountS.GT.max_npart_exch ) THEN
309 STOP 'ABNORMAL END: S/R FLT_EXCH2'
310 ENDIF
311 IF ( (icountN+icountS).GT.0 ) THEN
312 C Remove from this tile-list, floats which have been sent to an other tile
313 npNew = npart_tile(bi,bj) - (icountN+icountS)
314 jl = 0
315 DO jp = npNew+1,npart_tile(bi,bj)
316 IF ( npart(jp,bi,bj).NE.0. _d 0 ) THEN
317 jl = jl + 1
318 ip = deleteList(jl)
319 C copy: ip <-- jp
320 npart (ip,bi,bj) = npart (jp,bi,bj)
321 tstart(ip,bi,bj) = tstart(jp,bi,bj)
322 ipart (ip,bi,bj) = ipart (jp,bi,bj)
323 jpart (ip,bi,bj) = jpart (jp,bi,bj)
324 kpart (ip,bi,bj) = kpart (jp,bi,bj)
325 kfloat(ip,bi,bj) = kfloat(jp,bi,bj)
326 iup (ip,bi,bj) = iup (jp,bi,bj)
327 itop (ip,bi,bj) = itop (jp,bi,bj)
328 tend (ip,bi,bj) = tend (jp,bi,bj)
329 ENDIF
330 ENDDO
331 npart_tile(bi,bj) = npNew
332 ENDIF
333
334 ENDDO
335 ENDDO
336
337 C-- Send or Put east and west edges.
338
339 #ifdef DBUG_EXCH_VEC
340 WRITE(errorMessageUnit,'(A,I8)') 'FLT_EXCH: 0x', myIter
341 #endif
342 CALL EXCH2_RL_SEND_PUT_VEC(
343 I fltbuf_send, fltbuf_recv,
344 O e2_msgHandles(1,1,1,1),
345 I imax2, myThid )
346 #ifdef DBUG_EXCH_VEC
347 WRITE(errorMessageUnit,'(A,I8)') 'FLT_EXCH2: 1x', myIter
348 #endif
349 C-- Receive east/west arrays
350 CALL EXCH2_RL_RECV_GET_VEC(
351 U fltbuf_recv,
352 I imax2, myThid )
353 #ifdef DBUG_EXCH_VEC
354 WRITE(errorMessageUnit,'(A,I8)') 'FLT_EXCH2: 2x', myIter
355 #endif
356
357 #ifdef ALLOW_USE_MPI
358 C-- Clear message handles/locks
359 DO bj=1,nSy
360 DO bi=1,nSx
361 nT=W2_myTileList(bi,bj)
362 nN=exch2_nNeighbours(nT)
363 DO N=1,nN
364 C Note: In a between process tile-tile data transport using
365 C MPI the sender needs to clear an Isend wait handle here.
366 C In a within process tile-tile data transport using true
367 C shared address space/or direct transfer through commonly
368 C addressable memory blocks the receiver needs to assert
369 C that he has consumed the buffer the sender filled here.
370 farTile=exch2_neighbourId(N,nT)
371 IF ( W2_myCommFlag(N,bi,bj) .EQ. 'M' ) THEN
372 wHandle = e2_msgHandles(1,N,bi,bj)
373 CALL MPI_Wait( wHandle, mpiStatus, mpiRc )
374 ELSEIF ( W2_myCommFlag(N,bi,bj) .EQ. 'P' ) THEN
375 ELSE
376 ENDIF
377 ENDDO
378 ENDDO
379 ENDDO
380 #endif
381
382 C-- Unpack arrays on new tiles
383
384 DO bj=myByLo(myThid),myByHi(myThid)
385 DO bi=myBxLo(myThid),myBxHi(myThid)
386
387 DO ip=1,max_npart_exch
388
389 ic=(ip-1)*imax
390 IF ( fltbuf_recv(ic+1,bi,bj,W2_EAST).NE.0. ) THEN
391 npart_tile(bi,bj) = npart_tile(bi,bj) + 1
392 IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
393 jp = npart_tile(bi,bj)
394 npart( jp,bi,bj) = fltbuf_recv(ic+1,bi,bj,W2_EAST)
395 tstart(jp,bi,bj) = fltbuf_recv(ic+2,bi,bj,W2_EAST)
396 ipart( jp,bi,bj) = fltbuf_recv(ic+3,bi,bj,W2_EAST)
397 jpart( jp,bi,bj) = fltbuf_recv(ic+4,bi,bj,W2_EAST)
398 kpart( jp,bi,bj) = fltbuf_recv(ic+5,bi,bj,W2_EAST)
399 kfloat(jp,bi,bj) = fltbuf_recv(ic+6,bi,bj,W2_EAST)
400 iup( jp,bi,bj) = fltbuf_recv(ic+7,bi,bj,W2_EAST)
401 itop( jp,bi,bj) = fltbuf_recv(ic+8,bi,bj,W2_EAST)
402 tend( jp,bi,bj) = fltbuf_recv(ic+9,bi,bj,W2_EAST)
403 ENDIF
404 ENDIF
405
406 ENDDO
407 IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
408 WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_EXCH2:+E',
409 & ' bi,bj=', bi, bj,
410 & ' npart_tile=', npart_tile(bi,bj),
411 & ' > max_npart_tile=', max_npart_tile
412 CALL PRINT_ERROR( msgBuf, myThid )
413 STOP 'ABNORMAL END: S/R FLT_EXCH2'
414 ENDIF
415
416 DO ip=1,max_npart_exch
417
418 ic=(ip-1)*imax
419 IF ( fltbuf_recv(ic+1,bi,bj,W2_WEST).NE.0. ) THEN
420 npart_tile(bi,bj) = npart_tile(bi,bj) + 1
421 IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
422 jp = npart_tile(bi,bj)
423 npart( jp,bi,bj) = fltbuf_recv(ic+1,bi,bj,W2_WEST)
424 tstart(jp,bi,bj) = fltbuf_recv(ic+2,bi,bj,W2_WEST)
425 ipart( jp,bi,bj) = fltbuf_recv(ic+3,bi,bj,W2_WEST)
426 jpart( jp,bi,bj) = fltbuf_recv(ic+4,bi,bj,W2_WEST)
427 kpart( jp,bi,bj) = fltbuf_recv(ic+5,bi,bj,W2_WEST)
428 kfloat(jp,bi,bj) = fltbuf_recv(ic+6,bi,bj,W2_WEST)
429 iup( jp,bi,bj) = fltbuf_recv(ic+7,bi,bj,W2_WEST)
430 itop( jp,bi,bj) = fltbuf_recv(ic+8,bi,bj,W2_WEST)
431 tend( jp,bi,bj) = fltbuf_recv(ic+9,bi,bj,W2_WEST)
432 ENDIF
433 ENDIF
434
435 ENDDO
436 IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
437 WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_EXCH2:+W',
438 & ' bi,bj=', bi, bj,
439 & ' npart_tile=', npart_tile(bi,bj),
440 & ' > max_npart_tile=', max_npart_tile
441 CALL PRINT_ERROR( msgBuf, myThid )
442 STOP 'ABNORMAL END: S/R FLT_EXCH2'
443 ENDIF
444
445 DO ip=1,max_npart_exch
446
447 ic=(ip-1)*imax
448 IF ( fltbuf_recv(ic+1,bi,bj,W2_NORTH).NE.0. ) THEN
449 npart_tile(bi,bj) = npart_tile(bi,bj) + 1
450 IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
451 jp = npart_tile(bi,bj)
452 npart( jp,bi,bj) = fltbuf_recv(ic+1,bi,bj,W2_NORTH)
453 tstart(jp,bi,bj) = fltbuf_recv(ic+2,bi,bj,W2_NORTH)
454 ipart( jp,bi,bj) = fltbuf_recv(ic+3,bi,bj,W2_NORTH)
455 jpart( jp,bi,bj) = fltbuf_recv(ic+4,bi,bj,W2_NORTH)
456 kpart( jp,bi,bj) = fltbuf_recv(ic+5,bi,bj,W2_NORTH)
457 kfloat(jp,bi,bj) = fltbuf_recv(ic+6,bi,bj,W2_NORTH)
458 iup( jp,bi,bj) = fltbuf_recv(ic+7,bi,bj,W2_NORTH)
459 itop( jp,bi,bj) = fltbuf_recv(ic+8,bi,bj,W2_NORTH)
460 tend( jp,bi,bj) = fltbuf_recv(ic+9,bi,bj,W2_NORTH)
461 ENDIF
462 ENDIF
463
464 ENDDO
465 IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
466 WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_EXCH2:+N',
467 & ' bi,bj=', bi, bj,
468 & ' npart_tile=', npart_tile(bi,bj),
469 & ' > max_npart_tile=', max_npart_tile
470 CALL PRINT_ERROR( msgBuf, myThid )
471 STOP 'ABNORMAL END: S/R FLT_EXCH2'
472 ENDIF
473
474 DO ip=1,max_npart_exch
475
476 ic=(ip-1)*imax
477 IF ( fltbuf_recv(ic+1,bi,bj,W2_SOUTH).NE.0. ) THEN
478 npart_tile(bi,bj) = npart_tile(bi,bj) + 1
479 IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
480 jp = npart_tile(bi,bj)
481 npart( jp,bi,bj) = fltbuf_recv(ic+1,bi,bj,W2_SOUTH)
482 tstart(jp,bi,bj) = fltbuf_recv(ic+2,bi,bj,W2_SOUTH)
483 ipart( jp,bi,bj) = fltbuf_recv(ic+3,bi,bj,W2_SOUTH)
484 jpart( jp,bi,bj) = fltbuf_recv(ic+4,bi,bj,W2_SOUTH)
485 kpart( jp,bi,bj) = fltbuf_recv(ic+5,bi,bj,W2_SOUTH)
486 kfloat(jp,bi,bj) = fltbuf_recv(ic+6,bi,bj,W2_SOUTH)
487 iup( jp,bi,bj) = fltbuf_recv(ic+7,bi,bj,W2_SOUTH)
488 itop( jp,bi,bj) = fltbuf_recv(ic+8,bi,bj,W2_SOUTH)
489 tend( jp,bi,bj) = fltbuf_recv(ic+9,bi,bj,W2_SOUTH)
490 ENDIF
491 ENDIF
492
493 ENDDO
494 IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
495 WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_EXCH2:+S',
496 & ' bi,bj=', bi, bj,
497 & ' npart_tile=', npart_tile(bi,bj),
498 & ' > max_npart_tile=', max_npart_tile
499 CALL PRINT_ERROR( msgBuf, myThid )
500 STOP 'ABNORMAL END: S/R FLT_EXCH2'
501 ENDIF
502
503 ENDDO
504 ENDDO
505
506 C ipass
507 ENDDO
508
509 #endif /* ALLOW_EXCH2 */
510
511 RETURN
512 END

  ViewVC Help
Powered by ViewVC 1.1.22