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

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

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


Revision 1.6 - (hide annotations) (download)
Tue May 18 17:39:21 1999 UTC (25 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint28, checkpoint29, checkpoint22, checkpoint23, checkpoint24, checkpoint25, checkpoint27, branch-atmos-merge-freeze, branch-atmos-merge-start, checkpoint26, branch-atmos-merge-shapiro, checkpoint33, checkpoint32, checkpoint31, checkpoint30, checkpoint34, branch-atmos-merge-zonalfilt, branch-atmos-merge-phase5, branch-atmos-merge-phase4, branch-atmos-merge-phase7, branch-atmos-merge-phase6, branch-atmos-merge-phase1, branch-atmos-merge-phase3, branch-atmos-merge-phase2
Branch point for: branch-atmos-merge
Changes since 1.5: +3 -2 lines
Added IMPLICIT NONE where missing and changed formatting from 'I' to 'I5'.

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

  ViewVC Help
Powered by ViewVC 1.1.22