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

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

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


Revision 1.4 - (hide annotations) (download)
Tue May 29 14:01:36 2001 UTC (23 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint40pre3, checkpoint40pre1, checkpoint40pre7, checkpoint40pre6, checkpoint40pre8, checkpoint40pre2, checkpoint40pre4, checkpoint40pre5
Changes since 1.3: +4 -3 lines
Merge from branch pre38:
 o essential mods for cubed sphere
 o debugged atmosphere, dynamcis + physics (aim)
 o new packages (mom_vecinv, mom_fluxform, ...)

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

  ViewVC Help
Powered by ViewVC 1.1.22