/[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.3 - (show annotations) (download)
Thu Sep 6 16:14:28 2012 UTC (11 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: 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, checkpoint64, checkpoint65, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e
Changes since 1.2: +33 -48 lines
- fix so that it compiles without MPI; fix syntax in setting [n,s,e,w,]Side logicals
- rename S/R EXCH2_RL_SEND_PUT_VEC -> EXCH2_SEND_PUT_VEC_RL
     and S/R EXCH2_RL_RECV_GET_VEC -> EXCH2_RECV_GET_VEC_RL
  so that it closer to file names (exch_send_put_vec.F, exch_recv_get_vec.F)
  and match the printed messages
- move calls to MPI_Wait from FLT_EXCH2 to EXCH2_RECV_GET_VEC_RL
  (so that flt_exch2.F is free from MPI stuff)
- move BARRIER calls directly in flt_exch2.F (easier to follow)
- fix multi-threaded MPI (had many issues)

1 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_exch2.F,v 1.2 2010/12/22 21:25:18 jahn Exp $
2 C $Name: $
3
4 #include "FLT_OPTIONS.h"
5 #undef DBUG_EXCH_VEC
6
7 SUBROUTINE FLT_EXCH2 (
8 I myTime, myIter, myThid )
9
10 C ==================================================================
11 C SUBROUTINE FLT_EXCH2
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 adapted to exch2: Oliver Jahn 2010.09
17 C ==================================================================
18
19 C !USES:
20 IMPLICIT NONE
21
22 C == global variables ==
23 #include "SIZE.h"
24 #include "EEPARAMS.h"
25 #include "EESUPPORT.h"
26 #include "PARAMS.h"
27 #include "FLT_SIZE.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 #endif
34
35 C == routine arguments ==
36 _RL myTime
37 INTEGER myIter, myThid
38
39 #ifdef ALLOW_EXCH2
40
41 C == local variables ==
42 INTEGER bi, bj, ic
43 INTEGER ip, jp, jl, npNew
44 INTEGER icountE, icountW, icountN, icountS
45 INTEGER deleteList(max_npart_exch*2)
46 INTEGER imax, imax2, m
47 INTEGER N, nT, ipass, myFace
48 INTEGER e2_msgHandles( 2, W2_maxNeighbours, nSx, nSy )
49 _RL ilo, ihi, jlo, jhi, iNew, jNew
50 PARAMETER(imax=9)
51 PARAMETER(imax2=imax*max_npart_exch)
52 CHARACTER*(MAX_LEN_MBUF) msgBuf
53
54 C buffer for sending/receiving variables (4 levels <-> N,S,E,W)
55 COMMON/FLTBUF/fltbuf_send,fltbuf_recv
56 _RL fltbuf_send(imax2,nSx,nSy,4)
57 _RL fltbuf_recv(imax2,nSx,nSy,4)
58 LOGICAL wSide, eSide, sSide, nSide
59 _RL flt_stopped
60
61 C == end of interface ==
62
63 C have to do 2 passes to get into tiles diagonally across
64 DO ipass=1,2
65
66 C Prevent anyone to access shared buffer while an other thread modifies it
67 C-- not needed here since send buffer is different fron recv buffer
68 C (which is not the case for usual 3-D field exch in EXCH2)
69 c CALL BAR2( myThid )
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 nT = W2_myTileList(bi,bj)
77 myFace = exch2_myFace(nT)
78
79 C initialize buffers
80 DO N=1,4
81 DO m=1,imax2
82 fltbuf_send(m,bi,bj,N) = 0.
83 fltbuf_recv(m,bi,bj,N) = 0.
84 ENDDO
85 ENDDO
86
87 icountE=0
88 icountW=0
89 jl = 0
90
91 ilo = 0.5 _d 0
92 ihi = 0.5 _d 0 + DFLOAT(sNx)
93 wSide = exch2_isWedge(nT).EQ.1
94 & .AND. facet_link(W2_WEST,myFace).EQ.0.
95 eSide = exch2_isEedge(nT).EQ.1
96 & .AND. facet_link(W2_EAST,myFace).EQ.0.
97 flt_stopped = -2.
98 flt_stopped = MIN( baseTime, flt_stopped )
99
100 DO ip=1,npart_tile(bi,bj)
101
102 IF ( eSide .AND.
103 & (myTime.LE.tend(ip,bi,bj) .OR. tend(ip,bi,bj).EQ.-1.)
104 & .AND. ipart(ip,bi,bj).GE.ihi ) THEN
105 C stop the float:
106 tend(ip,bi,bj) = flt_stopped
107 ELSEIF ( ipart(ip,bi,bj).GE.ihi ) THEN
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_send(ic+1,bi,bj,W2_EAST) = npart(ip,bi,bj)
114 fltbuf_send(ic+2,bi,bj,W2_EAST) = tstart(ip,bi,bj)
115 fltbuf_send(ic+3,bi,bj,W2_EAST) = iNew
116 fltbuf_send(ic+4,bi,bj,W2_EAST) = jpart(ip,bi,bj)
117 fltbuf_send(ic+5,bi,bj,W2_EAST) = kpart(ip,bi,bj)
118 fltbuf_send(ic+6,bi,bj,W2_EAST) = kfloat(ip,bi,bj)
119 fltbuf_send(ic+7,bi,bj,W2_EAST) = iup(ip,bi,bj)
120 fltbuf_send(ic+8,bi,bj,W2_EAST) = itop(ip,bi,bj)
121 fltbuf_send(ic+9,bi,bj,W2_EAST) = 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 IF ( wSide .AND.
132 & (myTime.LE.tend(ip,bi,bj) .OR. tend(ip,bi,bj).EQ.-1.)
133 & .AND. ipart(ip,bi,bj).LT.ilo ) THEN
134 C stop the float:
135 tend(ip,bi,bj) = flt_stopped
136 ELSEIF ( ipart(ip,bi,bj).LT.ilo ) THEN
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_send(ic+1,bi,bj,W2_WEST) = npart(ip,bi,bj)
143 fltbuf_send(ic+2,bi,bj,W2_WEST) = tstart(ip,bi,bj)
144 fltbuf_send(ic+3,bi,bj,W2_WEST) = iNew
145 fltbuf_send(ic+4,bi,bj,W2_WEST) = jpart(ip,bi,bj)
146 fltbuf_send(ic+5,bi,bj,W2_WEST) = kpart(ip,bi,bj)
147 fltbuf_send(ic+6,bi,bj,W2_WEST) = kfloat(ip,bi,bj)
148 fltbuf_send(ic+7,bi,bj,W2_WEST) = iup(ip,bi,bj)
149 fltbuf_send(ic+8,bi,bj,W2_WEST) = itop(ip,bi,bj)
150 fltbuf_send(ic+9,bi,bj,W2_WEST) = 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_EXCH2:',
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_EXCH2:',
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_EXCH2'
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 icountN=0
203 icountS=0
204 jl = 0
205
206 jlo = 0.5 _d 0
207 jhi = 0.5 _d 0 + DFLOAT(sNy)
208 sSide = exch2_isSedge(nT).EQ.1
209 & .AND. facet_link(W2_SOUTH,myFace).EQ.0.
210 nSide = exch2_isNedge(nT).EQ.1
211 & .AND. facet_link(W2_NORTH,myFace).EQ.0.
212 flt_stopped = -2.
213 flt_stopped = MIN( baseTime, flt_stopped )
214
215 DO ip=1,npart_tile(bi,bj)
216
217 IF ( npart(ip,bi,bj).NE.0 ) THEN
218
219 IF ( nSide .AND.
220 & (myTime.LE.tend(ip,bi,bj) .OR. tend(ip,bi,bj).EQ.-1.)
221 & .AND. jpart(ip,bi,bj).GE.jhi ) THEN
222 C stop the float:
223 tend(ip,bi,bj) = flt_stopped
224 ELSEIF ( jpart(ip,bi,bj).GE.jhi ) THEN
225 icountN=icountN+1
226 IF ( icountN.LE.max_npart_exch ) THEN
227
228 ic = (icountN-1)*imax
229 jNew = jpart(ip,bi,bj) - DFLOAT(sNy)
230 fltbuf_send(ic+1,bi,bj,W2_NORTH) = npart(ip,bi,bj)
231 fltbuf_send(ic+2,bi,bj,W2_NORTH) = tstart(ip,bi,bj)
232 fltbuf_send(ic+3,bi,bj,W2_NORTH) = ipart(ip,bi,bj)
233 fltbuf_send(ic+4,bi,bj,W2_NORTH) = jNew
234 fltbuf_send(ic+5,bi,bj,W2_NORTH) = kpart(ip,bi,bj)
235 fltbuf_send(ic+6,bi,bj,W2_NORTH) = kfloat(ip,bi,bj)
236 fltbuf_send(ic+7,bi,bj,W2_NORTH) = iup(ip,bi,bj)
237 fltbuf_send(ic+8,bi,bj,W2_NORTH) = itop(ip,bi,bj)
238 fltbuf_send(ic+9,bi,bj,W2_NORTH) = tend(ip,bi,bj)
239
240 C tag this float to be removed:
241 jl = jl + 1
242 deleteList(jl) = ip
243 npart(ip,bi,bj) = 0.
244
245 c ELSE
246 c WRITE(msgBuf,'(2A,2I4,I6,A,2F17.6))') ' FLT_EXCH2,N:',
247 c & ' bi,bj,ip=', bi, bj, ip,
248 c & ' yp,yHi=', jpart(ip,bi,bj), jhi
249 c CALL PRINT_ERROR( msgBuf, myThid )
250 ENDIF
251 ENDIF
252
253 IF ( sSide .AND.
254 & (myTime.LE.tend(ip,bi,bj) .OR. tend(ip,bi,bj).EQ.-1.)
255 & .AND. jpart(ip,bi,bj).LT.jlo ) THEN
256 C stop the float:
257 tend(ip,bi,bj) = flt_stopped
258 ELSEIF ( jpart(ip,bi,bj).LT.jlo ) THEN
259 icountS=icountS+1
260 IF ( icountS.LE.max_npart_exch ) THEN
261
262 ic = (icountS-1)*imax
263 jNew = jpart(ip,bi,bj) + DFLOAT(sNy)
264 fltbuf_send(ic+1,bi,bj,W2_SOUTH) = npart(ip,bi,bj)
265 fltbuf_send(ic+2,bi,bj,W2_SOUTH) = tstart(ip,bi,bj)
266 fltbuf_send(ic+3,bi,bj,W2_SOUTH) = ipart(ip,bi,bj)
267 fltbuf_send(ic+4,bi,bj,W2_SOUTH) = jNew
268 fltbuf_send(ic+5,bi,bj,W2_SOUTH) = kpart(ip,bi,bj)
269 fltbuf_send(ic+6,bi,bj,W2_SOUTH) = kfloat(ip,bi,bj)
270 fltbuf_send(ic+7,bi,bj,W2_SOUTH) = iup(ip,bi,bj)
271 fltbuf_send(ic+8,bi,bj,W2_SOUTH) = itop(ip,bi,bj)
272 fltbuf_send(ic+9,bi,bj,W2_SOUTH) = tend(ip,bi,bj)
273
274 C tag this float to be removed:
275 jl = jl + 1
276 deleteList(jl) = ip
277 npart(ip,bi,bj) = 0.
278
279 c ELSE
280 c WRITE(msgBuf,'(2A,2I4,I6,A,2F17.6))') ' FLT_EXCH2,S:',
281 c & ' bi,bj,ip=', bi, bj, ip,
282 c & ' yp,yLo=', jpart(ip,bi,bj), jlo
283 c CALL PRINT_ERROR( msgBuf, myThid )
284 ENDIF
285 ENDIF
286
287 ENDIF
288
289 ENDDO
290 IF ( icountN.GT.max_npart_exch ) THEN
291 WRITE(msgBuf,'(2A,2I4,2(A,I8))') ' FLT_EXCH2:',
292 & ' bi,bj=', bi, bj,
293 & ' icountN=', icountN,
294 & ' > max_npart_exch=', max_npart_exch
295 CALL PRINT_ERROR( msgBuf, myThid )
296 ENDIF
297 IF ( icountS.GT.max_npart_exch ) THEN
298 WRITE(msgBuf,'(2A,2I4,2(A,I8))') ' FLT_EXCH2:',
299 & ' bi,bj=', bi, bj,
300 & ' icountS=', icountS,
301 & ' > max_npart_exch=', max_npart_exch
302 CALL PRINT_ERROR( msgBuf, myThid )
303 ENDIF
304 IF ( icountN.GT.max_npart_exch
305 & .OR. icountS.GT.max_npart_exch ) THEN
306 STOP 'ABNORMAL END: S/R FLT_EXCH2'
307 ENDIF
308 IF ( (icountN+icountS).GT.0 ) THEN
309 C Remove from this tile-list, floats which have been sent to an other tile
310 npNew = npart_tile(bi,bj) - (icountN+icountS)
311 jl = 0
312 DO jp = npNew+1,npart_tile(bi,bj)
313 IF ( npart(jp,bi,bj).NE.0. _d 0 ) THEN
314 jl = jl + 1
315 ip = deleteList(jl)
316 C copy: ip <-- jp
317 npart (ip,bi,bj) = npart (jp,bi,bj)
318 tstart(ip,bi,bj) = tstart(jp,bi,bj)
319 ipart (ip,bi,bj) = ipart (jp,bi,bj)
320 jpart (ip,bi,bj) = jpart (jp,bi,bj)
321 kpart (ip,bi,bj) = kpart (jp,bi,bj)
322 kfloat(ip,bi,bj) = kfloat(jp,bi,bj)
323 iup (ip,bi,bj) = iup (jp,bi,bj)
324 itop (ip,bi,bj) = itop (jp,bi,bj)
325 tend (ip,bi,bj) = tend (jp,bi,bj)
326 ENDIF
327 ENDDO
328 npart_tile(bi,bj) = npNew
329 ENDIF
330
331 ENDDO
332 ENDDO
333
334 C Prevent anyone to access shared buffer while an other thread modifies it
335 _BARRIER
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_SEND_PUT_VEC_RL(
343 I fltbuf_send,
344 O 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
351 #ifdef ALLOW_USE_MPI
352 IF ( usingMPI ) THEN
353 C-- Receive east/west arrays
354 CALL EXCH2_RECV_GET_VEC_RL(
355 U fltbuf_recv,
356 I e2_msgHandles(1,1,1,1),
357 I imax2, myThid )
358 #ifdef DBUG_EXCH_VEC
359 WRITE(errorMessageUnit,'(A,I8)') 'FLT_EXCH2: 2x', myIter
360 #endif
361 ENDIF
362 #endif /* ALLOW_USE_MPI */
363
364 C-- need to sync threads after master has received data ;
365 C (done after mpi waitall in case waitall is really needed)
366 _BARRIER
367
368 C-- Unpack arrays on new tiles
369
370 DO bj=myByLo(myThid),myByHi(myThid)
371 DO bi=myBxLo(myThid),myBxHi(myThid)
372
373 DO ip=1,max_npart_exch
374
375 ic=(ip-1)*imax
376 IF ( fltbuf_recv(ic+1,bi,bj,W2_EAST).NE.0. ) THEN
377 npart_tile(bi,bj) = npart_tile(bi,bj) + 1
378 IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
379 jp = npart_tile(bi,bj)
380 npart( jp,bi,bj) = fltbuf_recv(ic+1,bi,bj,W2_EAST)
381 tstart(jp,bi,bj) = fltbuf_recv(ic+2,bi,bj,W2_EAST)
382 ipart( jp,bi,bj) = fltbuf_recv(ic+3,bi,bj,W2_EAST)
383 jpart( jp,bi,bj) = fltbuf_recv(ic+4,bi,bj,W2_EAST)
384 kpart( jp,bi,bj) = fltbuf_recv(ic+5,bi,bj,W2_EAST)
385 kfloat(jp,bi,bj) = fltbuf_recv(ic+6,bi,bj,W2_EAST)
386 iup( jp,bi,bj) = fltbuf_recv(ic+7,bi,bj,W2_EAST)
387 itop( jp,bi,bj) = fltbuf_recv(ic+8,bi,bj,W2_EAST)
388 tend( jp,bi,bj) = fltbuf_recv(ic+9,bi,bj,W2_EAST)
389 ENDIF
390 ENDIF
391
392 ENDDO
393 IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
394 WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_EXCH2:+E',
395 & ' bi,bj=', bi, bj,
396 & ' npart_tile=', npart_tile(bi,bj),
397 & ' > max_npart_tile=', max_npart_tile
398 CALL PRINT_ERROR( msgBuf, myThid )
399 STOP 'ABNORMAL END: S/R FLT_EXCH2'
400 ENDIF
401
402 DO ip=1,max_npart_exch
403
404 ic=(ip-1)*imax
405 IF ( fltbuf_recv(ic+1,bi,bj,W2_WEST).NE.0. ) THEN
406 npart_tile(bi,bj) = npart_tile(bi,bj) + 1
407 IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
408 jp = npart_tile(bi,bj)
409 npart( jp,bi,bj) = fltbuf_recv(ic+1,bi,bj,W2_WEST)
410 tstart(jp,bi,bj) = fltbuf_recv(ic+2,bi,bj,W2_WEST)
411 ipart( jp,bi,bj) = fltbuf_recv(ic+3,bi,bj,W2_WEST)
412 jpart( jp,bi,bj) = fltbuf_recv(ic+4,bi,bj,W2_WEST)
413 kpart( jp,bi,bj) = fltbuf_recv(ic+5,bi,bj,W2_WEST)
414 kfloat(jp,bi,bj) = fltbuf_recv(ic+6,bi,bj,W2_WEST)
415 iup( jp,bi,bj) = fltbuf_recv(ic+7,bi,bj,W2_WEST)
416 itop( jp,bi,bj) = fltbuf_recv(ic+8,bi,bj,W2_WEST)
417 tend( jp,bi,bj) = fltbuf_recv(ic+9,bi,bj,W2_WEST)
418 ENDIF
419 ENDIF
420
421 ENDDO
422 IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
423 WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_EXCH2:+W',
424 & ' bi,bj=', bi, bj,
425 & ' npart_tile=', npart_tile(bi,bj),
426 & ' > max_npart_tile=', max_npart_tile
427 CALL PRINT_ERROR( msgBuf, myThid )
428 STOP 'ABNORMAL END: S/R FLT_EXCH2'
429 ENDIF
430
431 DO ip=1,max_npart_exch
432
433 ic=(ip-1)*imax
434 IF ( fltbuf_recv(ic+1,bi,bj,W2_NORTH).NE.0. ) THEN
435 npart_tile(bi,bj) = npart_tile(bi,bj) + 1
436 IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
437 jp = npart_tile(bi,bj)
438 npart( jp,bi,bj) = fltbuf_recv(ic+1,bi,bj,W2_NORTH)
439 tstart(jp,bi,bj) = fltbuf_recv(ic+2,bi,bj,W2_NORTH)
440 ipart( jp,bi,bj) = fltbuf_recv(ic+3,bi,bj,W2_NORTH)
441 jpart( jp,bi,bj) = fltbuf_recv(ic+4,bi,bj,W2_NORTH)
442 kpart( jp,bi,bj) = fltbuf_recv(ic+5,bi,bj,W2_NORTH)
443 kfloat(jp,bi,bj) = fltbuf_recv(ic+6,bi,bj,W2_NORTH)
444 iup( jp,bi,bj) = fltbuf_recv(ic+7,bi,bj,W2_NORTH)
445 itop( jp,bi,bj) = fltbuf_recv(ic+8,bi,bj,W2_NORTH)
446 tend( jp,bi,bj) = fltbuf_recv(ic+9,bi,bj,W2_NORTH)
447 ENDIF
448 ENDIF
449
450 ENDDO
451 IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
452 WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_EXCH2:+N',
453 & ' bi,bj=', bi, bj,
454 & ' npart_tile=', npart_tile(bi,bj),
455 & ' > max_npart_tile=', max_npart_tile
456 CALL PRINT_ERROR( msgBuf, myThid )
457 STOP 'ABNORMAL END: S/R FLT_EXCH2'
458 ENDIF
459
460 DO ip=1,max_npart_exch
461
462 ic=(ip-1)*imax
463 IF ( fltbuf_recv(ic+1,bi,bj,W2_SOUTH).NE.0. ) THEN
464 npart_tile(bi,bj) = npart_tile(bi,bj) + 1
465 IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
466 jp = npart_tile(bi,bj)
467 npart( jp,bi,bj) = fltbuf_recv(ic+1,bi,bj,W2_SOUTH)
468 tstart(jp,bi,bj) = fltbuf_recv(ic+2,bi,bj,W2_SOUTH)
469 ipart( jp,bi,bj) = fltbuf_recv(ic+3,bi,bj,W2_SOUTH)
470 jpart( jp,bi,bj) = fltbuf_recv(ic+4,bi,bj,W2_SOUTH)
471 kpart( jp,bi,bj) = fltbuf_recv(ic+5,bi,bj,W2_SOUTH)
472 kfloat(jp,bi,bj) = fltbuf_recv(ic+6,bi,bj,W2_SOUTH)
473 iup( jp,bi,bj) = fltbuf_recv(ic+7,bi,bj,W2_SOUTH)
474 itop( jp,bi,bj) = fltbuf_recv(ic+8,bi,bj,W2_SOUTH)
475 tend( jp,bi,bj) = fltbuf_recv(ic+9,bi,bj,W2_SOUTH)
476 ENDIF
477 ENDIF
478
479 ENDDO
480 IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
481 WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_EXCH2:+S',
482 & ' bi,bj=', bi, bj,
483 & ' npart_tile=', npart_tile(bi,bj),
484 & ' > max_npart_tile=', max_npart_tile
485 CALL PRINT_ERROR( msgBuf, myThid )
486 STOP 'ABNORMAL END: S/R FLT_EXCH2'
487 ENDIF
488
489 ENDDO
490 ENDDO
491
492 C ipass
493 ENDDO
494
495 #endif /* ALLOW_EXCH2 */
496
497 RETURN
498 END

  ViewVC Help
Powered by ViewVC 1.1.22