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

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

  ViewVC Help
Powered by ViewVC 1.1.22