/[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.3 - (hide annotations) (download)
Thu Apr 23 20:56:54 1998 UTC (26 years ago) by cnh
Branch: MAIN
CVS Tags: checkpoint11, checkpoint10, checkpoint13, redigm, checkpoint5, checkpoint4, checkpoint7, checkpoint6, checkpoint1, checkpoint3, checkpoint2, checkpoint9, checkpoint8, kloop1, kloop2, checkpoint12, branch-point-rdot
Branch point for: checkpoint7-4degree-ref, branch-rdot
Changes since 1.2: +1 -3 lines
Further changes to convert from $Id to $Header

1 cnh 1.3 C $Header: /home/ubuntu/mnt/e9_copy/MITgcm/eesupp/src/ini_threading_environment.F,v 1.3 1998/04/23 20:56:54 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     C | Generally we do not start separate threads here but |
12     C | just initialise data structures indicating which of the |
13     C | nSx x nSy blocks a thread is responsible for. |
14     C | The multiple threads are spawned in the top level MAIN |
15     C | routine. |
16     C \==========================================================/
17    
18     C == Global data ==
19     #include "SIZE.h"
20     #include "EEPARAMS.h"
21     #include "EESUPPORT.h"
22     CEndOfInterface
23    
24     C == Local variables ==
25     C bXPerThread - Blocks of size sNx per thread.
26     C byPerThread - Blocks of size sNy per thread.
27     C Thid - Thread index. Temporary used in loops
28     C which set per. thread values on a
29     C cartesian grid.
30     C bxLo, bxHi - Work vars. for thread index
31     C byLo, byHi range. bxLo is the lowest i index
32     C that a thread covers, bxHi is the
33     C highest i index. byLo is the lowest
34     C j index, byHi is the highest j index.
35     C I, J - Loop counter
36     C msgBuf - I/O buffer for reporting status information.
37     C myThid - Dummy thread id for use in printed messages
38     C ( this routine "INI_THREADING_ENVIRONMENT" is called before
39     C multi-threading has started.)
40     C threadWest - Temporaries used in calculating neighbor threads.
41     C threadEast
42     C threadSouth
43     C threadNorth
44     INTEGER bxPerThread
45     INTEGER byPerThread
46     INTEGER Thid
47     INTEGER bxLo, bxHi
48     INTEGER byLo, byHi
49     INTEGER I, J
50     CHARACTER*(MAX_LEN_MBUF) msgBuf
51     INTEGER myThid
52     INTEGER threadWest
53     INTEGER threadEast
54     INTEGER threadSouth
55     INTEGER threadNorth
56     INTEGER threadNW
57     INTEGER threadNE
58     INTEGER threadSW
59     INTEGER threadSE
60    
61     #ifdef ALLOW_USE_MPI
62     C elCount - Length in elements of an MPI datatype
63     C elStride - Stride between elements of an MPI datatype.
64     C elLen - Length of each element of the datatype
65     C arrElSize - Size in bytes of an array element
66     C arrElSep - Separation in array elements between consecutive
67     C start locations for an MPI datatype.
68     C mpiRC - MPI return code
69     INTEGER elCount
70     INTEGER elStride
71     INTEGER elLen
72     INTEGER arrElSize
73     INTEGER arrElSep
74     INTEGER mpiRC
75     #endif /* ALLOW_USE_MPI */
76    
77     C-- Set default for all threads of having no blocks to
78     C-- work on - except for thread 1.
79     myBxLo(1) = 1
80     myBxHi(1) = nSx
81     myByLo(1) = 1
82     myByHi(1) = nSy
83     DO I = 2, MAX_NO_THREADS
84     myBxLo(I) = 0
85     myBxHi(I) = 1
86     myByLo(I) = 0
87     myByHi(I) = 1
88     ENDDO
89     myThid = 1
90    
91     C-- If there are multiple threads allocate different range of the
92     C-- nSx*nSy blocks to each thread.
93     C For now handle simple case of no. blocks nSx = n*nTx and
94     C no. blocks nSy = m*nTy ( where m and n are integer ). This
95     C is handled by simply mapping threads to blocks in sequence
96     C with the x thread index moving fastest.
97     C Later code which sets the thread number of neighboring blocks
98     C needs to be consisten with the code here.
99     nThreads = nTx * nTy
100    
101     C-- Initialise the barrier mechanism
102     CALL BARRIER_INIT
103    
104     IF ( nThreads .NE. nTx*nTy ) THEN
105     WRITE(msgBuf,'(A,A,A,I,A,I)')
106     & 'S/R INI_THREADING_ENVIRONMENT:',
107     & ' Total number of threads is not the same as nTx*nTy.',
108     & ' nTx * nTy = ',nTx*nTy,' nThreads = ',nThreads
109     CALL PRINT_ERROR(msgBuf, myThid)
110     eeBootError = .TRUE.
111     STOP 'ABNORMAL END: S/R INI_THREADING_ENVIRONMENT'
112     ENDIF
113     bxPerThread = nSx/nTx
114     IF ( bxPerThread*nTx .NE. nSx ) THEN
115     WRITE(msgBuf,'(A,A)')
116     & 'S/R INI_THREADING_ENVIRONMENT:',
117     & ' Number of blocks in X (nSx) must be exact multiple of threads in X (nTx).'
118     CALL PRINT_ERROR(msgBuf, myThid)
119     eeBootError = .TRUE.
120     STOP 'ABNORMAL END: S/R INI_THREADING_ENVIRONMENT'
121     ENDIF
122     byPerThread = nSy/nTy
123     IF ( byPerThread*nTy .NE. nSy ) THEN
124     WRITE(msgBuf,'(A,A)')
125     & 'S/R INI_THREADING_ENVIRONMENT:',
126     & ' Number of blocks in Y (nSy) must be exact multiple of threads in Y (nTy).'
127     CALL PRINT_ERROR(msgBuf, myThid)
128     eeBootError = .TRUE.
129     STOP 'ABNORMAL END: S/R INI_THREADING_ENVIRONMENT'
130     ENDIF
131     IF ( .NOT. eeBootError ) THEN
132     byLo = 1
133     DO J=1,nTy
134     byHi = byLo+byPerThread-1
135     bxLo = 1
136     DO I=1,nTx
137     Thid = (J-1)*nTx+I
138     bxHi = bxLo+bxPerThread-1
139     myBxLo(Thid) = bxLo
140     myBxHi(Thid) = bxHi
141     myByLo(Thid) = byLo
142     myByHi(Thid) = byHi
143     bxLo = bxHi+1
144     ENDDO
145     byLo = byHi+1
146     ENDDO
147     ENDIF
148    
149     C-- Set flags saying how each thread is communicating
150     C Notes:
151     C ======
152     C By default each block communicates with its neighbor using
153     C direct reads and writes from the neighbors overlap regions.
154     C This rule will always applie for the blocks in the interior
155     C of a processes domain, but for the "outside" faces of blocks on
156     C the edges of the processes domain i.e. where bx=1 or nSx or
157     C where by = 1 or nSy. In this section each thread checks to see
158     C whether any of the blocks it is responsible for are "outside"
159     C blocks and if so what communication strategy should be used.
160     C to
161     DO I=1, nThreads
162    
163     C 1. Check for block which is on the west edge.
164     commW(I) = COMM_SHARED
165     IF ( notUsingXPeriodicity .AND.
166     & myBxLo(I) .EQ. 1 .AND.
167     & myPx .EQ. 1 ) THEN
168     commW(I) = COMM_NONE
169     ELSEIF ( myBxLo(I) .EQ. 1 ) THEN
170     #ifdef ALLOW_USE_MPI
171     #ifndef ALWAYS_USE_MPI
172     IF ( usingMPI ) THEN
173     #endif
174     IF ( mpiPidW .NE. MPI_PROC_NULL ) THEN
175     commW(I) = COMM_MPI
176     allMyEdgesAreSharedMemory(I) = .FALSE.
177     ENDIF
178     #ifndef ALWAYS_USE_MPI
179     ENDIF
180     #endif
181     #endif /* ALLOW_USE_MPI */
182     ENDIF
183    
184     C 2. Check for block which is on the east edge.
185     commE(I) = COMM_SHARED
186     IF ( notUsingXPeriodicity .AND.
187     & myBxHi(I) .EQ. nSx .AND.
188     & myPx .EQ. nPx ) THEN
189     commE(I) = COMM_NONE
190     ELSEIF ( myBxHi(I) .EQ. nSx ) THEN
191     #ifdef ALLOW_USE_MPI
192     #ifndef ALWAYS_USE_MPI
193     IF ( usingMPI ) THEN
194     #endif
195     IF ( mpiPidE .NE. MPI_PROC_NULL ) THEN
196     commE(I) = COMM_MPI
197     allMyEdgesAreSharedMemory(I) = .FALSE.
198     ENDIF
199     #ifndef ALWAYS_USE_MPI
200     ENDIF
201     #endif
202     #endif /* ALLOW_USE_MPI */
203     ENDIF
204    
205     C 3. Check for block which is southern edge
206     commS(I) = COMM_SHARED
207     IF ( notUsingYPeriodicity .AND.
208     & myByLo(I) .EQ. 1 .AND.
209     & myPy .EQ. 1 ) THEN
210     commS(I) = COMM_NONE
211     ELSEIF ( myByLo(I) .EQ. 1 ) THEN
212     #ifdef ALLOW_USE_MPI
213     #ifndef ALWAYS_USE_MPI
214     IF ( usingMPI ) THEN
215     #endif
216     IF ( mpiPidS .NE. MPI_PROC_NULL ) THEN
217     commS(I) = COMM_MPI
218     allMyEdgesAreSharedMemory(I) = .FALSE.
219     ENDIF
220     #ifndef ALWAYS_USE_MPI
221     ENDIF
222     #endif
223     #endif /* ALLOW_USE_MPI */
224     ENDIF
225    
226     C 4. Check for block which is on northern edge
227     commN(I) = COMM_SHARED
228     IF ( notUsingYPeriodicity .AND.
229     & myByHi(I) .EQ. nSy .AND.
230     & myPy .EQ. nPy ) THEN
231     commN(I) = COMM_NONE
232     ELSEIF ( myByHi(I) .EQ. nSy ) THEN
233     #ifdef ALLOW_USE_MPI
234     #ifndef ALWAYS_USE_MPI
235     IF ( usingMPI ) THEN
236     #endif
237     IF ( mpiPidN .NE. MPI_PROC_NULL ) THEN
238     commN(I) = COMM_MPI
239     allMyEdgesAreSharedMemory(I) = .FALSE.
240     ENDIF
241     #ifndef ALWAYS_USE_MPI
242     ENDIF
243     #endif
244     #endif /* ALLOW_USE_MPI */
245     ENDIF
246     ENDDO
247    
248     C-- Print mapping of threads to grid points.
249     WRITE(msgBuf,'(A)') '// ======================================================'
250     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
251     & SQUEEZE_RIGHT , 1)
252    
253     WRITE(msgBuf,'(A)') '// Mapping of tiles to threads'
254     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
255     & SQUEEZE_RIGHT , 1)
256    
257     WRITE(msgBuf,'(A)') '// ======================================================'
258     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
259     & SQUEEZE_RIGHT , 1)
260    
261     DO I=1,nThreads
262     WRITE(msgBuf,'(A,I4,A,4(I4,A1))')
263     & '// -o- Thread',I,', tiles (',
264     & myBxLo(I),':',myBxHi(I),',',myByLo(I),':',myByHi(I),')'
265     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_BOTH , 1)
266     IF ( myBxLo(I) .NE. 1 .OR.
267     & commW(I) .EQ. COMM_SHARED ) THEN
268     WRITE(msgBuf,'(A,A)') '//',' shared memory to west.'
269     ELSEIF ( commW(I) .NE. COMM_NONE ) THEN
270     WRITE(msgBuf,'(A,A)') '//',' messages to west.'
271     ELSE
272     WRITE(msgBuf,'(A,A)') '//',' no communication to west.'
273     ENDIF
274     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
275     IF ( myBxHi(I) .NE. nSx .OR.
276     & commE(I) .EQ. COMM_SHARED ) THEN
277     WRITE(msgBuf,'(A,A)') '//',' shared memory to east.'
278     ELSEIF ( commE(I) .NE. COMM_NONE ) THEN
279     WRITE(msgBuf,'(A,A)') '//',' messages to east.'
280     ELSE
281     WRITE(msgBuf,'(A,A)') '//',' no communication to east.'
282     ENDIF
283     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
284     IF ( myByLo(I) .NE. 1 .OR.
285     & commS(I) .EQ. COMM_SHARED ) THEN
286     WRITE(msgBuf,'(A,A)') '//',' shared memory to south.'
287     ELSEIF ( commS(I) .NE. COMM_NONE ) THEN
288     WRITE(msgBuf,'(A,A)') '//',' messages to south.'
289     ELSE
290     WRITE(msgBuf,'(A,A)') '//',' no communication to south.'
291     ENDIF
292     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
293     IF ( myByHi(I) .NE. nSy .OR.
294     & commN(I) .EQ. COMM_SHARED ) THEN
295     WRITE(msgBuf,'(A,A)') '//',' shared memory to north.'
296     ELSEIF ( commN(I) .NE. COMM_NONE ) THEN
297     WRITE(msgBuf,'(A,A)') '//',' messages to north.'
298     ELSE
299     WRITE(msgBuf,'(A,A)') '//',' no communication to north.'
300     ENDIF
301     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
302     ENDDO
303     WRITE(msgBuf,'(A)') ' '
304     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
305    
306     #ifdef ALLOW_USE_MPI
307     C-- Create MPI datatypes for communicating thread boundaries if needed
308     C For every thread we define 8 MPI datatypes for use
309     C in indicating regions of data to transfer as follows:
310     C o mpiTypeXFaceThread_xy_r4
311     C Handles east-west transfer for XY arrays of REAL*4
312     C o mpiTypeXFaceThread_xy_r8
313     C Handles east-west transfer for XY arrays of REAL*8
314     C o mpiTypeYFaceThread_xy_r4
315     C Handles north-south transfer for XY arrays of REAL*4
316     C o mpiTypeYFaceThread_xy_r8
317     C Handles north-south transfer for XY arrays of REAL*8
318     C o mpiTypeXFaceThread_xyz_r4
319     C Handles east-west transfer for XYZ arrays of REAL*4
320     C o mpiTypeXFaceThread_xyz_r8
321     C Handles east-west transfer for XYZ arrays of REAL*8
322     C o mpiTypeYFaceThread_xyz_r4
323     C Handles north-south transfer for XYZ arrays of REAL*4
324     C o mpiTypeYFaceThread_xyz_r8
325     C Handles north-south transfer for XYZarrays of REAL*8
326     #ifndef ALWAYS_USE_MPI
327     IF ( usingMPI ) THEN
328     #endif
329     DO I =1, nThreads
330    
331     C x-face exchanges for xy real*4 data
332     elCount = myByHi(I)-myByLo(I)+1
333     elLen = 1
334     arrElSep = (sNx+OLx*2)*(sNy+OLy*2)*nSx
335     arrElSize = 4
336     elStride = arrElSep*arrElSize
337     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,mpiTypeXFaceBlock_xy_r4,
338     O mpiTypeXFaceThread_xy_r4(I), mpiRC )
339     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
340     eeBootError = .TRUE.
341     WRITE(msgBuf,'(A,I)')
342     & 'S/R INI_THREADS: MPI_TYPE_HVECTOR (mpiTypeXFaceThread_xy_r4)',
343     & mpiRC
344     CALL PRINT_ERROR( msgBuf , myThid)
345     ENDIF
346     CALL MPI_TYPE_COMMIT(mpiTypeXFaceThread_xy_r4(I),mpiRC)
347     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
348     eeBootError = .TRUE.
349     WRITE(msgBuf,'(A,I)')
350     & 'S/R INI_THREADS: MPI_TYPE_COMMIT (mpiTypeXFaceThread_xy_r4)',
351     & mpiRC
352     CALL PRINT_ERROR( msgBuf , myThid)
353     ENDIF
354    
355     C x-face exchanges for xy real*8 data
356     arrElSize = 8
357     elStride = arrElSep*arrElSize
358     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,mpiTypeXFaceBlock_xy_r8,
359     O mpiTypeXFaceThread_xy_r8(I), mpiRC )
360     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
361     eeBootError = .TRUE.
362     WRITE(msgBuf,'(A,I)')
363     & 'S/R INI_THREADS: MPI_TYPE_HVECTOR (mpiTypeXFaceThread_xy_r8)',
364     & mpiRC
365     CALL PRINT_ERROR( msgBuf , myThid)
366     ENDIF
367     CALL MPI_TYPE_COMMIT(mpiTypeXFaceThread_xy_r8(I),mpiRC)
368     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
369     eeBootError = .TRUE.
370     WRITE(msgBuf,'(A,I)')
371     & 'S/R INI_THREADS: MPI_TYPE_COMMIT (mpiTypeXFaceThread_xy_r8)',
372     & mpiRC
373     CALL PRINT_ERROR( msgBuf , myThid)
374     ENDIF
375    
376     C x-face exchanges for xyz real*4 data
377     elCount = myByHi(I)-myByLo(I)+1
378     elLen = 1
379     arrElSep = (sNx+OLx*2)*(sNy+OLy*2)*Nz*nSx
380     arrElSize = 4
381     elStride = arrElSep*arrElSize
382     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,mpiTypeXFaceBlock_xyz_r4,
383     O mpiTypeXFaceThread_xyz_r4(I), mpiRC )
384     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
385     eeBootError = .TRUE.
386     WRITE(msgBuf,'(A,I)')
387     & 'S/R INI_THREADS: MPI_TYPE_HVECTOR (mpiTypeXFaceThread_xyz_r4)',
388     & mpiRC
389     CALL PRINT_ERROR( msgBuf , myThid)
390     ENDIF
391     CALL MPI_TYPE_COMMIT(mpiTypeXFaceThread_xyz_r4(I),mpiRC)
392     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
393     eeBootError = .TRUE.
394     WRITE(msgBuf,'(A,I)')
395     & 'S/R INI_THREADS: MPI_TYPE_COMMIT (mpiTypeXFaceThread_xyz_r4)',
396     & mpiRC
397     CALL PRINT_ERROR( msgBuf , myThid)
398     ENDIF
399    
400     C x-face exchanges for xyz real*8 data
401     arrElSize = 8
402     elStride = arrElSep*arrElSize
403     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,mpiTypeXFaceBlock_xyz_r8,
404     O mpiTypeXFaceThread_xyz_r8(I), mpiRC )
405     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
406     eeBootError = .TRUE.
407     WRITE(msgBuf,'(A,I)')
408     & 'S/R INI_THREADS: MPI_TYPE_HVECTOR (mpiTypeXFaceThread_xyz_r8)',
409     & mpiRC
410     CALL PRINT_ERROR( msgBuf , myThid)
411     ENDIF
412     CALL MPI_TYPE_COMMIT(mpiTypeXFaceThread_xyz_r8(I),mpiRC)
413     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
414     eeBootError = .TRUE.
415     WRITE(msgBuf,'(A,I)')
416     & 'S/R INI_THREADS: MPI_TYPE_COMMIT (mpiTypeXFaceThread_xyz_r8)',
417     & mpiRC
418     CALL PRINT_ERROR( msgBuf , myThid)
419     ENDIF
420    
421     C y-face exchages for xy real*4 data
422     elCount = myBxHi(I)-myBxLo(I)+1
423     elLen = 1
424     arrElSep = (sNx+OLx*2)*(sNy+OLy*2)
425     arrElSize = 4
426     elStride = arrElSep*arrElSize
427     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,mpiTypeYFaceBlock_xy_r4,
428     O mpiTypeYFaceThread_xy_r4(I), mpiRC )
429     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
430     eeBootError = .TRUE.
431     WRITE(msgBuf,'(A,I)')
432     & 'S/R INI_THREADS: MPI_TYPE_HVECTOR (mpiTypeYFaceThread_xy_r4)',
433     & mpiRC
434     CALL PRINT_ERROR( msgBuf , myThid)
435     ENDIF
436     CALL MPI_TYPE_COMMIT(mpiTypeYFaceThread_xy_r4(I),mpiRC)
437     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
438     eeBootError = .TRUE.
439     WRITE(msgBuf,'(A,I)')
440     & 'S/R INI_THREADS: MPI_TYPE_COMMIT (mpiTypeYFaceThread_xy_r4)',
441     & mpiRC
442     CALL PRINT_ERROR( msgBuf , myThid)
443     ENDIF
444    
445     C y-face exchages for xy real*8 data
446     arrElSize = 8
447     elStride = arrElSep*arrElSize
448     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,mpiTypeYFaceBlock_xy_r8,
449     O mpiTypeYFaceThread_xy_r8(I), mpiRC )
450     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
451     eeBootError = .TRUE.
452     WRITE(msgBuf,'(A,I)')
453     & 'S/R INI_THREADS: MPI_TYPE_HVECTOR (mpiTypeYFaceThread_xy_r8)',
454     & mpiRC
455     CALL PRINT_ERROR( msgBuf , myThid)
456     ENDIF
457     CALL MPI_TYPE_COMMIT(mpiTypeYFaceThread_xy_r8(I),mpiRC)
458     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
459     eeBootError = .TRUE.
460     WRITE(msgBuf,'(A,I)')
461     & 'S/R INI_THREADS: MPI_TYPE_COMMIT (mpiTypeYFaceThread_xy_r8)',
462     & mpiRC
463     CALL PRINT_ERROR( msgBuf , myThid)
464     ENDIF
465    
466     C y-face exchages for xyz real*4 data
467     elCount = myBxHi(I)-myBxLo(I)+1
468     elLen = 1
469     arrElSep = (sNx+OLx*2)*(sNy+OLy*2)*Nz
470     arrElSize = 4
471     elStride = arrElSep*arrElSize
472     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,mpiTypeYFaceBlock_xyz_r4,
473     O mpiTypeYFaceThread_xyz_r4(I), mpiRC )
474     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
475     eeBootError = .TRUE.
476     WRITE(msgBuf,'(A,I)')
477     & 'S/R INI_THREADS: MPI_TYPE_HVECTOR (mpiTypeYFaceThread_xyz_r4)',
478     & mpiRC
479     CALL PRINT_ERROR( msgBuf , myThid)
480     ENDIF
481     CALL MPI_TYPE_COMMIT(mpiTypeYFaceThread_xyz_r4(I),mpiRC)
482     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
483     eeBootError = .TRUE.
484     WRITE(msgBuf,'(A,I)')
485     & 'S/R INI_THREADS: MPI_TYPE_COMMIT (mpiTypeYFaceThread_xyz_r4)',
486     & mpiRC
487     CALL PRINT_ERROR( msgBuf , myThid)
488     ENDIF
489    
490     C y-face exchages for xy real*8 data
491     arrElSize = 8
492     elStride = arrElSep*arrElSize
493     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,mpiTypeYFaceBlock_xyz_r8,
494     O mpiTypeYFaceThread_xyz_r8(I), mpiRC )
495     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
496     eeBootError = .TRUE.
497     WRITE(msgBuf,'(A,I)')
498     & 'S/R INI_THREADS: MPI_TYPE_HVECTOR (mpiTypeYFaceThread_xyz_r8)',
499     & mpiRC
500     CALL PRINT_ERROR( msgBuf , myThid)
501     ENDIF
502     CALL MPI_TYPE_COMMIT(mpiTypeYFaceThread_xyz_r8(I),mpiRC)
503     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
504     eeBootError = .TRUE.
505     WRITE(msgBuf,'(A,I)')
506     & 'S/R INI_THREADS: MPI_TYPE_COMMIT (mpiTypeYFaceThread_xyz_r8)',
507     & mpiRC
508     CALL PRINT_ERROR( msgBuf , myThid)
509     ENDIF
510    
511     ENDDO
512    
513     #ifndef ALWAYS_USE_MPI
514     ENDIF
515     #endif
516     #endif /* ALLOW_USE_MPI */
517    
518     C-- Calculate the thread numbers of the threads I might want to "message"
519     C Notes:
520     C 1. This code needs to be consistent with the code that maps threads to
521     C blocks earlier in this routine in which threads are arranged
522     C 13 14 15 16 /|\
523     C 9 10 11 12 | nTy
524     C 5 6 7 8 |
525     C 1 2 3 4 \|/
526     C <---- nTx --->
527     C on equally sized collections of sNx x sNy sub-blocks.
528     DO I = 1, nThreads
529     C Find thread to west, east, south, north using wrap around for
530     C threads managing "outside" blocks.
531     threadWest = I-1
532     IF ( myBxLo(I) .EQ. 1 ) threadWest = I+nTx-1
533     threadEast = I+1
534     IF ( myBxHi(I) .EQ. nSx ) threadEast = I-nTx+1
535     threadSouth = I-nTx
536     IF ( myByLo(I) .EQ. 1 ) threadSouth = I+nTx*(nTy-1)
537     threadNorth = I+nTx
538     IF ( myByHi(I) .EQ. nSy ) threadNorth = I-nTx*(nTy-1)
539     C Find thread to NW, NE, SW, SE - again with wrap around.
540     threadNW = threadWest+nTx
541     IF ( myByHi(threadWest) .EQ. nSy ) threadNW = threadWest-nTx*(nTy-1)
542     threadNE = threadEast+nTx
543     IF ( myByHi(threadEast) .EQ. nSy ) threadNE = threadEast-nTx*(nTy-1)
544     threadSW = threadWest-nTx
545     IF ( myByHi(threadWest) .EQ. 1 ) threadSW = threadWest+nTx*(nTy-1)
546     threadSE = threadEast-nTx
547     IF ( myByHi(threadEast) .EQ. 1 ) threadSE = threadEast+nTx*(nTy-1)
548     myThrW(I) = threadWest
549     myThrE(I) = threadEast
550     myThrN(I) = threadNorth
551     myThrS(I) = threadSouth
552     myThrNW(I) = threadNW
553     myThrNE(I) = threadNE
554     myThrSW(I) = threadSW
555     myThrSE(I) = threadSE
556     ENDDO
557    
558     RETURN
559     END

  ViewVC Help
Powered by ViewVC 1.1.22