/[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.9 - (hide annotations) (download)
Mon May 3 21:37:55 1999 UTC (25 years, 2 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint21, checkpoint22
Changes since 1.8: +35 -26 lines
Modifications to fit the 72-column rule.

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

  ViewVC Help
Powered by ViewVC 1.1.22