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

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

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

revision 1.8 by adcroft, Mon Mar 22 17:37:43 1999 UTC revision 1.11 by adcroft, Mon May 24 15:19:53 1999 UTC
# Line 12  C     | Note: This routine can also be c Line 12  C     | Note: This routine can also be c
12  C     | directives set so that no multi-processing is initialise.|  C     | directives set so that no multi-processing is initialise.|
13  C     | This is OK and should work fine.                         |  C     | This is OK and should work fine.                         |
14  C     \==========================================================/  C     \==========================================================/
15          IMPLICIT NONE
16    
17  C     === Global data ===  C     === Global data ===
18  #include "SIZE.h"  #include "SIZE.h"
# Line 140  C      Could be periodic in X and/or Y - Line 141  C      Could be periodic in X and/or Y -
141       O  mpiComm, mpiRC )       O  mpiComm, mpiRC )
142         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
143          eeBootError = .TRUE.          eeBootError = .TRUE.
144          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
145       &        'S/R INI_PROCS: MPI_CART_CREATE return code',       &        'S/R INI_PROCS: MPI_CART_CREATE return code',
146       &        mpiRC       &        mpiRC
147          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 151  C--    Get my location on the grid Line 152  C--    Get my location on the grid
152         CALL MPI_CART_COORDS( mpiComm, mpiMyId, 2, mpiGridSpec, mpiRC )         CALL MPI_CART_COORDS( mpiComm, mpiMyId, 2, mpiGridSpec, mpiRC )
153         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
154          eeBootError = .TRUE.          eeBootError = .TRUE.
155          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
156       &        'S/R INI_PROCS: MPI_CART_COORDS return code',       &        'S/R INI_PROCS: MPI_CART_COORDS return code',
157       &        mpiRC       &        mpiRC
158          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 168  C--    Get my location on the grid Line 169  C--    Get my location on the grid
169         myPy = mpiPy+1         myPy = mpiPy+1
170  C--    Get MPI id for neighboring procs.  C--    Get MPI id for neighboring procs.
171         mpiGridSpec(1) = mpiPx-1         mpiGridSpec(1) = mpiPx-1
172         IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_ .AND. mpiGridSpec(1) .LT. 0 )         IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_
173         &   .AND. mpiGridSpec(1) .LT. 0 )
174       &  mpiGridSpec(1) = nPx-1       &  mpiGridSpec(1) = nPx-1
175         mpiGridSpec(2) = mpiPy         mpiGridSpec(2) = mpiPy
176         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidW , mpiRC )         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidW , mpiRC )
177         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
178          eeBootError = .TRUE.          eeBootError = .TRUE.
179          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
180       &        'S/R INI_PROCS: MPI_CART_RANK (pidW) return code',       &        'S/R INI_PROCS: MPI_CART_RANK (pidW) return code',
181       &        mpiRC       &        mpiRC
182          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 182  C--    Get MPI id for neighboring procs. Line 184  C--    Get MPI id for neighboring procs.
184         ENDIF         ENDIF
185         pidW = mpiPidW         pidW = mpiPidW
186         mpiGridSpec(1) = mpiPx+1         mpiGridSpec(1) = mpiPx+1
187         IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_ .AND. mpiGridSpec(1) .GT. nPx-1 )         IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_
188         &   .AND. mpiGridSpec(1) .GT. nPx-1 )
189       &  mpiGridSpec(1) = 0       &  mpiGridSpec(1) = 0
190         mpiGridSpec(2) = mpiPy         mpiGridSpec(2) = mpiPy
191         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidE , mpiRC )         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidE , mpiRC )
192         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
193          eeBootError = .TRUE.          eeBootError = .TRUE.
194          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
195       &        'S/R INI_PROCS: MPI_CART_RANK (pidE) return code',       &        'S/R INI_PROCS: MPI_CART_RANK (pidE) return code',
196       &        mpiRC       &        mpiRC
197          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 197  C--    Get MPI id for neighboring procs. Line 200  C--    Get MPI id for neighboring procs.
200         pidE = mpiPidE         pidE = mpiPidE
201         mpiGridSpec(1) = mpiPx         mpiGridSpec(1) = mpiPx
202         mpiGridSpec(2) = mpiPy-1         mpiGridSpec(2) = mpiPy-1
203         IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_ .AND. mpiGridSpec(2) .LT. 0 )         IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_
204         &   .AND. mpiGridSpec(2) .LT. 0 )
205       &  mpiGridSpec(2) = nPy - 1       &  mpiGridSpec(2) = nPy - 1
206         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidS , mpiRC )         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidS , mpiRC )
207         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
208          eeBootError = .TRUE.          eeBootError = .TRUE.
209          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
210       &        'S/R INI_PROCS: MPI_CART_RANK (pidS) return code',       &        'S/R INI_PROCS: MPI_CART_RANK (pidS) return code',
211       &        mpiRC       &        mpiRC
212          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 211  C--    Get MPI id for neighboring procs. Line 215  C--    Get MPI id for neighboring procs.
215         pidS = mpiPidS         pidS = mpiPidS
216         mpiGridSpec(1) = mpiPx         mpiGridSpec(1) = mpiPx
217         mpiGridSpec(2) = mpiPy+1         mpiGridSpec(2) = mpiPy+1
218         IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_ .AND. mpiGridSpec(2) .GT. nPy-1 )         IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_
219         &   .AND. mpiGridSpec(2) .GT. nPy-1 )
220       &  mpiGridSpec(2) = 0       &  mpiGridSpec(2) = 0
221         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidN , mpiRC )         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidN , mpiRC )
222         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
223          eeBootError = .TRUE.          eeBootError = .TRUE.
224          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
225       &        'S/R INI_PROCS: MPI_CART_RANK (pidN) return code',       &        'S/R INI_PROCS: MPI_CART_RANK (pidN) return code',
226       &        mpiRC       &        mpiRC
227          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 228  C--    Print summary of processor mappin Line 233  C--    Print summary of processor mappin
233         CALL MPI_GET_PROCESSOR_NAME( mpiProcNam, mpilProcNam, mpiRC )         CALL MPI_GET_PROCESSOR_NAME( mpiProcNam, mpilProcNam, mpiRC )
234         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
235          eeBootError = .TRUE.          eeBootError = .TRUE.
236          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
237       &        'S/R INI_PROCS: MPI_GET_PROCESSOR_NAME return code',       &        'S/R INI_PROCS: MPI_GET_PROCESSOR_NAME return code',
238       &        mpiRC       &        mpiRC
239          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
240          GOTO 999          GOTO 999
241         ENDIF         ENDIF
242         WRITE(msgBuffer,'(A)') '======= Starting MPI parallel Run ========='         WRITE(msgBuffer,'(A)')
243         &   '======= Starting MPI parallel Run ========='
244         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
245       &  SQUEEZE_BOTH , myThid)       &  SQUEEZE_BOTH , myThid)
246         WRITE(msgBuffer,'(A,A64)') ' My Processor Name = ',         WRITE(msgBuffer,'(A,A64)') ' My Processor Name = ',
# Line 251  C--    Print summary of processor mappin Line 257  C--    Print summary of processor mappin
257       &  ') on global grid (1:',nPx*sNx*nSx,',1:',nPy*sNy*nSy,')'       &  ') on global grid (1:',nPx*sNx*nSx,',1:',nPy*sNy*nSy,')'
258         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
259       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
260         WRITE(msgBuffer,'(A,I4.4)') ' North neighbor = processor ', mpiPidN         WRITE(msgBuffer,'(A,I4.4)')
261         &   ' North neighbor = processor ', mpiPidN
262         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
263       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
264         WRITE(msgBuffer,'(A,I4.4)') ' South neighbor = processor ', mpiPidS         WRITE(msgBuffer,'(A,I4.4)')
265         &   ' South neighbor = processor ', mpiPidS
266         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
267       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
268         WRITE(msgBuffer,'(A,I4.4)') '  East neighbor = processor ', mpiPidE         WRITE(msgBuffer,'(A,I4.4)')
269         &   '  East neighbor = processor ', mpiPidE
270         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
271       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
272         WRITE(msgBuffer,'(A,I4.4)') '  West neighbor = processor ', mpiPidW         WRITE(msgBuffer,'(A,I4.4)')
273         &   '  West neighbor = processor ', mpiPidW
274         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
275       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
276  C  C
# Line 286  C      xFace (y=constant) for XY arrays Line 296  C      xFace (y=constant) for XY arrays
296       &                       mpiTypeXFaceBlock_xy_r4, mpiRC)       &                       mpiTypeXFaceBlock_xy_r4, mpiRC)
297         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
298          eeBootError = .TRUE.          eeBootError = .TRUE.
299          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
300       &        'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r4)',
301       &        mpiRC       &        mpiRC
302          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
303         ENDIF         ENDIF
304         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r4, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r4, mpiRC)
305         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
306          eeBootError = .TRUE.          eeBootError = .TRUE.
307          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
308       &        'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r4)',
309       &        mpiRC       &        mpiRC
310          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
311         ENDIF         ENDIF
# Line 305  C      xFace (y=constant) for XY arrays Line 315  C      xFace (y=constant) for XY arrays
315       &                       mpiTypeXFaceBlock_xy_r8, mpiRC)       &                       mpiTypeXFaceBlock_xy_r8, mpiRC)
316         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
317          eeBootError = .TRUE.          eeBootError = .TRUE.
318          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
319       &        'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r8)',
320       &        mpiRC       &        mpiRC
321          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
322         ENDIF         ENDIF
323         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r8, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r8, mpiRC)
324         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
325          eeBootError = .TRUE.          eeBootError = .TRUE.
326          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
327       &        'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r8)',
328       &        mpiRC       &        mpiRC
329          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
330         ENDIF         ENDIF
# Line 330  C      xFace (y=constant) for XYZ arrays Line 340  C      xFace (y=constant) for XYZ arrays
340       &                       mpiTypeXFaceBlock_xyz_r4, mpiRC)       &                       mpiTypeXFaceBlock_xyz_r4, mpiRC)
341         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
342          eeBootError = .TRUE.          eeBootError = .TRUE.
343          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
344       &        'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r4)',
345       &        mpiRC       &        mpiRC
346          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
347         ENDIF         ENDIF
348         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r4, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r4, mpiRC)
349         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
350          eeBootError = .TRUE.          eeBootError = .TRUE.
351          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
352       &        'S/R INI_PROCS: MPI_TYPE_COMMIT  (mpiTypeXFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT  (mpiTypeXFaceBlock_xyz_r4)',
353       &        mpiRC       &        mpiRC
354          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
355         ENDIF         ENDIF
# Line 352  C      xFace (y=constant) for XYZ arrays Line 362  C      xFace (y=constant) for XYZ arrays
362       &                       mpiTypeXFaceBlock_xyz_r8, mpiRC)       &                       mpiTypeXFaceBlock_xyz_r8, mpiRC)
363         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
364          eeBootError = .TRUE.          eeBootError = .TRUE.
365          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
366       &        'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r8)',
367       &        mpiRC       &        mpiRC
368          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
369         ENDIF         ENDIF
370         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r8, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r8, mpiRC)
371         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
372          eeBootError = .TRUE.          eeBootError = .TRUE.
373          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
374       &        'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xyz_r8)',
375       &        mpiRC       &        mpiRC
376          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
377         ENDIF         ENDIF
# Line 374  C      yFace (x=constant) for XY arrays Line 384  C      yFace (x=constant) for XY arrays
384       &                          mpiTypeYFaceBlock_xy_r4, mpiRC)       &                          mpiTypeYFaceBlock_xy_r4, mpiRC)
385         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
386          eeBootError = .TRUE.          eeBootError = .TRUE.
387          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
388       &        'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r4)',
389       &        mpiRC       &        mpiRC
390          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
391         ENDIF         ENDIF
392         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r4, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r4, mpiRC)
393         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
394          eeBootError = .TRUE.          eeBootError = .TRUE.
395          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
396       &        'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r4)',
397       &        mpiRC       &        mpiRC
398          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
399         ENDIF         ENDIF
# Line 392  C      yFace (x=constant) for XY arrays Line 402  C      yFace (x=constant) for XY arrays
402       &                          mpiTypeYFaceBlock_xy_r8, mpiRC)       &                          mpiTypeYFaceBlock_xy_r8, mpiRC)
403         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
404          eeBootError = .TRUE.          eeBootError = .TRUE.
405          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
406       &        'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r8)',
407       &        mpiRC       &        mpiRC
408          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
409         ENDIF         ENDIF
410         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r8, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r8, mpiRC)
411         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
412          eeBootError = .TRUE.          eeBootError = .TRUE.
413          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
414       &        'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r8)',
415       &        mpiRC       &        mpiRC
416          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
417         ENDIF         ENDIF
# Line 416  C      yFace (x=constant) for XYZ arrays Line 426  C      yFace (x=constant) for XYZ arrays
426       &                       mpiTypeYFaceBlock_xyz_r4, mpiRC)       &                       mpiTypeYFaceBlock_xyz_r4, mpiRC)
427         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
428          eeBootError = .TRUE.          eeBootError = .TRUE.
429          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
430       &        'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r4)',
431       &        mpiRC       &        mpiRC
432          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
433         ENDIF         ENDIF
434         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r4, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r4, mpiRC)
435         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
436          eeBootError = .TRUE.          eeBootError = .TRUE.
437          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
438       &        'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r4)',
439       &        mpiRC       &        mpiRC
440          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
441         ENDIF         ENDIF
# Line 437  C      yFace (x=constant) for XYZ arrays Line 447  C      yFace (x=constant) for XYZ arrays
447       &                       mpiTypeYFaceBlock_xyz_r8, mpiRC)       &                       mpiTypeYFaceBlock_xyz_r8, mpiRC)
448         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
449          eeBootError = .TRUE.          eeBootError = .TRUE.
450          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
451       &        'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r8)',
452       &        mpiRC       &        mpiRC
453          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
454         ENDIF         ENDIF
455         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r8, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r8, mpiRC)
456         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
457          eeBootError = .TRUE.          eeBootError = .TRUE.
458          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
459       &        'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r8)',
460       &        mpiRC       &        mpiRC
461          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
462         ENDIF         ENDIF

Legend:
Removed from v.1.8  
changed lines
  Added in v.1.11

  ViewVC Help
Powered by ViewVC 1.1.22