/[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.2 - (show annotations) (download)
Wed Dec 22 21:25:18 2010 UTC (13 years, 4 months ago) by jahn
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.1: +3 -2 lines
add FLT_SIZE.h

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

  ViewVC Help
Powered by ViewVC 1.1.22