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

Contents of /MITgcm/eesupp/src/ini_threading_environment.F

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


Revision 1.7 - (show annotations) (download)
Sun Feb 4 14:38:43 2001 UTC (23 years, 4 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint40pre3, checkpoint40pre1, checkpoint40pre7, checkpoint40pre6, checkpoint40pre9, checkpoint40pre8, checkpoint38, checkpoint40pre2, checkpoint40pre4, pre38tag1, c37_adj, pre38-close, checkpoint39, checkpoint37, checkpoint36, checkpoint35, checkpoint40pre5, checkpoint40
Branch point for: pre38
Changes since 1.6: +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_threading_environment.F,v 1.6 1999/05/18 17:39:21 adcroft Exp $
2 C $Name: $
3
4 #include "CPP_EEOPTIONS.h"
5
6 CStartOfInterface
7 SUBROUTINE INI_THREADING_ENVIRONMENT
8 C /==========================================================\
9 C | SUBROUTINE INI_THREADING_ENVIRONMENT |
10 C | o Initialise multi-threaded environment. |
11 C |==========================================================|
12 C | Generally we do not start separate threads here. |
13 C | The separate threads a spawned at later on. |
14 C | Here we perform initialisation of data-structures |
15 C | that indicate which of the nSx x nSy tiles a thread is |
16 C | responsible for. |
17 C | The multiple threads are spawned in the top level MAIN |
18 C | routine. |
19 C \==========================================================/
20 IMPLICIT NONE
21
22 C == Global data ==
23 #include "SIZE.h"
24 #include "EEPARAMS.h"
25 #include "EESUPPORT.h"
26 CEndOfInterface
27
28 C == Local variables ==
29 C bXPerThread - Blocks of size sNx per thread.
30 C byPerThread - Blocks of size sNy per thread.
31 C Thid - Thread index. Temporary used in loops
32 C which set per. thread values on a
33 C cartesian grid.
34 C bxLo, bxHi - Work vars. for thread index
35 C byLo, byHi range. bxLo is the lowest i index
36 C that a thread covers, bxHi is the
37 C highest i index. byLo is the lowest
38 C j index, byHi is the highest j index.
39 C I, J - Loop counter
40 C msgBuf - I/O buffer for reporting status information.
41 C myThid - Dummy thread id for use in printed messages
42 C ( this routine "INI_THREADING_ENVIRONMENT" is
43 C called before multi-threading has started.)
44 INTEGER bxPerThread
45 INTEGER byPerThread
46 INTEGER Thid
47 INTEGER bxLo, bxHi
48 INTEGER byLo, byHi
49 INTEGER I, J, nT
50 CHARACTER*(MAX_LEN_MBUF) msgBuf
51 INTEGER myThid
52
53 C-- Set default for all threads of having no blocks to
54 C-- work on - except for thread 1.
55 myBxLo(1) = 1
56 myBxHi(1) = nSx
57 myByLo(1) = 1
58 myByHi(1) = nSy
59 DO I = 2, MAX_NO_THREADS
60 myBxLo(I) = 0
61 myBxHi(I) = 0
62 myByLo(I) = 0
63 myByHi(I) = 0
64 ENDDO
65 myThid = 1
66 commName(COMM_NONE) = 'none'
67 commName(COMM_MSG ) = 'messages'
68 commName(COMM_PUT ) = 'put'
69 commName(COMM_GET ) = 'get'
70
71 C-- If there are multiple threads allocate different range of the
72 C-- nSx*nSy blocks to each thread.
73 C For now handle simple case of no. blocks nSx = n*nTx and
74 C no. blocks nSy = m*nTy ( where m and n are integer ). This
75 C is handled by simply mapping threads to blocks in sequence
76 C with the x thread index moving fastest.
77 C Later code which sets the thread number of neighboring blocks
78 C needs to be consistent with the code here.
79 nThreads = nTx * nTy
80
81 C-- Initialise the barrier mechanisms
82 C BAR2 will eventually replace barrier everywhere.
83 CALL BARRIER_INIT
84 DO I=1, MAX_NO_THREADS
85 CALL BAR2_INIT(I)
86 ENDDO
87
88 C-- Initialise exchange mechanism
89 CALL EXCH_INIT
90
91 IF ( nThreads .NE. nTx*nTy ) THEN
92 WRITE(msgBuf,'(A,A,A,I5,A,I5)')
93 & 'S/R INI_THREADING_ENVIRONMENT:',
94 & ' Total number of threads is not the same as nTx*nTy.',
95 & ' nTx * nTy = ',nTx*nTy,' nThreads = ',nThreads
96 CALL PRINT_ERROR(msgBuf, myThid)
97 eeBootError = .TRUE.
98 STOP 'ABNORMAL END: S/R INI_THREADING_ENVIRONMENT'
99 ENDIF
100 bxPerThread = nSx/nTx
101 IF ( bxPerThread*nTx .NE. nSx ) THEN
102 WRITE(msgBuf,'(A,A,A)')
103 & 'S/R INI_THREADING_ENVIRONMENT:',
104 & ' Number of blocks in X (nSx)',
105 & ' must be exact multiple of threads in X (nTx).'
106 CALL PRINT_ERROR(msgBuf, myThid)
107 eeBootError = .TRUE.
108 STOP 'ABNORMAL END: S/R INI_THREADING_ENVIRONMENT'
109 ENDIF
110 byPerThread = nSy/nTy
111 IF ( byPerThread*nTy .NE. nSy ) THEN
112 WRITE(msgBuf,'(A,A,A)')
113 & 'S/R INI_THREADING_ENVIRONMENT:',
114 & ' Number of blocks in Y (nSy)',
115 & ' must be exact multiple of threads in Y (nTy).'
116 CALL PRINT_ERROR(msgBuf, myThid)
117 eeBootError = .TRUE.
118 STOP 'ABNORMAL END: S/R INI_THREADING_ENVIRONMENT'
119 ENDIF
120 IF ( .NOT. eeBootError ) THEN
121 byLo = 1
122 DO J=1,nTy
123 byHi = byLo+byPerThread-1
124 bxLo = 1
125 DO I=1,nTx
126 Thid = (J-1)*nTx+I
127 bxHi = bxLo+bxPerThread-1
128 myBxLo(Thid) = bxLo
129 myBxHi(Thid) = bxHi
130 myByLo(Thid) = byLo
131 myByHi(Thid) = byHi
132 bxLo = bxHi+1
133 ENDDO
134 byLo = byHi+1
135 ENDDO
136 ENDIF
137
138 DO nT=1,nThreads
139 CALL INI_COMMUNICATION_PATTERNS( nT )
140 ENDDO
141
142 C-- Print mapping of threads to grid points.
143 WRITE(msgBuf,'(A)')
144 &'// ======================================================'
145 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
146 & SQUEEZE_RIGHT , 1)
147 WRITE(msgBuf,'(A)') '// Mapping of tiles to threads'
148 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
149 & SQUEEZE_RIGHT , 1)
150 C o Write list of tiles each thread is responsible for
151 WRITE(msgBuf,'(A)')
152 &'// ======================================================'
153 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
154 & SQUEEZE_RIGHT , 1)
155 DO I=1,nThreads
156 WRITE(msgBuf,'(A,I4,A,4(I4,A1))')
157 & '// -o- Thread',I,', tiles (',
158 & myBxLo(I),':',myBxHi(I),',',myByLo(I),':',myByHi(I),')'
159 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,SQUEEZE_BOTH , 1)
160 ENDDO
161 WRITE(msgBuf,'(A)') ' '
162 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,SQUEEZE_RIGHT , 1)
163
164 C o For each tile print its communication method(s)
165 WRITE(msgBuf,'(A)')
166 &'// ======================================================'
167 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
168 & SQUEEZE_RIGHT , 1)
169 WRITE(msgBuf,'(A)') '// Tile <-> Tile connectvity table'
170 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
171 & SQUEEZE_RIGHT , 1)
172 WRITE(msgBuf,'(A)')
173 &'// ======================================================'
174 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
175 & SQUEEZE_RIGHT , 1)
176 DO J=1,nSy
177 DO I=1,nSx
178 WRITE(msgBuf,'(A,A,I6.6,A,I6.6,A)')
179 & '//',' Tile number: ',tileNo(I,J),
180 & ' (process no. = ',myPid,')'
181 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT , 1)
182 C o West communication details
183 IF ( tileNoW(I,J).NE. NULL_TILE ) THEN
184 WRITE(msgBuf,'(A,A,I6.6,A,I6.6,A,A)')
185 & '// WEST: ',
186 & 'Tile = ',tileNoW(I,J),
187 & ', Process = ',tilePidW(I,J),
188 & ', Comm = ',commName(tileCommModeW(I,J))
189 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT, 1)
190 WRITE(msgBuf,'(A,A,I6.6,A,I6.6)')
191 & '// ',
192 & ' bi = ',tileBiW(I,J),
193 & ', bj = ',tileBjW(I,J)
194 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT, 1)
195 ELSE
196 WRITE(msgBuf,'(A)')
197 & '// WEST: no neighbor'
198 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT, 1)
199 ENDIF
200 C o East communication details
201 IF ( tileNoE(I,J).NE. NULL_TILE ) THEN
202 WRITE(msgBuf,'(A,A,I6.6,A,I6.6,A,A)')
203 & '// EAST: ',
204 & 'Tile = ',tileNoE(I,J),
205 & ', Process = ',tilePidE(I,J),
206 & ', Comm = ',commName(tileCommModeE(I,J))
207 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT, 1)
208 WRITE(msgBuf,'(A,A,I6.6,A,I6.6)')
209 & '// ',
210 & ' bi = ',tileBiE(I,J),
211 & ', bj = ',tileBjE(I,J)
212 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT, 1)
213 ELSE
214 WRITE(msgBuf,'(A)')
215 & '// EAST: no neighbor'
216 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT, 1)
217 ENDIF
218 C o South communication method
219 IF ( tileNoS(I,J).NE. NULL_TILE ) THEN
220 WRITE(msgBuf,'(A,A,I6.6,A,I6.6,A,A)')
221 & '// SOUTH: ',
222 & 'Tile = ',tileNoS(I,J),
223 & ', Process = ',tilePidS(I,J),
224 & ', Comm = ',commName(tileCommModeS(I,J))
225 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT, 1)
226 WRITE(msgBuf,'(A,A,I6.6,A,I6.6)')
227 & '// ',
228 & ' bi = ',tileBiS(I,J),
229 & ', bj = ',tileBjS(I,J)
230 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT, 1)
231 ELSE
232 WRITE(msgBuf,'(A)')
233 & '// SOUTH: no neighbor'
234 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT, 1)
235 ENDIF
236 C o North communication method
237 IF ( tileNoN(I,J).NE. NULL_TILE ) THEN
238 WRITE(msgBuf,'(A,A,I6.6,A,I6.6,A,A)')
239 & '// NORTH: ',
240 & 'Tile = ',tileNoN(I,J),
241 & ', Process = ',tilePidN(I,J),
242 & ', Comm = ',commName(tileCommModeN(I,J))
243 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT, 1)
244 WRITE(msgBuf,'(A,A,I6.6,A,I6.6)')
245 & '// ',
246 & ' bi = ',tileBiN(I,J),
247 & ', bj = ',tileBjN(I,J)
248 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT, 1)
249 ELSE
250 WRITE(msgBuf,'(A)')
251 & '// NORTH: no neighbor'
252 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT, 1)
253 ENDIF
254 ENDDO
255 ENDDO
256 WRITE(msgBuf,'(A)') ' '
257 CALL PRINT_MESSAGE( msgBuf,standardMessageUnit,SQUEEZE_RIGHT, 1)
258
259 RETURN
260 END

  ViewVC Help
Powered by ViewVC 1.1.22