/[MITgcm]/MITgcm/eesupp/src/ini_communication_patterns.F
ViewVC logotype

Contents of /MITgcm/eesupp/src/ini_communication_patterns.F

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


Revision 1.5 - (show annotations) (download)
Wed Sep 5 19:59:31 2001 UTC (22 years, 9 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint40pre9, checkpoint40
Changes since 1.4: +8 -2 lines
[Temporary] fix for broken MPI on SGI's.

1 C $Header: /u/gcmpack/models/MITgcmUV/eesupp/src/ini_communication_patterns.F,v 1.4 2001/05/29 14:01:36 adcroft Exp $
2 C $Name: $
3
4 #include "CPP_EEOPTIONS.h"
5
6 CStartOfInterface
7 SUBROUTINE INI_COMMUNICATION_PATTERNS( myThid )
8 C /==========================================================\
9 C | SUBROUTINE INI_COMMUNICATION_PATTERNS |
10 C | o Initialise between tile communication data structures. |
11 C |==========================================================|
12 C | This routine assigns identifiers to each tile and then |
13 C | defines a map of neighbors for each tile. |
14 C | For each neighbor a communication method is defined. |
15 C \==========================================================/
16 IMPLICIT NONE
17
18 C === Global data ===
19 #include "SIZE.h"
20 #include "EEPARAMS.h"
21 #include "EESUPPORT.h"
22 #include "EXCH.h"
23 CEndOfInterface
24
25 C === Routine arguments ===
26 C myThid - Thread number we are dealing with in this call
27 INTEGER myThid
28
29 C === Local variables ===
30 C pxW - Process X coord of process to west.
31 C pxE - Process X coord of process to west.
32 C pyN - Process Y coord of process to north.
33 C pyS - Process Y coord of process to south.
34 C procW - Process Id of process to west.
35 C procE - Process Id of process to east.
36 C procN - Process Id of process to north.
37 C procS - Process Id of process to south.
38 C totalTileCount - Total number of tiles
39 C tagW0, tagE0, tagS0, tagN0, theTag - Working variables for
40 C calculating message tags.
41 C biW, biE, bjN, bjS - Tile x and y indices to west, east,
42 C south and north.
43 C bi, bj - Tile loop counter
44 C pi, pj - Process loop counter
45 INTEGER bi0(nPx)
46 INTEGER bj0(nPy)
47 INTEGER bi, bj, pi, pj
48 INTEGER pxW, pxE, pyN, pyS
49 INTEGER procW, procE, procN, procS
50 INTEGER totalTileCount
51 INTEGER tagW0, tagE0, tagS0, tagN0, theTag
52 INTEGER biE, biW, bjN, bjS
53 INTEGER thePx, thePy, theBj, theBi
54
55 #ifndef ALWAYS_USE_MPI
56 C-- Turn off memsync by default (e.g. needed for threads on SUNs)
57 exchNeedsMemsync = .TRUE.
58 exchUsesBarrier = .TRUE.
59 #else
60 C-- ... except that MPI needs this until some counter problem is fixed.
61 exchNeedsMemsync = .FALSE.
62 exchUsesBarrier = .FALSE.
63 #endif
64
65 C-- Define a globally unique tile numbers for each tile.
66 C-- We aslo define the tile numbers for our east, west, south
67 C-- and north neighbor tiles here. As coded below this is done from
68 C-- a simple cartesian formula. To handle irregular tile distributions
69 C-- the code below would be changed. For instance we could read
70 C-- the neighbor tile information from a file rather than deriving
71 C-- it in-line. This allows general tile distributions and connectivity
72 C-- both within a thread, between threads and between processors.
73 C Notes --
74 C 1. The cartesian based formula coded below works as follows:
75 C i. Each tile has one west neighbor, one east neighbor
76 C one north neignbor and one south neighbor.
77 C ii. For each of my neighbors store the following
78 C - neighbor tile id
79 C - neighbor process id
80 C 2. The information that is stored is then used to determine
81 C the between tile communication method. The method used
82 C depends on whether the tile is part of the same process,
83 C on the same machine etc...
84 C 3. To initialise a tile distribution with holes in it
85 C i.e. tiles that are not computed on. Set tile number to
86 C the value NULL_TILE. This must also be done for tileNoW,
87 C tileNoE, tileNoS, tileNoN.
88 C 4. The default formula below assigns tile numbers sequentially
89 C in X on the **global** grid. Within a process the tile numbers
90 C will not necessairily be sequential. This means that the tile
91 C numbering label does not change when nTx, nTy, nPx or nPy change.
92 C It will only change if the tile size changes or the global
93 C grid changes.
94 C bi0 and bj0 are the base global tile grid coordinate for the first
95 C tile in this process.
96 DO pi = 1, nPx
97 bi0(pi) = pi
98 ENDDO
99 DO pj = 1, nPy
100 bj0(pj) = pj
101 ENDDO
102 DO bj=myByLo(myThid),myByHi(myThid)
103 DO bi=myBxLo(myThid),myBxHi(myThid)
104 C o My tile identifier
105 Crg tileNo(bi,bj) = (bj0(myPy)-1+bj-1)*nSx*nPx+bi0(myPx)+bi-1
106 thePx = myPx
107 thePy = myPy
108 theBj = bj
109 theBi = bi
110 tileNo(bi,bj) =
111 & ((thePy-1)*nSy+theBj-1)*nSx*nPx
112 & + (thePx-1)*nSx
113 & + theBi
114 C o My west neighbor tile and process identifier
115 biW = bi-1
116 pxW = myPx
117 procW = myPid
118 IF ( biW .LT. 1 ) THEN
119 biW = nSx
120 pxW = myPx-1
121 procW = pidW
122 IF ( pxW .LT. 1 ) pxW = nPx
123 ENDIF
124 Crg tileNoW (bi,bj) = (bj0(myPy)-1+bj-1)*nSx*nPx+bi0(pxW)+biW-1
125 thePx = pxW
126 thePy = myPy
127 theBj = bj
128 theBi = biW
129 tileNoW (bi,bj) =
130 & ((thePy-1)*nSy+theBj-1)*nSx*nPx
131 & + (thePx-1)*nSx
132 & + theBi
133 tilePidW(bi,bj) = procW
134 tileBiW (bi,bj) = biW
135 tileBjW (bi,bj) = bj
136 C o My east neighbor tile and process identifier
137 biE = bi+1
138 pxE = myPx
139 procE = myPid
140 IF ( biE .GT. nSx ) THEN
141 biE = 1
142 pxE = myPx+1
143 procE = pidE
144 IF ( pxE .GT. nPx ) pxE = 1
145 ENDIF
146 Crg tileNoE(bi,bj) = (bj0(myPy)-1+bj-1)*nSx*nPx+bi0(pxE)+biE-1
147 thePx = pxE
148 thePy = myPy
149 theBi = biE
150 theBj = bj
151 tileNoE(bi,bj) =
152 & ((thePy-1)*nSy+theBj-1)*nSx*nPx
153 & + (thePx-1)*nSx
154 & + theBi
155 tilePidE(bi,bj) = procE
156 tileBiE (bi,bj) = biE
157 tileBjE (bi,bj) = bj
158 C o My north neighbor tile and process identifier
159 bjN = bj+1
160 pyN = myPy
161 procN = myPid
162 IF ( bjN .GT. nSy ) THEN
163 bjN = 1
164 pyN = myPy+1
165 procN = pidN
166 IF ( pyN .GT. nPy ) pyN = 1
167 ENDIF
168 Crg tileNoN(bi,bj) = (bj0(pyN)-1+bjN-1)*nSx*nPx+bi0(myPx)+bi-1
169 thePx = myPx
170 thePy = pyN
171 theBi = bi
172 theBj = bjN
173 tileNoN(bi,bj) =
174 & ((thePy-1)*nSy+theBj-1)*nSx*nPx
175 & + (thePx-1)*nSx
176 & + theBi
177 tilePidN(bi,bj) = procN
178 tileBiN(bi,bj) = bi
179 tileBjN(bi,bj) = bjN
180 C o My south neighbor tile and process identifier
181 bjS = bj-1
182 pyS = myPy
183 procS = myPid
184 IF ( bjS .LT. 1 ) THEN
185 bjS = nSy
186 pyS = pyS-1
187 procS = pidS
188 IF ( pyS .LT. 1 ) pyS = nPy
189 ENDIF
190 Crg tileNoS(bi,bj) = (bj0(pyS+1)-1+bjS-1)*nSx*nPx+bi0(myPx+1)+bi-1
191 thePx = myPx
192 thePy = pyS
193 theBi = bi
194 theBj = bjS
195 tileNoS(bi,bj) =
196 & ((thePy-1)*nSy+theBj-1)*nSx*nPx
197 & + (thePx-1)*nSx
198 & + theBi
199 tilePidS(bi,bj) = procS
200 tileBiS(bi,bj) = bi
201 tileBjS(bi,bj) = bjS
202 ENDDO
203 ENDDO
204
205 C-- Define the total count of tiles.
206 totalTileCount = nSx*nSy*nPx*nPy
207
208 C-- Set tags for each tile face.
209 C Tags are used to distinguish exchanges from particular
210 C faces of particular tiles.
211 C Tag numbers are based on
212 C i - The tile number
213 C ii - The direction (N,S,W,E) of the message
214 C We dont check for the NULL_TILE tile number here as it
215 C should not actually be used.
216 TagW0=1
217 TagE0=2
218 TagN0=3
219 TagS0=4
220 DO bj=myByLo(myThid),myByHi(myThid)
221 DO bi=myBxLo(myThid),myBxHi(myThid)
222 C Send tags
223 C o Tag I use for messages I send to west
224 theTag = TagW0*totalTileCount+tileNo(bi,bj)-1
225 tileTagSendW(bi,bj) = theTag
226 C o Tag I use for messages I send to east
227 theTag = TagE0*totalTileCount+tileNo(bi,bj)-1
228 tileTagSendE(bi,bj) = theTag
229 C o Tag I use for messages I send to north
230 theTag = TagN0*totalTileCount+tileNo(bi,bj)-1
231 tileTagSendN(bi,bj) = theTag
232 C o Tag I use for messages I send to south
233 theTag = TagS0*totalTileCount+tileNo(bi,bj)-1
234 tileTagSendS(bi,bj) = theTag
235 C Receive tags
236 C o Tag on messages I receive from my east
237 theTag = TagW0*totalTileCount+tileNoE(bi,bj)-1
238 tileTagRecvE(bi,bj) = theTag
239 C o Tag on messages I receive from my west
240 theTag = TagE0*totalTileCount+tileNoW(bi,bj)-1
241 tileTagRecvW(bi,bj) = theTag
242 C o Tag on messages I receive from my north
243 theTag = TagS0*totalTileCount+tileNoN(bi,bj)-1
244 tileTagRecvN(bi,bj) = theTag
245 C o Tag on messages I receive from my north
246 theTag = TagN0*totalTileCount+tileNoS(bi,bj)-1
247 tileTagRecvS(bi,bj) = theTag
248 ENDDO
249 ENDDO
250
251 C-- Set the form of excahnge to use between neighboring
252 C -- tiles.
253 C For now use either shared memory, messages or nothing. Further
254 C rules can be added later to allow shm regions and ump regions
255 C etc...
256 C Notes -
257 C 1. We require symmetry here. If one face of a tile uses
258 C communication method A then the matching face on its neighbor
259 C tile must also use communication method A.
260 DO bj=myByLo(myThid),myByHi(myThid)
261 DO bi=myBxLo(myThid),myBxHi(myThid)
262 C o West face communication
263 IF ( tileNoW(bi,bj) .EQ. NULL_TILE ) THEN
264 tileCommModeW(bi,bj) = COMM_NONE
265 ELSE
266 IF ( myPid .EQ. tilePidW(bi,bj) ) THEN
267 tileCommModeW(bi,bj) = COMM_PUT
268 ELSE
269 tileCommModeW(bi,bj) = COMM_MSG
270 ENDIF
271 ENDIF
272 C o East face communication
273 IF ( tileNoE(bi,bj) .EQ. NULL_TILE ) THEN
274 tileCommModeE(bi,bj) = COMM_NONE
275 ELSE
276 IF ( myPid .EQ. tilePidE(bi,bj) ) THEN
277 tileCommModeE(bi,bj) = COMM_PUT
278 ELSE
279 tileCommModeE(bi,bj) = COMM_MSG
280 ENDIF
281 ENDIF
282 C o South face communication
283 IF ( tileNoS(bi,bj) .EQ. NULL_TILE ) THEN
284 tileCommModeS(bi,bj) = COMM_NONE
285 ELSE
286 IF ( myPid .EQ. tilePidS(bi,bj) ) THEN
287 tileCommModeS(bi,bj) = COMM_PUT
288 ELSE
289 tileCommModeS(bi,bj) = COMM_MSG
290 ENDIF
291 ENDIF
292 C o North face communication
293 IF ( tileNoN(bi,bj) .EQ. NULL_TILE ) THEN
294 tileCommModeN(bi,bj) = COMM_NONE
295 ELSE
296 IF ( myPid .EQ. tilePidN(bi,bj) ) THEN
297 tileCommModeN(bi,bj) = COMM_PUT
298 ELSE
299 tileCommModeN(bi,bj) = COMM_MSG
300 ENDIF
301 ENDIF
302
303 ENDDO
304 ENDDO
305
306 C Initialise outstanding exchange request counter
307 DO bj=myByLo(myThid),myByHi(myThid)
308 DO bi=myBxLo(myThid),myBxHi(myThid)
309 exchNReqsX(1,bi,bj) = 0
310 exchNReqsY(1,bi,bj) = 0
311 ENDDO
312 ENDDO
313
314 RETURN
315 END

  ViewVC Help
Powered by ViewVC 1.1.22