/[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.2 - (show annotations) (download)
Mon May 24 14:25:55 1999 UTC (25 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint28, checkpoint29, checkpoint23, checkpoint24, checkpoint25, checkpoint27, branch-atmos-merge-freeze, branch-atmos-merge-start, checkpoint26, branch-atmos-merge-shapiro, checkpoint33, checkpoint32, checkpoint31, checkpoint30, checkpoint34, branch-atmos-merge-zonalfilt, branch-atmos-merge-phase5, branch-atmos-merge-phase4, branch-atmos-merge-phase7, branch-atmos-merge-phase6, branch-atmos-merge-phase1, branch-atmos-merge-phase3, branch-atmos-merge-phase2
Branch point for: branch-atmos-merge
Changes since 1.1: +6 -6 lines
Commented out redundant lines that will (later) deal with unstructured
tiling. As was, the lines were using uninitialised data!

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

  ViewVC Help
Powered by ViewVC 1.1.22