/[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.10 - (hide annotations) (download)
Mon May 24 15:15:11 1999 UTC (25 years ago) by adcroft
Branch: MAIN
Changes since 1.9: +2 -1 lines
Added IMPLICIT NONE.

1 cnh 1.1 #include "CPP_EEOPTIONS.h"
2     CStartOfInterface
3     SUBROUTINE INI_PROCS
4     C /==========================================================\
5     C | SUBROUTINE INI_PROCS |
6     C | o Initialise multiple concurrent processes environment. |
7     C |==========================================================|
8     C | Under MPI this routine calls various MPI service routines|
9     C | that map the model grid to MPI processes. The information|
10     C | is then stored in a common block for later use. |
11     C | Note: This routine can also be compiled with CPP |
12     C | directives set so that no multi-processing is initialise.|
13     C | This is OK and should work fine. |
14     C \==========================================================/
15 adcroft 1.10 IMPLICIT NONE
16 cnh 1.1
17     C === Global data ===
18     #include "SIZE.h"
19     #include "EEPARAMS.h"
20     #include "EESUPPORT.h"
21     CEndOfInterface
22    
23     C === Local variables ===
24     #ifdef ALLOW_USE_MPI
25     C msgBuffer - IO buffer
26     C myThid - Dummy thread id
27     C mpiRC - Error code reporting variable used
28     C with MPI.
29     C mpiGridSpec - No. of processes in X and Y.
30     C mpiPeriodicity - Flag indicating XY priodicity to MPI.
31     C arrElSize - Size of an array element in bytes used
32     C to define MPI datatypes for communication
33     C operations.
34     C arrElSep - Separation in units of array elements between
35     C blocks to be communicated.
36     C elCount - No. of blocks that are associated with MPI
37     C datatype.
38     C elLen - Length of an MPI datatype in terms of preexisting
39     C datatype.
40     C elStride - Distance between starting location of elements
41     C in an MPI datatype - can be bytes of datatype
42     C units.
43     CHARACTER*(MAX_LEN_MBUF) msgBuffer
44     INTEGER mpiRC
45     INTEGER mpiGridSpec(2)
46     INTEGER mpiPeriodicity(2)
47     INTEGER mpiLProcNam
48     CHARACTER*(MPI_MAX_PROCESSOR_NAME) mpiProcNam
49     INTEGER arrElSize
50     INTEGER arrElSep
51     INTEGER elCount
52     INTEGER elLen
53     INTEGER elStride
54     #endif /* ALLOW_USE_MPI */
55 cnh 1.6 INTEGER myThid
56 cnh 1.1
57     C-- Default values set to single processor case
58 cnh 1.7 C pid[W-SE] are the MPI process id of the neighbor
59 cnh 1.1 C processes. A process can be its own neighbor!
60 cnh 1.6 myThid = 1
61     myPid = 1
62     nProcs = 1
63     myPx = 1
64     myPy = 1
65     myXGlobalLo = 1
66     myYGlobalLo = 1
67     pidW = 1
68     pidE = 1
69     pidN = 1
70     pidS = 1
71     errorMessageUnit = 0
72     standardMessageUnit = 6
73    
74 cnh 1.1 #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 adcroft 1.8 I MPI_COMM_MODEL,2,mpiGridSpec,mpiPeriodicity,_mpiTRUE_,
141 cnh 1.1 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 cnh 1.6 myPid = mpiMyId
162 cnh 1.1 mpiPx = mpiGridSpec(1)
163     mpiPy = mpiGridSpec(2)
164     mpiXGlobalLo = 1 + sNx*nSx*(mpiPx)
165     mpiYGlobalLo = 1 + sNy*nSy*(mpiPy)
166     myXGlobalLo = mpiXGlobalLo
167     myYGlobalLo = mpiYGlobalLo
168 cnh 1.6 myPx = mpiPx+1
169     myPy = mpiPy+1
170 cnh 1.1 C-- Get MPI id for neighboring procs.
171     mpiGridSpec(1) = mpiPx-1
172 adcroft 1.9 IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_
173     & .AND. mpiGridSpec(1) .LT. 0 )
174 cnh 1.1 & mpiGridSpec(1) = nPx-1
175     mpiGridSpec(2) = mpiPy
176     CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidW , mpiRC )
177     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
178     eeBootError = .TRUE.
179     WRITE(msgBuffer,'(A,I)')
180     & 'S/R INI_PROCS: MPI_CART_RANK (pidW) return code',
181     & mpiRC
182     CALL PRINT_ERROR( msgBuffer , myThid)
183     GOTO 999
184     ENDIF
185     pidW = mpiPidW
186     mpiGridSpec(1) = mpiPx+1
187 adcroft 1.9 IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_
188     & .AND. mpiGridSpec(1) .GT. nPx-1 )
189 cnh 1.1 & mpiGridSpec(1) = 0
190     mpiGridSpec(2) = mpiPy
191     CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidE , mpiRC )
192     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
193     eeBootError = .TRUE.
194     WRITE(msgBuffer,'(A,I)')
195     & 'S/R INI_PROCS: MPI_CART_RANK (pidE) return code',
196     & mpiRC
197     CALL PRINT_ERROR( msgBuffer , myThid)
198     GOTO 999
199     ENDIF
200     pidE = mpiPidE
201     mpiGridSpec(1) = mpiPx
202     mpiGridSpec(2) = mpiPy-1
203 adcroft 1.9 IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_
204     & .AND. mpiGridSpec(2) .LT. 0 )
205 cnh 1.1 & mpiGridSpec(2) = nPy - 1
206     CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidS , mpiRC )
207     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
208     eeBootError = .TRUE.
209     WRITE(msgBuffer,'(A,I)')
210     & 'S/R INI_PROCS: MPI_CART_RANK (pidS) return code',
211     & mpiRC
212     CALL PRINT_ERROR( msgBuffer , myThid)
213     GOTO 999
214     ENDIF
215     pidS = mpiPidS
216     mpiGridSpec(1) = mpiPx
217     mpiGridSpec(2) = mpiPy+1
218 adcroft 1.9 IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_
219     & .AND. mpiGridSpec(2) .GT. nPy-1 )
220 cnh 1.1 & mpiGridSpec(2) = 0
221     CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidN , mpiRC )
222     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
223     eeBootError = .TRUE.
224     WRITE(msgBuffer,'(A,I)')
225     & 'S/R INI_PROCS: MPI_CART_RANK (pidN) return code',
226     & mpiRC
227     CALL PRINT_ERROR( msgBuffer , myThid)
228     GOTO 999
229     ENDIF
230     pidN = mpiPidN
231    
232     C-- Print summary of processor mapping on standard output
233     CALL MPI_GET_PROCESSOR_NAME( mpiProcNam, mpilProcNam, mpiRC )
234     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
235     eeBootError = .TRUE.
236     WRITE(msgBuffer,'(A,I)')
237     & 'S/R INI_PROCS: MPI_GET_PROCESSOR_NAME return code',
238     & mpiRC
239     CALL PRINT_ERROR( msgBuffer , myThid)
240     GOTO 999
241     ENDIF
242 adcroft 1.9 WRITE(msgBuffer,'(A)')
243     & '======= Starting MPI parallel Run ========='
244 cnh 1.1 CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
245     & SQUEEZE_BOTH , myThid)
246     WRITE(msgBuffer,'(A,A64)') ' My Processor Name = ',
247     & mpiProcNam(1:mpilProcNam)
248     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
249     & SQUEEZE_RIGHT , myThid)
250     WRITE(msgBuffer,'(A,I3,A,I3,A,I3,A,I3,A)') ' Located at (',
251     & mpiPx,',',mpiPy,
252     & ') on processor grid (0:',nPx-1,',0:',nPy-1,')'
253     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
254     & SQUEEZE_RIGHT , myThid)
255     WRITE(msgBuffer,'(A,I4,A,I4,A,I4,A,I4,A)') ' Origin at (',
256     & mpiXGlobalLo,',',mpiYGLobalLo,
257     & ') on global grid (1:',nPx*sNx*nSx,',1:',nPy*sNy*nSy,')'
258     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
259     & SQUEEZE_RIGHT , myThid)
260 adcroft 1.9 WRITE(msgBuffer,'(A,I4.4)')
261     & ' North neighbor = processor ', mpiPidN
262 cnh 1.1 CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
263     & SQUEEZE_RIGHT , myThid)
264 adcroft 1.9 WRITE(msgBuffer,'(A,I4.4)')
265     & ' South neighbor = processor ', mpiPidS
266 cnh 1.1 CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
267     & SQUEEZE_RIGHT , myThid)
268 adcroft 1.9 WRITE(msgBuffer,'(A,I4.4)')
269     & ' East neighbor = processor ', mpiPidE
270 cnh 1.1 CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
271     & SQUEEZE_RIGHT , myThid)
272 adcroft 1.9 WRITE(msgBuffer,'(A,I4.4)')
273     & ' West neighbor = processor ', mpiPidW
274 cnh 1.1 CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
275     & SQUEEZE_RIGHT , myThid)
276     C
277     C-- Create MPI types for transfer of array edges.
278     C-- Four and eight byte primitive (one block only) datatypes.
279     C-- These are common to all threads in the process.
280     C Notes:
281     C ======
282     C 1. The datatypes MPI_REAL4 and MPI_REAL8 are usually predefined.
283     C If they are not defined code must be added to create them -
284     C the MPI standard leaves optional whether they exist.
285     C 2. Per thread datatypes that handle all the edges for a thread
286     C are defined based on the type defined here.
287     C--
288     C-- xFace datatypes (east<-->west messages)
289     C--
290     C xFace (y=constant) for XY arrays with real*4 declaration.
291     arrElSep = (sNx+OLx*2)
292     elCount = sNy+OLy*2
293     elLen = OLx
294     elStride = arrElSep
295     CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_REAL4,
296     & mpiTypeXFaceBlock_xy_r4, mpiRC)
297     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
298     eeBootError = .TRUE.
299     WRITE(msgBuffer,'(A,I)')
300 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r4)',
301 cnh 1.1 & mpiRC
302     CALL PRINT_ERROR( msgBuffer , myThid)
303     ENDIF
304     CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r4, mpiRC)
305     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
306     eeBootError = .TRUE.
307     WRITE(msgBuffer,'(A,I)')
308 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r4)',
309 cnh 1.1 & mpiRC
310     CALL PRINT_ERROR( msgBuffer , myThid)
311     ENDIF
312    
313     C xFace (y=constant) for XY arrays with real*8 declaration.
314     CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_REAL8,
315     & mpiTypeXFaceBlock_xy_r8, mpiRC)
316     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
317     eeBootError = .TRUE.
318     WRITE(msgBuffer,'(A,I)')
319 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r8)',
320 cnh 1.1 & mpiRC
321     CALL PRINT_ERROR( msgBuffer , myThid)
322     ENDIF
323     CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r8, mpiRC)
324     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
325     eeBootError = .TRUE.
326     WRITE(msgBuffer,'(A,I)')
327 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r8)',
328 cnh 1.1 & mpiRC
329     CALL PRINT_ERROR( msgBuffer , myThid)
330     ENDIF
331    
332     C xFace (y=constant) for XYZ arrays with real*4 declaration.
333     arrElSize = 4
334     arrElSep = (sNx+OLx*2)*(sNy+OLy*2)
335 cnh 1.5 elCount = Nr
336 cnh 1.1 elLen = 1
337     elStride = arrElSize*arrElSep
338     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,
339     & mpiTypeXFaceBlock_xy_r4,
340     & mpiTypeXFaceBlock_xyz_r4, mpiRC)
341     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
342     eeBootError = .TRUE.
343     WRITE(msgBuffer,'(A,I)')
344 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r4)',
345 cnh 1.1 & mpiRC
346     CALL PRINT_ERROR( msgBuffer , myThid)
347     ENDIF
348     CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r4, mpiRC)
349     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
350     eeBootError = .TRUE.
351     WRITE(msgBuffer,'(A,I)')
352 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xyz_r4)',
353 cnh 1.1 & mpiRC
354     CALL PRINT_ERROR( msgBuffer , myThid)
355     ENDIF
356    
357     C xFace (y=constant) for XYZ arrays with real*8 declaration.
358     arrElSize = 8
359     elStride = arrElSize*arrElSep
360     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,
361     & mpiTypeXFaceBlock_xy_r8,
362     & mpiTypeXFaceBlock_xyz_r8, mpiRC)
363     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
364     eeBootError = .TRUE.
365     WRITE(msgBuffer,'(A,I)')
366 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r8)',
367 cnh 1.1 & mpiRC
368     CALL PRINT_ERROR( msgBuffer , myThid)
369     ENDIF
370     CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r8, mpiRC)
371     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
372     eeBootError = .TRUE.
373     WRITE(msgBuffer,'(A,I)')
374 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xyz_r8)',
375 cnh 1.1 & mpiRC
376     CALL PRINT_ERROR( msgBuffer , myThid)
377     ENDIF
378     C--
379     C-- yFace datatypes (north<-->south messages)
380     C--
381     C yFace (x=constant) for XY arrays with real*4 declaration
382     elCount = OLy*(sNx+OLx*2)
383     CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_REAL4,
384     & mpiTypeYFaceBlock_xy_r4, mpiRC)
385     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
386     eeBootError = .TRUE.
387     WRITE(msgBuffer,'(A,I)')
388 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r4)',
389 cnh 1.1 & mpiRC
390     CALL PRINT_ERROR( msgBuffer , myThid)
391     ENDIF
392     CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r4, mpiRC)
393     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
394     eeBootError = .TRUE.
395     WRITE(msgBuffer,'(A,I)')
396 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r4)',
397 cnh 1.1 & mpiRC
398     CALL PRINT_ERROR( msgBuffer , myThid)
399     ENDIF
400     C yFace (x=constant) for XY arrays with real*8 declaration
401     CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_REAL8,
402     & mpiTypeYFaceBlock_xy_r8, mpiRC)
403     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
404     eeBootError = .TRUE.
405     WRITE(msgBuffer,'(A,I)')
406 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r8)',
407 cnh 1.1 & mpiRC
408     CALL PRINT_ERROR( msgBuffer , myThid)
409     ENDIF
410     CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r8, mpiRC)
411     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
412     eeBootError = .TRUE.
413     WRITE(msgBuffer,'(A,I)')
414 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r8)',
415 cnh 1.1 & mpiRC
416     CALL PRINT_ERROR( msgBuffer , myThid)
417     ENDIF
418     C yFace (x=constant) for XYZ arrays with real*4 declaration
419     arrElSize = 4
420     arrElSep = (sNx+OLx*2)*(sNy+OLy*2)
421 cnh 1.5 elCount = Nr
422 cnh 1.1 elLen = 1
423     elStride = arrElSize*arrElSep
424     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,
425     & mpiTypeYFaceBlock_xy_r4,
426     & mpiTypeYFaceBlock_xyz_r4, mpiRC)
427     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
428     eeBootError = .TRUE.
429     WRITE(msgBuffer,'(A,I)')
430 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r4)',
431 cnh 1.1 & mpiRC
432     CALL PRINT_ERROR( msgBuffer , myThid)
433     ENDIF
434     CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r4, mpiRC)
435     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
436     eeBootError = .TRUE.
437     WRITE(msgBuffer,'(A,I)')
438 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r4)',
439 cnh 1.1 & mpiRC
440     CALL PRINT_ERROR( msgBuffer , myThid)
441     ENDIF
442     C yFace (x=constant) for XYZ arrays with real*8 declaration
443     arrElSize = 8
444     elStride = arrElSize*arrElSep
445     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,
446     & mpiTypeYFaceBlock_xy_r8,
447     & mpiTypeYFaceBlock_xyz_r8, mpiRC)
448     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
449     eeBootError = .TRUE.
450     WRITE(msgBuffer,'(A,I)')
451 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r8)',
452 cnh 1.1 & mpiRC
453     CALL PRINT_ERROR( msgBuffer , myThid)
454     ENDIF
455     CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r8, mpiRC)
456     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
457     eeBootError = .TRUE.
458     WRITE(msgBuffer,'(A,I)')
459 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r8)',
460 cnh 1.1 & mpiRC
461     CALL PRINT_ERROR( msgBuffer , myThid)
462     ENDIF
463    
464     C-- Assign MPI values used in generating unique tags for messages.
465     mpiTagW = 1
466     mpiTagE = 2
467     mpiTagS = 3
468     mpiTagN = 4
469    
470     C
471 adcroft 1.8 CALL MPI_Barrier(MPI_COMM_MODEL,mpiRC)
472 cnh 1.1
473    
474     C
475     #ifndef ALWAYS_USE_MPI
476     ENDIF
477     #endif
478     #endif /* ALLOW_USE_MPI */
479    
480     999 CONTINUE
481    
482     RETURN
483     END
484 cnh 1.6
485 adcroft 1.10 C $Id: ini_procs.F,v 1.9 1999/05/03 21:37:55 adcroft Exp $

  ViewVC Help
Powered by ViewVC 1.1.22