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

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

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


Revision 1.4 - (hide annotations) (download)
Tue May 12 19:44:58 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61o
Changes since 1.3: +5 -4 lines
new header files "W2_EXCH2_SIZE.h" (taken out of W2_EXCH2_TOPOLOGY.h)
             and "W2_EXCH2_BUFFER.h" (taken out of W2_EXCH2_PARAMS.h)

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

  ViewVC Help
Powered by ViewVC 1.1.22