/[MITgcm]/MITgcm_contrib/sannino/GRID_Refinemet/code/ini_communication_patterns.F
ViewVC logotype

Contents of /MITgcm_contrib/sannino/GRID_Refinemet/code/ini_communication_patterns.F

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


Revision 1.1 - (show annotations) (download)
Thu Jul 20 21:08:14 2006 UTC (19 years, 6 months ago) by sannino
Branch: MAIN
CVS Tags: HEAD
o Adding OASIS package
o Adding grid refinement package

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

  ViewVC Help
Powered by ViewVC 1.1.22