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

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

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


Revision 1.1 - (hide annotations) (download)
Wed Apr 22 19:15:30 1998 UTC (26 years, 1 month ago) by cnh
Branch: MAIN
Branch point for: cnh
Initial revision

1 cnh 1.1 C $Id$
2    
3     #include "CPP_EEOPTIONS.h"
4    
5     CStartOfInterface
6     SUBROUTINE INI_PROCS
7     C /==========================================================\
8     C | SUBROUTINE INI_PROCS |
9     C | o Initialise multiple concurrent processes environment. |
10     C |==========================================================|
11     C | Under MPI this routine calls various MPI service routines|
12     C | that map the model grid to MPI processes. The information|
13     C | is then stored in a common block for later use. |
14     C | Note: This routine can also be compiled with CPP |
15     C | directives set so that no multi-processing is initialise.|
16     C | This is OK and should work fine. |
17     C \==========================================================/
18    
19     C === Global data ===
20     #include "SIZE.h"
21     #include "EEPARAMS.h"
22     #include "EESUPPORT.h"
23     CEndOfInterface
24    
25     C === Local variables ===
26     #ifdef ALLOW_USE_MPI
27     C msgBuffer - IO buffer
28     C myThid - Dummy thread id
29     C mpiRC - Error code reporting variable used
30     C with MPI.
31     C mpiGridSpec - No. of processes in X and Y.
32     C mpiPeriodicity - Flag indicating XY priodicity to MPI.
33     C arrElSize - Size of an array element in bytes used
34     C to define MPI datatypes for communication
35     C operations.
36     C arrElSep - Separation in units of array elements between
37     C blocks to be communicated.
38     C elCount - No. of blocks that are associated with MPI
39     C datatype.
40     C elLen - Length of an MPI datatype in terms of preexisting
41     C datatype.
42     C elStride - Distance between starting location of elements
43     C in an MPI datatype - can be bytes of datatype
44     C units.
45     CHARACTER*(MAX_LEN_MBUF) msgBuffer
46     INTEGER myThid
47     INTEGER mpiRC
48     INTEGER mpiGridSpec(2)
49     INTEGER mpiPeriodicity(2)
50     INTEGER mpiLProcNam
51     CHARACTER*(MPI_MAX_PROCESSOR_NAME) mpiProcNam
52     INTEGER arrElSize
53     INTEGER arrElSep
54     INTEGER elCount
55     INTEGER elLen
56     INTEGER elStride
57     #endif /* ALLOW_USE_MPI */
58    
59     C-- Default values set to single processor case
60     C pid[W-SE] are the MPI process id's of the neighbor
61     C processes. A process can be its own neighbor!
62     pidW = 1
63     pidE = 1
64     pidN = 1
65     pidS = 1
66     pidNW = 1
67     pidNE = 1
68     pidSW = 1
69     pidSE = 1
70     myPx = 1
71     myPy = 1
72     myXGlobalLo = 1
73     myYGlobalLo = 1
74     #ifdef ALLOW_USE_MPI
75     C--
76     C-- MPI style full multiple-process initialisation
77     C-- ==============================================
78     #ifndef ALWAYS_USE_MPI
79     IF ( usingMPI ) THEN
80     #endif
81    
82     C-- Arrange MPI processes on a cartesian grid
83     C Set variable indicating which MPI process is to the north,
84     C south, east, west, south-west, south-east, north-west
85     C and north-east of me e.g.
86     C
87     C Plan view of model domain centered on process ME
88     C ================================================
89     C
90     C : : : :
91     C : : : :
92     C : : : :
93     C .....------------------------------.....
94     C | | | |
95     C | NW | N | NE |
96     C | | | |
97     C .....------------------------------.....
98     C | | | |
99     C | W | ME | E |
100     C | | | |
101     C .....------------------------------.....
102     C | | | |
103     C | SW | S | SE |
104     C | | | |
105     C .....------------------------------.....
106     C : : : :
107     C Y : : : :
108     C / \ : : : :
109     C |
110     C |
111     C |----> X
112     C
113     C-- Set default MPI communicator to XY processor grid
114     myThid = 1
115     mpiGridSpec(1) = nPx
116     mpiGridSpec(2) = nPy
117     C Could be periodic in X and/or Y - set at run time or compile time!
118     mpiPeriodicity(1) = _mpiTRUE_
119     mpiPeriodicity(2) = _mpiTRUE_
120     #ifdef CAN_PREVENT_X_PERIODICITY
121     #ifndef ALWAYS_PREVENT_X_PERIODICITY
122     IF ( notUsingXPeriodicity ) THEN
123     #endif
124     mpiPeriodicity(1) = _mpiFALSE_
125     #ifndef ALWAYS_PREVENT_X_PERIODICITY
126     ENDIF
127     #endif
128     #endif /* CAN_PREVENT_X_PERIODICITY */
129     #ifdef CAN_PREVENT_Y_PERIODICITY
130     #ifndef ALWAYS_PREVENT_Y_PERIODICITY
131     IF ( notUsingYPeriodicity ) THEN
132     #endif
133     mpiPeriodicity(2) = _mpiFALSE_
134     #ifndef ALWAYS_PREVENT_Y_PERIODICITY
135     ENDIF
136     #endif
137     #endif /* CAN_PREVENT_Y_PERIODICITY */
138    
139     CALL MPI_CART_CREATE(
140     I MPI_COMM_WORLD,2,mpiGridSpec,mpiPeriodicity,_mpiTRUE_,
141     O mpiComm, mpiRC )
142     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
143     eeBootError = .TRUE.
144     WRITE(msgBuffer,'(A,I)')
145     & 'S/R INI_PROCS: MPI_CART_CREATE return code',
146     & mpiRC
147     CALL PRINT_ERROR( msgBuffer , myThid)
148     GOTO 999
149     ENDIF
150    
151     C-- Get my location on the grid
152     CALL MPI_CART_COORDS( mpiComm, mpiMyId, 2, mpiGridSpec, mpiRC )
153     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
154     eeBootError = .TRUE.
155     WRITE(msgBuffer,'(A,I)')
156     & 'S/R INI_PROCS: MPI_CART_COORDS return code',
157     & mpiRC
158     CALL PRINT_ERROR( msgBuffer , myThid)
159     GOTO 999
160     ENDIF
161     mpiPx = mpiGridSpec(1)
162     mpiPy = mpiGridSpec(2)
163     mpiXGlobalLo = 1 + sNx*nSx*(mpiPx)
164     mpiYGlobalLo = 1 + sNy*nSy*(mpiPy)
165     myXGlobalLo = mpiXGlobalLo
166     myYGlobalLo = mpiYGlobalLo
167     C-- Get MPI id for neighboring procs.
168     mpiGridSpec(1) = mpiPx-1
169     IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_ .AND. mpiGridSpec(1) .LT. 0 )
170     & mpiGridSpec(1) = nPx-1
171     mpiGridSpec(2) = mpiPy
172     CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidW , mpiRC )
173     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
174     eeBootError = .TRUE.
175     WRITE(msgBuffer,'(A,I)')
176     & 'S/R INI_PROCS: MPI_CART_RANK (pidW) return code',
177     & mpiRC
178     CALL PRINT_ERROR( msgBuffer , myThid)
179     GOTO 999
180     ENDIF
181     pidW = mpiPidW
182     mpiGridSpec(1) = mpiPx+1
183     IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_ .AND. mpiGridSpec(1) .GT. nPx-1 )
184     & mpiGridSpec(1) = 0
185     mpiGridSpec(2) = mpiPy
186     CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidE , mpiRC )
187     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
188     eeBootError = .TRUE.
189     WRITE(msgBuffer,'(A,I)')
190     & 'S/R INI_PROCS: MPI_CART_RANK (pidE) return code',
191     & mpiRC
192     CALL PRINT_ERROR( msgBuffer , myThid)
193     GOTO 999
194     ENDIF
195     pidE = mpiPidE
196     mpiGridSpec(1) = mpiPx
197     mpiGridSpec(2) = mpiPy-1
198     IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_ .AND. mpiGridSpec(2) .LT. 0 )
199     & mpiGridSpec(2) = nPy - 1
200     CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidS , mpiRC )
201     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
202     eeBootError = .TRUE.
203     WRITE(msgBuffer,'(A,I)')
204     & 'S/R INI_PROCS: MPI_CART_RANK (pidS) return code',
205     & mpiRC
206     CALL PRINT_ERROR( msgBuffer , myThid)
207     GOTO 999
208     ENDIF
209     pidS = mpiPidS
210     mpiGridSpec(1) = mpiPx
211     mpiGridSpec(2) = mpiPy+1
212     IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_ .AND. mpiGridSpec(2) .GT. nPy-1 )
213     & mpiGridSpec(2) = 0
214     CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidN , mpiRC )
215     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
216     eeBootError = .TRUE.
217     WRITE(msgBuffer,'(A,I)')
218     & 'S/R INI_PROCS: MPI_CART_RANK (pidN) return code',
219     & mpiRC
220     CALL PRINT_ERROR( msgBuffer , myThid)
221     GOTO 999
222     ENDIF
223     pidN = mpiPidN
224     mpiGridSpec(1) = mpiPx-1
225     IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_ .AND. mpiGridSpec(1) .LT. 0 )
226     & mpiGridSpec(1) = nPx - 1
227     mpiGridSpec(2) = mpiPy-1
228     IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_ .AND. mpiGridSpec(2) .LT. 0 )
229     & mpiGridSpec(2) = nPy - 1
230     CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidSW, mpiRC )
231     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
232     eeBootError = .TRUE.
233     WRITE(msgBuffer,'(A,I)')
234     & 'S/R INI_PROCS: MPI_CART_RANK (pidSW) return code',
235     & mpiRC
236     CALL PRINT_ERROR( msgBuffer , myThid)
237     GOTO 999
238     ENDIF
239     pidSW = mpiPidSW
240     mpiGridSpec(1) = mpiPx+1
241     IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_ .AND. mpiGridSpec(1) .GT. nPx-1 )
242     & mpiGridSpec(1) = 0
243     mpiGridSpec(2) = mpiPy-1
244     IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_ .AND. mpiGridSpec(2) .LT. 0 )
245     & mpiGridSpec(2) = nPy - 1
246     CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidSE, mpiRC )
247     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
248     eeBootError = .TRUE.
249     WRITE(msgBuffer,'(A,I)')
250     & 'S/R INI_PROCS: MPI_CART_RANK (pidSE) return code',
251     & mpiRC
252     CALL PRINT_ERROR( msgBuffer , myThid)
253     GOTO 999
254     ENDIF
255     pidSE = mpiPidSE
256     mpiGridSpec(1) = mpiPx-1
257     IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_ .AND. mpiGridSpec(1) .LT. 0 )
258     & mpiGridSpec(1) = nPx-1
259     mpiGridSpec(2) = mpiPy+1
260     IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_ .AND. mpiGridSpec(2) .GT. nPy-1 )
261     & mpiGridSpec(2) = 0
262     CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidNW, mpiRC )
263     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
264     eeBootError = .TRUE.
265     WRITE(msgBuffer,'(A,I)')
266     & 'S/R INI_PROCS: MPI_CART_RANK (pidNW) return code',
267     & mpiRC
268     CALL PRINT_ERROR( msgBuffer , myThid)
269     GOTO 999
270     ENDIF
271     pidNW = mpiPidNW
272     mpiGridSpec(1) = mpiPx+1
273     IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_ .AND. mpiGridSpec(1) .LT. 0 )
274     & mpiGridSpec(1) = nPx-1
275     mpiGridSpec(2) = mpiPy+1
276     IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_ .AND. mpiGridSpec(2) .GT. nPy-1 )
277     & mpiGridSpec(2) = 0
278     CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidNE, mpiRC )
279     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
280     eeBootError = .TRUE.
281     WRITE(msgBuffer,'(A,I)')
282     & 'S/R INI_PROCS: MPI_CART_RANK (pidNE) return code',
283     & mpiRC
284     CALL PRINT_ERROR( msgBuffer , myThid)
285     GOTO 999
286     ENDIF
287     pidNE = mpiPidNE
288    
289     C-- Print summary of processor mapping on standard output
290     CALL MPI_GET_PROCESSOR_NAME( mpiProcNam, mpilProcNam, mpiRC )
291     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
292     eeBootError = .TRUE.
293     WRITE(msgBuffer,'(A,I)')
294     & 'S/R INI_PROCS: MPI_GET_PROCESSOR_NAME return code',
295     & mpiRC
296     CALL PRINT_ERROR( msgBuffer , myThid)
297     GOTO 999
298     ENDIF
299     WRITE(msgBuffer,'(A)') '======= Starting MPI parallel Run ========='
300     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
301     & SQUEEZE_BOTH , myThid)
302     WRITE(msgBuffer,'(A,A64)') ' My Processor Name = ',
303     & mpiProcNam(1:mpilProcNam)
304     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
305     & SQUEEZE_RIGHT , myThid)
306     WRITE(msgBuffer,'(A,I3,A,I3,A,I3,A,I3,A)') ' Located at (',
307     & mpiPx,',',mpiPy,
308     & ') on processor grid (0:',nPx-1,',0:',nPy-1,')'
309     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
310     & SQUEEZE_RIGHT , myThid)
311     WRITE(msgBuffer,'(A,I4,A,I4,A,I4,A,I4,A)') ' Origin at (',
312     & mpiXGlobalLo,',',mpiYGLobalLo,
313     & ') on global grid (1:',nPx*sNx*nSx,',1:',nPy*sNy*nSy,')'
314     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
315     & SQUEEZE_RIGHT , myThid)
316     WRITE(msgBuffer,'(A,I4.4)') ' North neighbor = processor ', mpiPidN
317     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
318     & SQUEEZE_RIGHT , myThid)
319     WRITE(msgBuffer,'(A,I4.4)') ' South neighbor = processor ', mpiPidS
320     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
321     & SQUEEZE_RIGHT , myThid)
322     WRITE(msgBuffer,'(A,I4.4)') ' East neighbor = processor ', mpiPidE
323     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
324     & SQUEEZE_RIGHT , myThid)
325     WRITE(msgBuffer,'(A,I4.4)') ' West neighbor = processor ', mpiPidW
326     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
327     & SQUEEZE_RIGHT , myThid)
328     WRITE(msgBuffer,'(A,I4.4)') ' NW neighbor = processor ', mpiPidNW
329     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
330     & SQUEEZE_RIGHT , myThid)
331     WRITE(msgBuffer,'(A,I4.4)') ' NE neighbor = processor ', mpiPidNE
332     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
333     & SQUEEZE_RIGHT , myThid)
334     WRITE(msgBuffer,'(A,I4.4)') ' SW neighbor = processor ', mpiPidSW
335     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
336     & SQUEEZE_RIGHT , myThid)
337     WRITE(msgBuffer,'(A,I4.4)') ' SE neighbor = processor ', mpiPidSE
338     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
339     & SQUEEZE_RIGHT , myThid)
340     C
341     C-- Create MPI types for transfer of array edges.
342     C-- Four and eight byte primitive (one block only) datatypes.
343     C-- These are common to all threads in the process.
344     C Notes:
345     C ======
346     C 1. The datatypes MPI_REAL4 and MPI_REAL8 are usually predefined.
347     C If they are not defined code must be added to create them -
348     C the MPI standard leaves optional whether they exist.
349     C 2. Per thread datatypes that handle all the edges for a thread
350     C are defined based on the type defined here.
351     C--
352     C-- xFace datatypes (east<-->west messages)
353     C--
354     C xFace (y=constant) for XY arrays with real*4 declaration.
355     arrElSep = (sNx+OLx*2)
356     elCount = sNy+OLy*2
357     elLen = OLx
358     elStride = arrElSep
359     CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_REAL4,
360     & mpiTypeXFaceBlock_xy_r4, mpiRC)
361     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
362     eeBootError = .TRUE.
363     WRITE(msgBuffer,'(A,I)')
364     & 'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r4)',
365     & mpiRC
366     CALL PRINT_ERROR( msgBuffer , myThid)
367     ENDIF
368     CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r4, mpiRC)
369     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
370     eeBootError = .TRUE.
371     WRITE(msgBuffer,'(A,I)')
372     & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r4)',
373     & mpiRC
374     CALL PRINT_ERROR( msgBuffer , myThid)
375     ENDIF
376    
377     C xFace (y=constant) for XY arrays with real*8 declaration.
378     CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_REAL8,
379     & mpiTypeXFaceBlock_xy_r8, mpiRC)
380     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
381     eeBootError = .TRUE.
382     WRITE(msgBuffer,'(A,I)')
383     & 'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r8)',
384     & mpiRC
385     CALL PRINT_ERROR( msgBuffer , myThid)
386     ENDIF
387     CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r8, mpiRC)
388     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
389     eeBootError = .TRUE.
390     WRITE(msgBuffer,'(A,I)')
391     & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r8)',
392     & mpiRC
393     CALL PRINT_ERROR( msgBuffer , myThid)
394     ENDIF
395    
396     C xFace (y=constant) for XYZ arrays with real*4 declaration.
397     arrElSize = 4
398     arrElSep = (sNx+OLx*2)*(sNy+OLy*2)
399     elCount = Nz
400     elLen = 1
401     elStride = arrElSize*arrElSep
402     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,
403     & mpiTypeXFaceBlock_xy_r4,
404     & mpiTypeXFaceBlock_xyz_r4, mpiRC)
405     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
406     eeBootError = .TRUE.
407     WRITE(msgBuffer,'(A,I)')
408     & 'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r4)',
409     & mpiRC
410     CALL PRINT_ERROR( msgBuffer , myThid)
411     ENDIF
412     CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r4, mpiRC)
413     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
414     eeBootError = .TRUE.
415     WRITE(msgBuffer,'(A,I)')
416     & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xyz_r4)',
417     & mpiRC
418     CALL PRINT_ERROR( msgBuffer , myThid)
419     ENDIF
420    
421     C xFace (y=constant) for XYZ arrays with real*8 declaration.
422     arrElSize = 8
423     elStride = arrElSize*arrElSep
424     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,
425     & mpiTypeXFaceBlock_xy_r8,
426     & mpiTypeXFaceBlock_xyz_r8, mpiRC)
427     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
428     eeBootError = .TRUE.
429     WRITE(msgBuffer,'(A,I)')
430     & 'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r8)',
431     & mpiRC
432     CALL PRINT_ERROR( msgBuffer , myThid)
433     ENDIF
434     CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r8, mpiRC)
435     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
436     eeBootError = .TRUE.
437     WRITE(msgBuffer,'(A,I)')
438     & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xyz_r8)',
439     & mpiRC
440     CALL PRINT_ERROR( msgBuffer , myThid)
441     ENDIF
442     C--
443     C-- yFace datatypes (north<-->south messages)
444     C--
445     C yFace (x=constant) for XY arrays with real*4 declaration
446     elCount = OLy*(sNx+OLx*2)
447     CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_REAL4,
448     & mpiTypeYFaceBlock_xy_r4, mpiRC)
449     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
450     eeBootError = .TRUE.
451     WRITE(msgBuffer,'(A,I)')
452     & 'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r4)',
453     & mpiRC
454     CALL PRINT_ERROR( msgBuffer , myThid)
455     ENDIF
456     CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r4, mpiRC)
457     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
458     eeBootError = .TRUE.
459     WRITE(msgBuffer,'(A,I)')
460     & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r4)',
461     & mpiRC
462     CALL PRINT_ERROR( msgBuffer , myThid)
463     ENDIF
464     C yFace (x=constant) for XY arrays with real*8 declaration
465     CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_REAL8,
466     & mpiTypeYFaceBlock_xy_r8, mpiRC)
467     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
468     eeBootError = .TRUE.
469     WRITE(msgBuffer,'(A,I)')
470     & 'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r8)',
471     & mpiRC
472     CALL PRINT_ERROR( msgBuffer , myThid)
473     ENDIF
474     CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r8, mpiRC)
475     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
476     eeBootError = .TRUE.
477     WRITE(msgBuffer,'(A,I)')
478     & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r8)',
479     & mpiRC
480     CALL PRINT_ERROR( msgBuffer , myThid)
481     ENDIF
482     C yFace (x=constant) for XYZ arrays with real*4 declaration
483     arrElSize = 4
484     arrElSep = (sNx+OLx*2)*(sNy+OLy*2)
485     elCount = Nz
486     elLen = 1
487     elStride = arrElSize*arrElSep
488     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,
489     & mpiTypeYFaceBlock_xy_r4,
490     & mpiTypeYFaceBlock_xyz_r4, mpiRC)
491     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
492     eeBootError = .TRUE.
493     WRITE(msgBuffer,'(A,I)')
494     & 'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r4)',
495     & mpiRC
496     CALL PRINT_ERROR( msgBuffer , myThid)
497     ENDIF
498     CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r4, mpiRC)
499     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
500     eeBootError = .TRUE.
501     WRITE(msgBuffer,'(A,I)')
502     & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r4)',
503     & mpiRC
504     CALL PRINT_ERROR( msgBuffer , myThid)
505     ENDIF
506     C yFace (x=constant) for XYZ arrays with real*8 declaration
507     arrElSize = 8
508     elStride = arrElSize*arrElSep
509     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,
510     & mpiTypeYFaceBlock_xy_r8,
511     & mpiTypeYFaceBlock_xyz_r8, mpiRC)
512     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
513     eeBootError = .TRUE.
514     WRITE(msgBuffer,'(A,I)')
515     & 'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r8)',
516     & mpiRC
517     CALL PRINT_ERROR( msgBuffer , myThid)
518     ENDIF
519     CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r8, mpiRC)
520     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
521     eeBootError = .TRUE.
522     WRITE(msgBuffer,'(A,I)')
523     & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r8)',
524     & mpiRC
525     CALL PRINT_ERROR( msgBuffer , myThid)
526     ENDIF
527    
528     C-- Assign MPI values used in generating unique tags for messages.
529     mpiTagW = 1
530     mpiTagE = 2
531     mpiTagS = 3
532     mpiTagN = 4
533     mpiTagSW = 5
534     mpiTagSE = 6
535     mpiTagNW = 7
536     mpiTagNE = 8
537    
538     C
539     CALL MPI_Barrier(MPI_COMM_WORLD,mpiRC)
540    
541    
542     C
543     #ifndef ALWAYS_USE_MPI
544     ENDIF
545     #endif
546     #endif /* ALLOW_USE_MPI */
547    
548     999 CONTINUE
549    
550     RETURN
551     END
552    
553     C $Id: $

  ViewVC Help
Powered by ViewVC 1.1.22