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

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

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


Revision 1.2 - (hide annotations) (download)
Mon Apr 5 15:27:06 2004 UTC (20 years, 2 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint52n_post, checkpoint53d_post, checkpoint54a_pre, checkpoint55c_post, checkpoint54e_post, checkpoint54a_post, checkpoint53c_post, checkpoint57k_post, checkpoint55d_pre, checkpoint57d_post, checkpoint57g_post, checkpoint57b_post, checkpoint57c_pre, checkpoint55j_post, checkpoint56b_post, checkpoint57i_post, checkpoint57e_post, checkpoint55h_post, checkpoint53b_post, checkpoint57g_pre, checkpoint54b_post, checkpoint53b_pre, checkpoint55b_post, checkpoint54d_post, checkpoint56c_post, checkpoint52m_post, checkpoint55, checkpoint53a_post, checkpoint57f_pre, checkpoint57a_post, checkpoint54, checkpoint54f_post, checkpoint55g_post, checkpoint55f_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, checkpoint53, eckpoint57e_pre, checkpoint57h_done, checkpoint53g_post, checkpoint57f_post, checkpoint57c_post, checkpoint55e_post, checkpoint53f_post, checkpoint55a_post, checkpoint53d_pre, checkpoint54c_post, checkpoint57j_post, checkpoint57h_pre, checkpoint57l_post, checkpoint57h_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.1: +6 -2 lines
 o fix "make clean"
 o add CVS Header: and Name:

1 edhill 1.2 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_rx2_cube.template,v 1.1 2004/01/09 20:46:09 afe Exp $
2 afe 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(
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     INTEGER I,J,K
66     INTEGER bl,bt,bn,bs,be,bw
67     C Variables for working through W2 topology
68     INTEGER thisTile, farTile, N, nN, oN
69     INTEGER tIlo, tIhi, tJlo, tJhi, tKlo, tKhi
70     INTEGER tIStride, tJStride, tKStride
71     INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
72     INTEGER i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi
73     C == Statement function ==
74     C tilemod - Permutes indices to return neighboring tile index on
75     C six face cube.
76     INTEGER tilemod
77    
78     C MPI stuff (should be in a routine call)
79     #ifdef ALLOW_USE_MPI
80     INTEGER mpiStatus(MPI_STATUS_SIZE)
81     #endif
82     INTEGER mpiRc
83     INTEGER wHandle
84     CEOP
85    
86     theSimulationMode = simulationMode
87     theCornerMode = cornerMode
88    
89     C For now tile<->tile exchanges are sequentialised through
90     C thread 1. This is a temporary feature for preliminary testing until
91     C general tile decomposistion is in place (CNH April 11, 2001)
92     CALL BAR2( myThid )
93    
94     C Post sends as messages or buffer copies
95     DO I=myBxLo(myThid), myBxHi(myThid)
96     thisTile=W2_myTileList(I)
97     nN=exch2_nNeighbours(thisTile)
98     DO N=1,nN
99     farTile=exch2_neighbourId(N,thisTile)
100     tIlo =exch2_itlo_c(N,thisTile)
101     tIhi =exch2_ithi_c(N,thisTile)
102     tJlo =exch2_jtlo_c(N,thisTile)
103     tJhi =exch2_jthi_c(N,thisTile)
104     CALL EXCH2_GET_SEND_BOUNDS(
105     I fieldCode, exchWidthX,
106     O tiStride, tjStride,
107     U tIlo, tiHi, tjLo, tjHi )
108     tKLo=1
109     tKHi=myNz
110     tKStride=1
111     i1Lo = 1-myOLw
112     i1Hi = sNx+myOLe
113     j1Lo = 1-myOLs
114     j1Hi = sNy+myOLs
115     k1Lo = 1
116     k1Hi = myNz
117     i2Lo = 1-myOLw
118     i2Hi = sNx+myOLe
119     j2Lo = 1-myOLs
120     j2Hi = sNy+myOLs
121     k2Lo = 1
122     k2Hi = myNz
123     C Send to neighbour N to fill neighbor points
124     C (tIlo:tIhi:tiStride,tJlo:tJhi,tJStride,tKlo:tKhi,tKStride)
125     C in its copy of "array".
126     CALL EXCH2_SEND_RX2(
127     I tIlo, tIhi, tiStride,
128     I tJlo, tJhi, tjStride,
129     I tKlo, tKhi, tkStride,
130     I thisTile, N,
131     I e2Bufr1_RX(1,N,I,1), e2BufrRecSize,
132     I e2Bufr2_RX(1,N,I,1),
133     I array1(1-myOLw,1-myOLs,1,I,1),
134     I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
135     I array2(1-myOLw,1-myOLs,1,I,1),
136     I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
137     O e2_msgHandles(1,N,I),
138     O e2_msgHandles(2,N,I),
139     I W2_myCommFlag(N,I), signOption,
140     I myThid )
141     ENDDO
142     ENDDO
143    
144     C Receive messages or extract buffer copies
145     DO I=myBxLo(myThid), myBxHi(myThid)
146     thisTile=W2_myTileList(I)
147     nN=exch2_nNeighbours(thisTile)
148     DO N=1,nN
149     farTile=exch2_neighbourId(N,thisTile)
150     oN=exch2_opposingSend_Record(N,thisTile)
151     tIlo =exch2_itlo_c(oN,farTile)
152     tIhi =exch2_ithi_c(oN,farTile)
153     tJlo =exch2_jtlo_c(oN,farTile)
154     tJhi =exch2_jthi_c(oN,farTile)
155     CALL EXCH2_GET_RECV_BOUNDS(
156     I fieldCode, exchWidthX,
157     O tiStride, tjStride,
158     U tIlo, tiHi, tjLo, tjHi )
159     tKLo=1
160     tKHi=myNz
161     tKStride=1
162     i1Lo = 1-myOLw
163     i1Hi = sNx+myOLe
164     j1Lo = 1-myOLs
165     j1Hi = sNy+myOLs
166     k1Lo = 1
167     k1Hi = myNz
168     i2Lo = 1-myOLw
169     i2Hi = sNx+myOLe
170     j2Lo = 1-myOLs
171     j2Hi = sNy+myOLs
172     k2Lo = 1
173     k2Hi = myNz
174     C Receive from neighbour N to fill my points
175     C (tIlo:tIhi:tiStride,tJlo:tJhi,tJStride,tKlo:tKhi,tKStride)
176     C in "array".
177     C Note: when transferring data within a process:
178     C o e2Bufr entry to read is entry associated with opposing send record
179     C o e2_msgHandle entry to read is entry associated with opposing send
180     C record.
181     CALL EXCH2_RECV_RX2(
182     I tIlo, tIhi, tiStride,
183     I tJlo, tJhi, tjStride,
184     I tKlo, tKhi, tkStride,
185     I thisTile, I, N,
186     I e2Bufr1_RX, e2Bufr2_RX, e2BufrRecSize,
187     I MAX_NEIGHBOURS, nSx,
188     I array1(1-myOLw,1-myOLs,1,I,1),
189     I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
190     I array2(1-myOLw,1-myOLs,1,I,1),
191     I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
192     U e2_msgHandles,
193     I W2_myTileList,
194     I W2_myCommFlag(N,I),
195     I myThid )
196     ENDDO
197     ENDDO
198    
199     C Clear message handles/locks
200     DO I=1,nSx
201     thisTile=W2_myTileList(I)
202     nN=exch2_nNeighbours(thisTile)
203     DO N=1,nN
204     C Note: In a between process tile-tile data transport using
205     C MPI the sender needs to clear an Isend wait handle here.
206     C In a within process tile-tile data transport using true
207     C shared address space/or direct transfer through commonly
208     C addressable memory blocks the receiver needs to assert
209     C that is has consumed the buffer the sender filled here.
210     farTile=exch2_neighbourId(N,thisTile)
211     IF ( W2_myCommFlag(N,I) .EQ. 'M' ) THEN
212     #ifdef ALLOW_USE_MPI
213     wHandle = e2_msgHandles(1,N,I)
214     CALL MPI_Wait( wHandle, mpiStatus, mpiRc )
215     wHandle = e2_msgHandles(2,N,I)
216     CALL MPI_Wait( wHandle, mpiStatus, mpiRc )
217     #endif
218     ELSEIF ( W2_myCommFlag(N,I) .EQ. 'P' ) THEN
219     ELSE
220     ENDIF
221     ENDDO
222     ENDDO
223    
224     CALL BAR2(myThid)
225    
226     RETURN
227     END
228    
229 edhill 1.2 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
230    
231     CEH3 ;;; Local Variables: ***
232     CEH3 ;;; mode:fortran ***
233     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22