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

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

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


Revision 1.4 - (hide annotations) (download)
Sat Feb 11 21:07:13 2017 UTC (7 years, 3 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, HEAD
Changes since 1.3: +17 -1 lines
- flt_init_varia.F: use pickupSuff if specified

- add code and test case as a first step towards completing pkg/exch2 support within pkg/flt
  - flt_init_fixed.F: if DEVEL_FLT_EXCH2 then comment out stop
  - flt_exch2.F: if DEVEL_FLT_EXCH2 then conserve ipart, jpart (grid coordinates)
  - exch2_recv_get_vec.F: if DEVEL_FLT_EXCH2 then transform ipart, jpart (grid coordinates)
  - flt_mapping.F: if DEVEL_FLT_EXCH2 then attempt to fix longitude diagnostic near date-line
  - flt_init_varia.F: if DEVEL_FLT_EXCH2 then hack initialization (for testing purposes w. LLC90)

1 gforget 1.4 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_exch2.F,v 1.3 2012/09/06 16:14:28 jmc Exp $
2 jahn 1.2 C $Name: $
3 jahn 1.1
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 jahn 1.2 #include "FLT_SIZE.h"
28 jahn 1.1 #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 jmc 1.3 INTEGER N, nT, ipass, myFace
48 jahn 1.1 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 jmc 1.3 C buffer for sending/receiving variables (4 levels <-> N,S,E,W)
55 jahn 1.1 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 jmc 1.3 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 jahn 1.1
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 jmc 1.3 DO m=1,imax2
82 jahn 1.1 fltbuf_send(m,bi,bj,N) = 0.
83     fltbuf_recv(m,bi,bj,N) = 0.
84 jmc 1.3 ENDDO
85 jahn 1.1 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 jmc 1.3 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 jahn 1.1 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 gforget 1.4 #ifdef DEVEL_FLT_EXCH2
116     fltbuf_send(ic+3,bi,bj,W2_EAST) = ipart(ip,bi,bj)
117     #else
118 jahn 1.1 fltbuf_send(ic+3,bi,bj,W2_EAST) = iNew
119 gforget 1.4 #endif
120 jahn 1.1 fltbuf_send(ic+4,bi,bj,W2_EAST) = jpart(ip,bi,bj)
121     fltbuf_send(ic+5,bi,bj,W2_EAST) = kpart(ip,bi,bj)
122     fltbuf_send(ic+6,bi,bj,W2_EAST) = kfloat(ip,bi,bj)
123     fltbuf_send(ic+7,bi,bj,W2_EAST) = iup(ip,bi,bj)
124     fltbuf_send(ic+8,bi,bj,W2_EAST) = itop(ip,bi,bj)
125     fltbuf_send(ic+9,bi,bj,W2_EAST) = tend(ip,bi,bj)
126    
127     C tag this float to be removed:
128     jl = jl + 1
129     deleteList(jl) = ip
130     npart(ip,bi,bj) = 0.
131    
132     ENDIF
133     ENDIF
134    
135     IF ( wSide .AND.
136     & (myTime.LE.tend(ip,bi,bj) .OR. tend(ip,bi,bj).EQ.-1.)
137     & .AND. ipart(ip,bi,bj).LT.ilo ) THEN
138     C stop the float:
139     tend(ip,bi,bj) = flt_stopped
140     ELSEIF ( ipart(ip,bi,bj).LT.ilo ) THEN
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_send(ic+1,bi,bj,W2_WEST) = npart(ip,bi,bj)
147     fltbuf_send(ic+2,bi,bj,W2_WEST) = tstart(ip,bi,bj)
148 gforget 1.4 #ifdef DEVEL_FLT_EXCH2
149     fltbuf_send(ic+3,bi,bj,W2_WEST) = ipart(ip,bi,bj)
150     #else
151 jahn 1.1 fltbuf_send(ic+3,bi,bj,W2_WEST) = iNew
152 gforget 1.4 #endif
153 jahn 1.1 fltbuf_send(ic+4,bi,bj,W2_WEST) = jpart(ip,bi,bj)
154     fltbuf_send(ic+5,bi,bj,W2_WEST) = kpart(ip,bi,bj)
155     fltbuf_send(ic+6,bi,bj,W2_WEST) = kfloat(ip,bi,bj)
156     fltbuf_send(ic+7,bi,bj,W2_WEST) = iup(ip,bi,bj)
157     fltbuf_send(ic+8,bi,bj,W2_WEST) = itop(ip,bi,bj)
158     fltbuf_send(ic+9,bi,bj,W2_WEST) = tend(ip,bi,bj)
159    
160     C tag this float to be removed:
161     jl = jl + 1
162     deleteList(jl) = ip
163     npart(ip,bi,bj) = 0.
164    
165     ENDIF
166     ENDIF
167    
168     ENDDO
169     IF ( icountE.GT.max_npart_exch ) THEN
170     WRITE(msgBuf,'(2A,2I4,2(A,I8))') ' FLT_EXCH2:',
171     & ' bi,bj=', bi, bj,
172     & ' icountE=', icountE,
173     & ' > max_npart_exch=', max_npart_exch
174     CALL PRINT_ERROR( msgBuf, myThid )
175     ENDIF
176     IF ( icountW.GT.max_npart_exch ) THEN
177     WRITE(msgBuf,'(2A,2I4,2(A,I8))') ' FLT_EXCH2:',
178     & ' bi,bj=', bi, bj,
179     & ' icountW=', icountW,
180     & ' > max_npart_exch=', max_npart_exch
181     CALL PRINT_ERROR( msgBuf, myThid )
182     ENDIF
183     IF ( icountE.GT.max_npart_exch
184     & .OR. icountW.GT.max_npart_exch ) THEN
185     STOP 'ABNORMAL END: S/R FLT_EXCH2'
186     ENDIF
187     IF ( (icountE+icountW).GT.0 ) THEN
188     C Remove from this tile-list, floats which have been sent to an other tile
189     npNew = npart_tile(bi,bj) - (icountE+icountW)
190     jl = 0
191     DO jp = npNew+1,npart_tile(bi,bj)
192     IF ( npart(jp,bi,bj).NE.0. _d 0 ) THEN
193     jl = jl + 1
194     ip = deleteList(jl)
195     C copy: ip <-- jp
196     npart (ip,bi,bj) = npart (jp,bi,bj)
197     tstart(ip,bi,bj) = tstart(jp,bi,bj)
198     ipart (ip,bi,bj) = ipart (jp,bi,bj)
199     jpart (ip,bi,bj) = jpart (jp,bi,bj)
200     kpart (ip,bi,bj) = kpart (jp,bi,bj)
201     kfloat(ip,bi,bj) = kfloat(jp,bi,bj)
202     iup (ip,bi,bj) = iup (jp,bi,bj)
203     itop (ip,bi,bj) = itop (jp,bi,bj)
204     tend (ip,bi,bj) = tend (jp,bi,bj)
205     ENDIF
206     ENDDO
207     npart_tile(bi,bj) = npNew
208     ENDIF
209    
210     icountN=0
211     icountS=0
212     jl = 0
213    
214     jlo = 0.5 _d 0
215     jhi = 0.5 _d 0 + DFLOAT(sNy)
216 jmc 1.3 sSide = exch2_isSedge(nT).EQ.1
217     & .AND. facet_link(W2_SOUTH,myFace).EQ.0.
218     nSide = exch2_isNedge(nT).EQ.1
219     & .AND. facet_link(W2_NORTH,myFace).EQ.0.
220 jahn 1.1 flt_stopped = -2.
221     flt_stopped = MIN( baseTime, flt_stopped )
222    
223     DO ip=1,npart_tile(bi,bj)
224    
225     IF ( npart(ip,bi,bj).NE.0 ) THEN
226    
227     IF ( nSide .AND.
228     & (myTime.LE.tend(ip,bi,bj) .OR. tend(ip,bi,bj).EQ.-1.)
229     & .AND. jpart(ip,bi,bj).GE.jhi ) THEN
230     C stop the float:
231     tend(ip,bi,bj) = flt_stopped
232     ELSEIF ( jpart(ip,bi,bj).GE.jhi ) THEN
233     icountN=icountN+1
234     IF ( icountN.LE.max_npart_exch ) THEN
235    
236     ic = (icountN-1)*imax
237     jNew = jpart(ip,bi,bj) - DFLOAT(sNy)
238     fltbuf_send(ic+1,bi,bj,W2_NORTH) = npart(ip,bi,bj)
239     fltbuf_send(ic+2,bi,bj,W2_NORTH) = tstart(ip,bi,bj)
240     fltbuf_send(ic+3,bi,bj,W2_NORTH) = ipart(ip,bi,bj)
241 gforget 1.4 #ifdef DEVEL_FLT_EXCH2
242     fltbuf_send(ic+4,bi,bj,W2_NORTH) = jpart(ip,bi,bj)
243     #else
244 jahn 1.1 fltbuf_send(ic+4,bi,bj,W2_NORTH) = jNew
245 gforget 1.4 #endif
246 jahn 1.1 fltbuf_send(ic+5,bi,bj,W2_NORTH) = kpart(ip,bi,bj)
247     fltbuf_send(ic+6,bi,bj,W2_NORTH) = kfloat(ip,bi,bj)
248     fltbuf_send(ic+7,bi,bj,W2_NORTH) = iup(ip,bi,bj)
249     fltbuf_send(ic+8,bi,bj,W2_NORTH) = itop(ip,bi,bj)
250     fltbuf_send(ic+9,bi,bj,W2_NORTH) = tend(ip,bi,bj)
251    
252     C tag this float to be removed:
253     jl = jl + 1
254     deleteList(jl) = ip
255     npart(ip,bi,bj) = 0.
256    
257     c ELSE
258     c WRITE(msgBuf,'(2A,2I4,I6,A,2F17.6))') ' FLT_EXCH2,N:',
259     c & ' bi,bj,ip=', bi, bj, ip,
260     c & ' yp,yHi=', jpart(ip,bi,bj), jhi
261     c CALL PRINT_ERROR( msgBuf, myThid )
262     ENDIF
263     ENDIF
264    
265     IF ( sSide .AND.
266     & (myTime.LE.tend(ip,bi,bj) .OR. tend(ip,bi,bj).EQ.-1.)
267     & .AND. jpart(ip,bi,bj).LT.jlo ) THEN
268     C stop the float:
269     tend(ip,bi,bj) = flt_stopped
270     ELSEIF ( jpart(ip,bi,bj).LT.jlo ) THEN
271     icountS=icountS+1
272     IF ( icountS.LE.max_npart_exch ) THEN
273    
274     ic = (icountS-1)*imax
275     jNew = jpart(ip,bi,bj) + DFLOAT(sNy)
276     fltbuf_send(ic+1,bi,bj,W2_SOUTH) = npart(ip,bi,bj)
277     fltbuf_send(ic+2,bi,bj,W2_SOUTH) = tstart(ip,bi,bj)
278     fltbuf_send(ic+3,bi,bj,W2_SOUTH) = ipart(ip,bi,bj)
279 gforget 1.4 #ifdef DEVEL_FLT_EXCH2
280     fltbuf_send(ic+4,bi,bj,W2_SOUTH) = jpart(ip,bi,bj)
281     #else
282 jahn 1.1 fltbuf_send(ic+4,bi,bj,W2_SOUTH) = jNew
283 gforget 1.4 #endif
284 jahn 1.1 fltbuf_send(ic+5,bi,bj,W2_SOUTH) = kpart(ip,bi,bj)
285     fltbuf_send(ic+6,bi,bj,W2_SOUTH) = kfloat(ip,bi,bj)
286     fltbuf_send(ic+7,bi,bj,W2_SOUTH) = iup(ip,bi,bj)
287     fltbuf_send(ic+8,bi,bj,W2_SOUTH) = itop(ip,bi,bj)
288     fltbuf_send(ic+9,bi,bj,W2_SOUTH) = tend(ip,bi,bj)
289    
290     C tag this float to be removed:
291     jl = jl + 1
292     deleteList(jl) = ip
293     npart(ip,bi,bj) = 0.
294    
295     c ELSE
296     c WRITE(msgBuf,'(2A,2I4,I6,A,2F17.6))') ' FLT_EXCH2,S:',
297     c & ' bi,bj,ip=', bi, bj, ip,
298     c & ' yp,yLo=', jpart(ip,bi,bj), jlo
299     c CALL PRINT_ERROR( msgBuf, myThid )
300     ENDIF
301     ENDIF
302    
303     ENDIF
304    
305     ENDDO
306     IF ( icountN.GT.max_npart_exch ) THEN
307     WRITE(msgBuf,'(2A,2I4,2(A,I8))') ' FLT_EXCH2:',
308     & ' bi,bj=', bi, bj,
309     & ' icountN=', icountN,
310     & ' > max_npart_exch=', max_npart_exch
311     CALL PRINT_ERROR( msgBuf, myThid )
312     ENDIF
313     IF ( icountS.GT.max_npart_exch ) THEN
314     WRITE(msgBuf,'(2A,2I4,2(A,I8))') ' FLT_EXCH2:',
315     & ' bi,bj=', bi, bj,
316     & ' icountS=', icountS,
317     & ' > max_npart_exch=', max_npart_exch
318     CALL PRINT_ERROR( msgBuf, myThid )
319     ENDIF
320     IF ( icountN.GT.max_npart_exch
321     & .OR. icountS.GT.max_npart_exch ) THEN
322     STOP 'ABNORMAL END: S/R FLT_EXCH2'
323     ENDIF
324     IF ( (icountN+icountS).GT.0 ) THEN
325     C Remove from this tile-list, floats which have been sent to an other tile
326     npNew = npart_tile(bi,bj) - (icountN+icountS)
327     jl = 0
328     DO jp = npNew+1,npart_tile(bi,bj)
329     IF ( npart(jp,bi,bj).NE.0. _d 0 ) THEN
330     jl = jl + 1
331     ip = deleteList(jl)
332     C copy: ip <-- jp
333     npart (ip,bi,bj) = npart (jp,bi,bj)
334     tstart(ip,bi,bj) = tstart(jp,bi,bj)
335     ipart (ip,bi,bj) = ipart (jp,bi,bj)
336     jpart (ip,bi,bj) = jpart (jp,bi,bj)
337     kpart (ip,bi,bj) = kpart (jp,bi,bj)
338     kfloat(ip,bi,bj) = kfloat(jp,bi,bj)
339     iup (ip,bi,bj) = iup (jp,bi,bj)
340     itop (ip,bi,bj) = itop (jp,bi,bj)
341     tend (ip,bi,bj) = tend (jp,bi,bj)
342     ENDIF
343     ENDDO
344     npart_tile(bi,bj) = npNew
345     ENDIF
346    
347     ENDDO
348     ENDDO
349    
350 jmc 1.3 C Prevent anyone to access shared buffer while an other thread modifies it
351     _BARRIER
352    
353 jahn 1.1 C-- Send or Put east and west edges.
354    
355     #ifdef DBUG_EXCH_VEC
356     WRITE(errorMessageUnit,'(A,I8)') 'FLT_EXCH: 0x', myIter
357     #endif
358 jmc 1.3 CALL EXCH2_SEND_PUT_VEC_RL(
359     I fltbuf_send,
360     O fltbuf_recv,
361 jahn 1.1 O e2_msgHandles(1,1,1,1),
362     I imax2, myThid )
363     #ifdef DBUG_EXCH_VEC
364     WRITE(errorMessageUnit,'(A,I8)') 'FLT_EXCH2: 1x', myIter
365     #endif
366 jmc 1.3
367     #ifdef ALLOW_USE_MPI
368     IF ( usingMPI ) THEN
369 jahn 1.1 C-- Receive east/west arrays
370 jmc 1.3 CALL EXCH2_RECV_GET_VEC_RL(
371 jahn 1.1 U fltbuf_recv,
372 jmc 1.3 I e2_msgHandles(1,1,1,1),
373 jahn 1.1 I imax2, myThid )
374     #ifdef DBUG_EXCH_VEC
375 jmc 1.3 WRITE(errorMessageUnit,'(A,I8)') 'FLT_EXCH2: 2x', myIter
376 jahn 1.1 #endif
377 jmc 1.3 ENDIF
378     #endif /* ALLOW_USE_MPI */
379 jahn 1.1
380 jmc 1.3 C-- need to sync threads after master has received data ;
381     C (done after mpi waitall in case waitall is really needed)
382     _BARRIER
383 jahn 1.1
384     C-- Unpack arrays on new tiles
385    
386     DO bj=myByLo(myThid),myByHi(myThid)
387     DO bi=myBxLo(myThid),myBxHi(myThid)
388    
389     DO ip=1,max_npart_exch
390    
391     ic=(ip-1)*imax
392     IF ( fltbuf_recv(ic+1,bi,bj,W2_EAST).NE.0. ) THEN
393     npart_tile(bi,bj) = npart_tile(bi,bj) + 1
394     IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
395     jp = npart_tile(bi,bj)
396     npart( jp,bi,bj) = fltbuf_recv(ic+1,bi,bj,W2_EAST)
397     tstart(jp,bi,bj) = fltbuf_recv(ic+2,bi,bj,W2_EAST)
398     ipart( jp,bi,bj) = fltbuf_recv(ic+3,bi,bj,W2_EAST)
399     jpart( jp,bi,bj) = fltbuf_recv(ic+4,bi,bj,W2_EAST)
400     kpart( jp,bi,bj) = fltbuf_recv(ic+5,bi,bj,W2_EAST)
401     kfloat(jp,bi,bj) = fltbuf_recv(ic+6,bi,bj,W2_EAST)
402     iup( jp,bi,bj) = fltbuf_recv(ic+7,bi,bj,W2_EAST)
403     itop( jp,bi,bj) = fltbuf_recv(ic+8,bi,bj,W2_EAST)
404     tend( jp,bi,bj) = fltbuf_recv(ic+9,bi,bj,W2_EAST)
405     ENDIF
406     ENDIF
407    
408     ENDDO
409     IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
410     WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_EXCH2:+E',
411     & ' bi,bj=', bi, bj,
412     & ' npart_tile=', npart_tile(bi,bj),
413     & ' > max_npart_tile=', max_npart_tile
414     CALL PRINT_ERROR( msgBuf, myThid )
415     STOP 'ABNORMAL END: S/R FLT_EXCH2'
416     ENDIF
417    
418     DO ip=1,max_npart_exch
419    
420     ic=(ip-1)*imax
421     IF ( fltbuf_recv(ic+1,bi,bj,W2_WEST).NE.0. ) THEN
422     npart_tile(bi,bj) = npart_tile(bi,bj) + 1
423     IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
424     jp = npart_tile(bi,bj)
425     npart( jp,bi,bj) = fltbuf_recv(ic+1,bi,bj,W2_WEST)
426     tstart(jp,bi,bj) = fltbuf_recv(ic+2,bi,bj,W2_WEST)
427     ipart( jp,bi,bj) = fltbuf_recv(ic+3,bi,bj,W2_WEST)
428     jpart( jp,bi,bj) = fltbuf_recv(ic+4,bi,bj,W2_WEST)
429     kpart( jp,bi,bj) = fltbuf_recv(ic+5,bi,bj,W2_WEST)
430     kfloat(jp,bi,bj) = fltbuf_recv(ic+6,bi,bj,W2_WEST)
431     iup( jp,bi,bj) = fltbuf_recv(ic+7,bi,bj,W2_WEST)
432     itop( jp,bi,bj) = fltbuf_recv(ic+8,bi,bj,W2_WEST)
433     tend( jp,bi,bj) = fltbuf_recv(ic+9,bi,bj,W2_WEST)
434     ENDIF
435     ENDIF
436    
437     ENDDO
438     IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
439     WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_EXCH2:+W',
440     & ' bi,bj=', bi, bj,
441     & ' npart_tile=', npart_tile(bi,bj),
442     & ' > max_npart_tile=', max_npart_tile
443     CALL PRINT_ERROR( msgBuf, myThid )
444     STOP 'ABNORMAL END: S/R FLT_EXCH2'
445     ENDIF
446    
447     DO ip=1,max_npart_exch
448    
449     ic=(ip-1)*imax
450     IF ( fltbuf_recv(ic+1,bi,bj,W2_NORTH).NE.0. ) THEN
451     npart_tile(bi,bj) = npart_tile(bi,bj) + 1
452     IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
453     jp = npart_tile(bi,bj)
454     npart( jp,bi,bj) = fltbuf_recv(ic+1,bi,bj,W2_NORTH)
455     tstart(jp,bi,bj) = fltbuf_recv(ic+2,bi,bj,W2_NORTH)
456     ipart( jp,bi,bj) = fltbuf_recv(ic+3,bi,bj,W2_NORTH)
457     jpart( jp,bi,bj) = fltbuf_recv(ic+4,bi,bj,W2_NORTH)
458     kpart( jp,bi,bj) = fltbuf_recv(ic+5,bi,bj,W2_NORTH)
459     kfloat(jp,bi,bj) = fltbuf_recv(ic+6,bi,bj,W2_NORTH)
460     iup( jp,bi,bj) = fltbuf_recv(ic+7,bi,bj,W2_NORTH)
461     itop( jp,bi,bj) = fltbuf_recv(ic+8,bi,bj,W2_NORTH)
462     tend( jp,bi,bj) = fltbuf_recv(ic+9,bi,bj,W2_NORTH)
463     ENDIF
464     ENDIF
465    
466     ENDDO
467     IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
468     WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_EXCH2:+N',
469     & ' bi,bj=', bi, bj,
470     & ' npart_tile=', npart_tile(bi,bj),
471     & ' > max_npart_tile=', max_npart_tile
472     CALL PRINT_ERROR( msgBuf, myThid )
473     STOP 'ABNORMAL END: S/R FLT_EXCH2'
474     ENDIF
475    
476     DO ip=1,max_npart_exch
477    
478     ic=(ip-1)*imax
479     IF ( fltbuf_recv(ic+1,bi,bj,W2_SOUTH).NE.0. ) THEN
480     npart_tile(bi,bj) = npart_tile(bi,bj) + 1
481     IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
482     jp = npart_tile(bi,bj)
483     npart( jp,bi,bj) = fltbuf_recv(ic+1,bi,bj,W2_SOUTH)
484     tstart(jp,bi,bj) = fltbuf_recv(ic+2,bi,bj,W2_SOUTH)
485     ipart( jp,bi,bj) = fltbuf_recv(ic+3,bi,bj,W2_SOUTH)
486     jpart( jp,bi,bj) = fltbuf_recv(ic+4,bi,bj,W2_SOUTH)
487     kpart( jp,bi,bj) = fltbuf_recv(ic+5,bi,bj,W2_SOUTH)
488     kfloat(jp,bi,bj) = fltbuf_recv(ic+6,bi,bj,W2_SOUTH)
489     iup( jp,bi,bj) = fltbuf_recv(ic+7,bi,bj,W2_SOUTH)
490     itop( jp,bi,bj) = fltbuf_recv(ic+8,bi,bj,W2_SOUTH)
491     tend( jp,bi,bj) = fltbuf_recv(ic+9,bi,bj,W2_SOUTH)
492     ENDIF
493     ENDIF
494    
495     ENDDO
496     IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
497     WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_EXCH2:+S',
498     & ' bi,bj=', bi, bj,
499     & ' npart_tile=', npart_tile(bi,bj),
500     & ' > max_npart_tile=', max_npart_tile
501     CALL PRINT_ERROR( msgBuf, myThid )
502     STOP 'ABNORMAL END: S/R FLT_EXCH2'
503     ENDIF
504    
505     ENDDO
506     ENDDO
507    
508     C ipass
509     ENDDO
510    
511     #endif /* ALLOW_EXCH2 */
512    
513     RETURN
514     END

  ViewVC Help
Powered by ViewVC 1.1.22