/[MITgcm]/MITgcm/pkg/exch2/exch2_rx2_cube_ad.template
ViewVC logotype

Annotation of /MITgcm/pkg/exch2/exch2_rx2_cube_ad.template

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


Revision 1.2 - (hide annotations) (download)
Tue Jul 29 20:25:23 2008 UTC (15 years, 10 months ago) by jmc
Branch: MAIN
Changes since 1.1: +10 -10 lines
- change index-bounds storage (move from target to local tile,
  more intuitive this way)
- rename/remove some variables

1 jmc 1.2 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_rx2_cube_ad.template,v 1.1 2007/07/27 22:15:23 heimbach Exp $
2 heimbach 1.1 C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5    
6     #undef Dbg
7    
8     CBOP
9     C !ROUTINE: EXCH_RX2_CUBE
10    
11     C !INTERFACE:
12     SUBROUTINE EXCH2_RX2_CUBE_AD(
13     U array1, array2, signOption, fieldCode,
14     I myOLw, myOLe, myOLn, myOLs, myNz,
15     I exchWidthX, exchWidthY,
16     I simulationMode, cornerMode, myThid )
17     IMPLICIT NONE
18    
19     C !DESCRIPTION:
20    
21     C !USES:
22     C == Global data ==
23     #include "SIZE.h"
24     #include "EEPARAMS.h"
25     #include "EESUPPORT.h"
26     #include "EXCH.h"
27     #include "W2_EXCH2_TOPOLOGY.h"
28     #include "W2_EXCH2_PARAMS.h"
29    
30     C !INPUT/OUTPUT PARAMETERS:
31     C array :: Array with edges to exchange.
32     C myOLw :: West, East, North and South overlap region sizes.
33     C myOLe
34     C myOLn
35     C myOLs
36     C exchWidthX :: Width of data region exchanged in X.
37     C exchWidthY :: Width of data region exchanged in Y.
38     C myThid :: Thread number of this instance of S/R EXCH...
39     LOGICAL signOption
40     CHARACTER*2 fieldCode
41     INTEGER myOLw
42     INTEGER myOLe
43     INTEGER myOLs
44     INTEGER myOLn
45     INTEGER myNz
46     INTEGER exchWidthX
47     INTEGER exchWidthY
48     INTEGER simulationMode
49     INTEGER cornerMode
50     INTEGER myThid
51     _RX array1(1-myOLw:sNx+myOLe,
52     & 1-myOLs:sNy+myOLn,
53     & myNZ, nSx, nSy)
54     _RX array2(1-myOLw:sNx+myOLe,
55     & 1-myOLs:sNy+myOLn,
56     & myNZ, nSx, nSy)
57    
58     C !LOCAL VARIABLES:
59     C theSimulationMode :: Holds working copy of simulation mode
60     C theCornerMode :: Holds working copy of corner mode
61     C I,J,K,bl,bt,bn,bs :: Loop and index counters
62     C be,bw
63     INTEGER theSimulationMode
64     INTEGER theCornerMode
65     c INTEGER I,J,K
66     c INTEGER bl,bt,bn,bs,be,bw
67     INTEGER I
68     C Variables for working through W2 topology
69     INTEGER e2_msgHandles(2,MAX_NEIGHBOURS, nSx)
70     INTEGER thisTile, farTile, N, nN, oN
71     INTEGER tIlo, tIhi, tJlo, tJhi, tKlo, tKhi
72     INTEGER tIStride, tJStride, tKStride
73     INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
74     INTEGER i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi
75     C == Statement function ==
76     C tilemod - Permutes indices to return neighboring tile index on
77     C six face cube.
78     c INTEGER tilemod
79    
80     C MPI stuff (should be in a routine call)
81     #ifdef ALLOW_USE_MPI
82     INTEGER mpiStatus(MPI_STATUS_SIZE)
83     INTEGER mpiRc
84     INTEGER wHandle
85     #endif
86     CEOP
87    
88     theSimulationMode = simulationMode
89     theCornerMode = cornerMode
90    
91     C For now tile<->tile exchanges are sequentialised through
92     C thread 1. This is a temporary feature for preliminary testing until
93     C general tile decomposistion is in place (CNH April 11, 2001)
94     CALL BAR2( myThid )
95    
96     C Receive messages or extract buffer copies
97     DO I=myBxLo(myThid), myBxHi(myThid)
98     thisTile=W2_myTileList(I)
99     nN=exch2_nNeighbours(thisTile)
100     CRG communication depends on order!!!
101     CRG DO N=1,nN
102     DO N=nN,1,-1
103     farTile=exch2_neighbourId(N,thisTile)
104 jmc 1.2 tIlo =exch2_iLo(N,thisTile)
105     tIhi =exch2_iHi(N,thisTile)
106     tJlo =exch2_jLo(N,thisTile)
107     tJhi =exch2_jHi(N,thisTile)
108 heimbach 1.1 CALL EXCH2_GET_RECV_BOUNDS(
109     I fieldCode, exchWidthX,
110     O tiStride, tjStride,
111     U tIlo, tiHi, tjLo, tjHi )
112     tKLo=1
113     tKHi=myNz
114     tKStride=1
115     i1Lo = 1-myOLw
116     i1Hi = sNx+myOLe
117     j1Lo = 1-myOLs
118     j1Hi = sNy+myOLs
119     k1Lo = 1
120     k1Hi = myNz
121     i2Lo = 1-myOLw
122     i2Hi = sNx+myOLe
123     j2Lo = 1-myOLs
124     j2Hi = sNy+myOLs
125     k2Lo = 1
126     k2Hi = myNz
127     C Receive from neighbour N to fill my points
128     C (tIlo:tIhi:tiStride,tJlo:tJhi,tJStride,tKlo:tKhi,tKStride)
129     C in "array".
130     C Note: when transferring data within a process:
131     C o e2Bufr entry to read is entry associated with opposing send record
132     C o e2_msgHandle entry to read is entry associated with opposing send
133     C record.
134     CALL EXCH2_RECV_RX2_AD(
135     I tIlo, tIhi, tiStride,
136     I tJlo, tJhi, tjStride,
137     I tKlo, tKhi, tkStride,
138     I thisTile, I, N,
139     I e2Bufr1_RX, e2Bufr2_RX, e2BufrRecSize,
140     I MAX_NEIGHBOURS, nSx,
141     I array1(1-myOLw,1-myOLs,1,I,1),
142     I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
143     I array2(1-myOLw,1-myOLs,1,I,1),
144     I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
145     O e2_msgHandles(1,N,I),
146     O e2_msgHandles(2,N,I),
147     I W2_myTileList,
148     I W2_myCommFlag(N,I),
149     I myThid )
150     ENDDO
151     ENDDO
152    
153     C without MPI: wait until all threads finish filling buffer
154     CALL BAR2( myThid )
155    
156     C Post sends as messages or buffer copies
157     DO I=myBxLo(myThid), myBxHi(myThid)
158     thisTile=W2_myTileList(I)
159     nN=exch2_nNeighbours(thisTile)
160     DO N=1,nN
161     farTile=exch2_neighbourId(N,thisTile)
162 jmc 1.2 oN=exch2_opposingSend(N,thisTile)
163     tIlo =exch2_iLo(oN,farTile)
164     tIhi =exch2_iHi(oN,farTile)
165     tJlo =exch2_jLo(oN,farTile)
166     tJhi =exch2_jHi(oN,farTile)
167 heimbach 1.1 CALL EXCH2_GET_SEND_BOUNDS(
168     I fieldCode, exchWidthX,
169     O tiStride, tjStride,
170     U tIlo, tiHi, tjLo, tjHi )
171     tKLo=1
172     tKHi=myNz
173     tKStride=1
174     i1Lo = 1-myOLw
175     i1Hi = sNx+myOLe
176     j1Lo = 1-myOLs
177     j1Hi = sNy+myOLs
178     k1Lo = 1
179     k1Hi = myNz
180     i2Lo = 1-myOLw
181     i2Hi = sNx+myOLe
182     j2Lo = 1-myOLs
183     j2Hi = sNy+myOLs
184     k2Lo = 1
185     k2Hi = myNz
186     C Send to neighbour N to fill neighbor points
187     C (tIlo:tIhi:tiStride,tJlo:tJhi,tJStride,tKlo:tKhi,tKStride)
188     C in its copy of "array".
189     CALL EXCH2_SEND_RX2_AD(
190     I tIlo, tIhi, tiStride,
191     I tJlo, tJhi, tjStride,
192     I tKlo, tKhi, tkStride,
193     I thisTile, N,
194     I e2Bufr1_RX(1,N,I,1), e2BufrRecSize,
195     I e2Bufr2_RX(1,N,I,1),
196     I array1(1-myOLw,1-myOLs,1,I,1),
197     I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
198     I array2(1-myOLw,1-myOLs,1,I,1),
199     I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
200     O e2_msgHandles(1,N,I),
201     O e2_msgHandles(2,N,I),
202     I W2_myCommFlag(N,I), signOption,
203     I myThid )
204     ENDDO
205     ENDDO
206    
207     C Clear message handles/locks
208     DO I=1,nSx
209     thisTile=W2_myTileList(I)
210     nN=exch2_nNeighbours(thisTile)
211     DO N=1,nN
212     C Note: In a between process tile-tile data transport using
213     C MPI the sender needs to clear an Isend wait handle here.
214     C In a within process tile-tile data transport using true
215     C shared address space/or direct transfer through commonly
216     C addressable memory blocks the receiver needs to assert
217     C that is has consumed the buffer the sender filled here.
218     farTile=exch2_neighbourId(N,thisTile)
219     IF ( W2_myCommFlag(N,I) .EQ. 'M' ) THEN
220     #ifdef ALLOW_USE_MPI
221     wHandle = e2_msgHandles(1,N,I)
222     CALL MPI_Wait( wHandle, mpiStatus, mpiRc )
223     wHandle = e2_msgHandles(2,N,I)
224     CALL MPI_Wait( wHandle, mpiStatus, mpiRc )
225     #endif
226     ELSEIF ( W2_myCommFlag(N,I) .EQ. 'P' ) THEN
227     ELSE
228     ENDIF
229     ENDDO
230     ENDDO
231    
232     CALL BAR2(myThid)
233    
234     RETURN
235     END
236    
237     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
238    
239     CEH3 ;;; Local Variables: ***
240     CEH3 ;;; mode:fortran ***
241     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22