/[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.3 - (show annotations) (download)
Sun Feb 4 14:38:43 2001 UTC (23 years, 3 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint38, c37_adj, checkpoint39, checkpoint37, checkpoint36, checkpoint35
Branch point for: pre38
Changes since 1.2: +2 -1 lines
Made sure each .F and .h file had
the CVS keywords Header and Name at its start.
Most had header but very few currently have Name, so
lots of changes!

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

  ViewVC Help
Powered by ViewVC 1.1.22