/[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.10 - (show annotations) (download)
Tue Nov 24 00:16:33 2009 UTC (14 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62c, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62w, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint63g, checkpoint62, checkpoint63, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint62b, checkpoint61z
Changes since 1.9: +35 -24 lines
incorporate modifs from Contrib/nesting_sannino/code_nest_merged

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

  ViewVC Help
Powered by ViewVC 1.1.22