/[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.5 by cnh, Sat Aug 22 17:51:06 1998 UTC revision 1.9 by adcroft, Mon May 3 21:37:55 1999 UTC
# Line 1  Line 1 
 C $Header$  
   
1  #include "CPP_EEOPTIONS.h"  #include "CPP_EEOPTIONS.h"
   
2  CStartOfInterface  CStartOfInterface
3        SUBROUTINE INI_PROCS        SUBROUTINE INI_PROCS
4  C     /==========================================================\  C     /==========================================================\
# Line 43  C     elStride         - Distance betwee Line 40  C     elStride         - Distance betwee
40  C                        in an MPI datatype - can be bytes of datatype  C                        in an MPI datatype - can be bytes of datatype
41  C                        units.  C                        units.
42        CHARACTER*(MAX_LEN_MBUF) msgBuffer        CHARACTER*(MAX_LEN_MBUF) msgBuffer
       INTEGER myThid  
43        INTEGER mpiRC        INTEGER mpiRC
44        INTEGER mpiGridSpec(2)        INTEGER mpiGridSpec(2)
45        INTEGER mpiPeriodicity(2)        INTEGER mpiPeriodicity(2)
# Line 55  C                        units. Line 51  C                        units.
51        INTEGER elLen        INTEGER elLen
52        INTEGER elStride        INTEGER elStride
53  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
54          INTEGER myThid
55    
56  C--   Default values set to single processor case  C--   Default values set to single processor case
57  C     pid[W-SE] are the MPI process id's of the neighbor  C     pid[W-SE] are the MPI process id of the neighbor
58  C     processes. A process can be its own neighbor!  C     processes. A process can be its own neighbor!
59        pidW          = 1        myThid      = 1
60        pidE          = 1        myPid       = 1
61        pidN          = 1        nProcs      = 1
62        pidS          = 1        myPx        = 1
63        pidNW         = 1        myPy        = 1
64        pidNE         = 1        myXGlobalLo = 1
65        pidSW         = 1        myYGlobalLo = 1
66        pidSE         = 1        pidW        = 1
67        myPx          = 1        pidE        = 1
68        myPy          = 1        pidN        = 1
69        myXGlobalLo   = 1        pidS        = 1
70        myYGlobalLo   = 1        errorMessageUnit    = 0
71          standardMessageUnit = 6
72    
73  #ifdef ALLOW_USE_MPI  #ifdef ALLOW_USE_MPI
74  C--  C--
75  C--   MPI style full multiple-process initialisation  C--   MPI style full multiple-process initialisation
# Line 137  C      Could be periodic in X and/or Y - Line 136  C      Could be periodic in X and/or Y -
136  #endif /* CAN_PREVENT_Y_PERIODICITY */  #endif /* CAN_PREVENT_Y_PERIODICITY */
137    
138         CALL MPI_CART_CREATE(         CALL MPI_CART_CREATE(
139       I  MPI_COMM_WORLD,2,mpiGridSpec,mpiPeriodicity,_mpiTRUE_,       I  MPI_COMM_MODEL,2,mpiGridSpec,mpiPeriodicity,_mpiTRUE_,
140       O  mpiComm, mpiRC )       O  mpiComm, mpiRC )
141         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
142          eeBootError = .TRUE.          eeBootError = .TRUE.
# Line 158  C--    Get my location on the grid Line 157  C--    Get my location on the grid
157          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
158          GOTO 999          GOTO 999
159         ENDIF         ENDIF
160           myPid = mpiMyId
161         mpiPx = mpiGridSpec(1)         mpiPx = mpiGridSpec(1)
162         mpiPy = mpiGridSpec(2)         mpiPy = mpiGridSpec(2)
163         mpiXGlobalLo = 1 + sNx*nSx*(mpiPx)         mpiXGlobalLo = 1 + sNx*nSx*(mpiPx)
164         mpiYGlobalLo = 1 + sNy*nSy*(mpiPy)         mpiYGlobalLo = 1 + sNy*nSy*(mpiPy)
165         myXGlobalLo  = mpiXGlobalLo         myXGlobalLo  = mpiXGlobalLo
166         myYGlobalLo  = mpiYGlobalLo         myYGlobalLo  = mpiYGlobalLo
167           myPx = mpiPx+1
168           myPy = mpiPy+1
169  C--    Get MPI id for neighboring procs.  C--    Get MPI id for neighboring procs.
170         mpiGridSpec(1) = mpiPx-1         mpiGridSpec(1) = mpiPx-1
171         IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_ .AND. mpiGridSpec(1) .LT. 0 )         IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_
172         &   .AND. mpiGridSpec(1) .LT. 0 )
173       &  mpiGridSpec(1) = nPx-1       &  mpiGridSpec(1) = nPx-1
174         mpiGridSpec(2) = mpiPy         mpiGridSpec(2) = mpiPy
175         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidW , mpiRC )         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidW , mpiRC )
# Line 180  C--    Get MPI id for neighboring procs. Line 183  C--    Get MPI id for neighboring procs.
183         ENDIF         ENDIF
184         pidW = mpiPidW         pidW = mpiPidW
185         mpiGridSpec(1) = mpiPx+1         mpiGridSpec(1) = mpiPx+1
186         IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_ .AND. mpiGridSpec(1) .GT. nPx-1 )         IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_
187         &   .AND. mpiGridSpec(1) .GT. nPx-1 )
188       &  mpiGridSpec(1) = 0       &  mpiGridSpec(1) = 0
189         mpiGridSpec(2) = mpiPy         mpiGridSpec(2) = mpiPy
190         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidE , mpiRC )         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidE , mpiRC )
# Line 195  C--    Get MPI id for neighboring procs. Line 199  C--    Get MPI id for neighboring procs.
199         pidE = mpiPidE         pidE = mpiPidE
200         mpiGridSpec(1) = mpiPx         mpiGridSpec(1) = mpiPx
201         mpiGridSpec(2) = mpiPy-1         mpiGridSpec(2) = mpiPy-1
202         IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_ .AND. mpiGridSpec(2) .LT. 0 )         IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_
203         &   .AND. mpiGridSpec(2) .LT. 0 )
204       &  mpiGridSpec(2) = nPy - 1       &  mpiGridSpec(2) = nPy - 1
205         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidS , mpiRC )         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidS , mpiRC )
206         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
# Line 209  C--    Get MPI id for neighboring procs. Line 214  C--    Get MPI id for neighboring procs.
214         pidS = mpiPidS         pidS = mpiPidS
215         mpiGridSpec(1) = mpiPx         mpiGridSpec(1) = mpiPx
216         mpiGridSpec(2) = mpiPy+1         mpiGridSpec(2) = mpiPy+1
217         IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_ .AND. mpiGridSpec(2) .GT. nPy-1 )         IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_
218         &   .AND. mpiGridSpec(2) .GT. nPy-1 )
219       &  mpiGridSpec(2) = 0       &  mpiGridSpec(2) = 0
220         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidN , mpiRC )         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidN , mpiRC )
221         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
# Line 221  C--    Get MPI id for neighboring procs. Line 227  C--    Get MPI id for neighboring procs.
227          GOTO 999          GOTO 999
228         ENDIF         ENDIF
229         pidN = mpiPidN         pidN = mpiPidN
        mpiGridSpec(1) = mpiPx-1  
        IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_ .AND. mpiGridSpec(1) .LT. 0 )  
      &  mpiGridSpec(1) = nPx - 1  
        mpiGridSpec(2) = mpiPy-1  
        IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_ .AND. mpiGridSpec(2) .LT. 0 )  
      &  mpiGridSpec(2) = nPy - 1  
        CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidSW, mpiRC )  
        IF ( mpiRC .NE. MPI_SUCCESS ) THEN  
         eeBootError = .TRUE.  
         WRITE(msgBuffer,'(A,I)')  
      &        'S/R INI_PROCS: MPI_CART_RANK (pidSW) return code',  
      &        mpiRC  
         CALL PRINT_ERROR( msgBuffer , myThid)  
         GOTO 999  
        ENDIF  
        pidSW = mpiPidSW  
        mpiGridSpec(1) = mpiPx+1  
        IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_ .AND. mpiGridSpec(1) .GT. nPx-1 )  
      &  mpiGridSpec(1) = 0  
        mpiGridSpec(2) = mpiPy-1  
        IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_ .AND. mpiGridSpec(2) .LT. 0 )  
      &  mpiGridSpec(2) = nPy - 1  
        CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidSE, mpiRC )  
        IF ( mpiRC .NE. MPI_SUCCESS ) THEN  
         eeBootError = .TRUE.  
         WRITE(msgBuffer,'(A,I)')  
      &        'S/R INI_PROCS: MPI_CART_RANK (pidSE) return code',  
      &        mpiRC  
         CALL PRINT_ERROR( msgBuffer , myThid)  
         GOTO 999  
        ENDIF  
        pidSE = mpiPidSE  
        mpiGridSpec(1) = mpiPx-1  
        IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_ .AND. mpiGridSpec(1) .LT. 0     )  
      &  mpiGridSpec(1) = nPx-1  
        mpiGridSpec(2) = mpiPy+1  
        IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_ .AND. mpiGridSpec(2) .GT. nPy-1 )  
      &  mpiGridSpec(2) = 0  
        CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidNW, mpiRC )  
        IF ( mpiRC .NE. MPI_SUCCESS ) THEN  
         eeBootError = .TRUE.  
         WRITE(msgBuffer,'(A,I)')  
      &        'S/R INI_PROCS: MPI_CART_RANK (pidNW) return code',  
      &        mpiRC  
         CALL PRINT_ERROR( msgBuffer , myThid)  
         GOTO 999  
        ENDIF  
        pidNW = mpiPidNW  
        mpiGridSpec(1) = mpiPx+1  
        IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_ .AND. mpiGridSpec(1) .GT. nPx-1 )  
      &  mpiGridSpec(1) = 0  
        mpiGridSpec(2) = mpiPy+1  
        IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_ .AND. mpiGridSpec(2) .GT. nPy-1 )  
      &  mpiGridSpec(2) = 0  
        CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidNE, mpiRC )  
        IF ( mpiRC .NE. MPI_SUCCESS ) THEN  
         eeBootError = .TRUE.  
         WRITE(msgBuffer,'(A,I)')  
      &        'S/R INI_PROCS: MPI_CART_RANK (pidNE) return code',  
      &        mpiRC  
         CALL PRINT_ERROR( msgBuffer , myThid)  
         GOTO 999  
        ENDIF  
        pidNE = mpiPidNE  
230    
231  C--    Print summary of processor mapping on standard output  C--    Print summary of processor mapping on standard output
232         CALL MPI_GET_PROCESSOR_NAME( mpiProcNam, mpilProcNam, mpiRC )         CALL MPI_GET_PROCESSOR_NAME( mpiProcNam, mpilProcNam, mpiRC )
# Line 296  C--    Print summary of processor mappin Line 238  C--    Print summary of processor mappin
238          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
239          GOTO 999          GOTO 999
240         ENDIF         ENDIF
241         WRITE(msgBuffer,'(A)') '======= Starting MPI parallel Run ========='         WRITE(msgBuffer,'(A)')
242         &   '======= Starting MPI parallel Run ========='
243         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
244       &  SQUEEZE_BOTH , myThid)       &  SQUEEZE_BOTH , myThid)
245         WRITE(msgBuffer,'(A,A64)') ' My Processor Name = ',         WRITE(msgBuffer,'(A,A64)') ' My Processor Name = ',
# Line 313  C--    Print summary of processor mappin Line 256  C--    Print summary of processor mappin
256       &  ') on global grid (1:',nPx*sNx*nSx,',1:',nPy*sNy*nSy,')'       &  ') on global grid (1:',nPx*sNx*nSx,',1:',nPy*sNy*nSy,')'
257         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
258       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
259         WRITE(msgBuffer,'(A,I4.4)') ' North neighbor = processor ', mpiPidN         WRITE(msgBuffer,'(A,I4.4)')
260         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,       &   ' North neighbor = processor ', mpiPidN
      &  SQUEEZE_RIGHT , myThid)  
        WRITE(msgBuffer,'(A,I4.4)') ' South neighbor = processor ', mpiPidS  
261         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
262       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
263         WRITE(msgBuffer,'(A,I4.4)') '  East neighbor = processor ', mpiPidE         WRITE(msgBuffer,'(A,I4.4)')
264         &   ' South neighbor = processor ', mpiPidS
265         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
266       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
267         WRITE(msgBuffer,'(A,I4.4)') '  West neighbor = processor ', mpiPidW         WRITE(msgBuffer,'(A,I4.4)')
268         &   '  East neighbor = processor ', mpiPidE
269         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
270       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
271         WRITE(msgBuffer,'(A,I4.4)') '    NW neighbor = processor ', mpiPidNW         WRITE(msgBuffer,'(A,I4.4)')
272         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,       &   '  West neighbor = processor ', mpiPidW
      &  SQUEEZE_RIGHT , myThid)  
        WRITE(msgBuffer,'(A,I4.4)') '    NE neighbor = processor ', mpiPidNE  
        CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,  
      &  SQUEEZE_RIGHT , myThid)  
        WRITE(msgBuffer,'(A,I4.4)') '    SW neighbor = processor ', mpiPidSW  
        CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,  
      &  SQUEEZE_RIGHT , myThid)  
        WRITE(msgBuffer,'(A,I4.4)') '    SE neighbor = processor ', mpiPidSE  
273         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
274       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
275  C  C
# Line 361  C      xFace (y=constant) for XY arrays Line 296  C      xFace (y=constant) for XY arrays
296         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
297          eeBootError = .TRUE.          eeBootError = .TRUE.
298          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I)')
299       &        'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r4)',
300       &        mpiRC       &        mpiRC
301          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
302         ENDIF         ENDIF
# Line 369  C      xFace (y=constant) for XY arrays Line 304  C      xFace (y=constant) for XY arrays
304         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
305          eeBootError = .TRUE.          eeBootError = .TRUE.
306          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I)')
307       &        'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r4)',
308       &        mpiRC       &        mpiRC
309          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
310         ENDIF         ENDIF
# Line 380  C      xFace (y=constant) for XY arrays Line 315  C      xFace (y=constant) for XY arrays
315         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
316          eeBootError = .TRUE.          eeBootError = .TRUE.
317          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I)')
318       &        'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r8)',
319       &        mpiRC       &        mpiRC
320          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
321         ENDIF         ENDIF
# Line 388  C      xFace (y=constant) for XY arrays Line 323  C      xFace (y=constant) for XY arrays
323         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
324          eeBootError = .TRUE.          eeBootError = .TRUE.
325          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I)')
326       &        'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r8)',
327       &        mpiRC       &        mpiRC
328          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
329         ENDIF         ENDIF
# Line 405  C      xFace (y=constant) for XYZ arrays Line 340  C      xFace (y=constant) for XYZ arrays
340         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
341          eeBootError = .TRUE.          eeBootError = .TRUE.
342          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I)')
343       &        'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r4)',
344       &        mpiRC       &        mpiRC
345          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
346         ENDIF         ENDIF
# Line 413  C      xFace (y=constant) for XYZ arrays Line 348  C      xFace (y=constant) for XYZ arrays
348         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
349          eeBootError = .TRUE.          eeBootError = .TRUE.
350          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I)')
351       &        'S/R INI_PROCS: MPI_TYPE_COMMIT  (mpiTypeXFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT  (mpiTypeXFaceBlock_xyz_r4)',
352       &        mpiRC       &        mpiRC
353          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
354         ENDIF         ENDIF
# Line 427  C      xFace (y=constant) for XYZ arrays Line 362  C      xFace (y=constant) for XYZ arrays
362         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
363          eeBootError = .TRUE.          eeBootError = .TRUE.
364          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I)')
365       &        'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r8)',
366       &        mpiRC       &        mpiRC
367          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
368         ENDIF         ENDIF
# Line 435  C      xFace (y=constant) for XYZ arrays Line 370  C      xFace (y=constant) for XYZ arrays
370         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
371          eeBootError = .TRUE.          eeBootError = .TRUE.
372          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I)')
373       &        'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xyz_r8)',
374       &        mpiRC       &        mpiRC
375          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
376         ENDIF         ENDIF
# Line 449  C      yFace (x=constant) for XY arrays Line 384  C      yFace (x=constant) for XY arrays
384         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
385          eeBootError = .TRUE.          eeBootError = .TRUE.
386          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I)')
387       &        'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r4)',
388       &        mpiRC       &        mpiRC
389          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
390         ENDIF         ENDIF
# Line 457  C      yFace (x=constant) for XY arrays Line 392  C      yFace (x=constant) for XY arrays
392         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
393          eeBootError = .TRUE.          eeBootError = .TRUE.
394          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I)')
395       &        'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r4)',
396       &        mpiRC       &        mpiRC
397          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
398         ENDIF         ENDIF
# Line 467  C      yFace (x=constant) for XY arrays Line 402  C      yFace (x=constant) for XY arrays
402         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
403          eeBootError = .TRUE.          eeBootError = .TRUE.
404          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I)')
405       &        'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r8)',
406       &        mpiRC       &        mpiRC
407          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
408         ENDIF         ENDIF
# Line 475  C      yFace (x=constant) for XY arrays Line 410  C      yFace (x=constant) for XY arrays
410         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
411          eeBootError = .TRUE.          eeBootError = .TRUE.
412          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I)')
413       &        'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r8)',
414       &        mpiRC       &        mpiRC
415          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
416         ENDIF         ENDIF
# Line 491  C      yFace (x=constant) for XYZ arrays Line 426  C      yFace (x=constant) for XYZ arrays
426         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
427          eeBootError = .TRUE.          eeBootError = .TRUE.
428          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I)')
429       &        'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r4)',
430       &        mpiRC       &        mpiRC
431          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
432         ENDIF         ENDIF
# Line 499  C      yFace (x=constant) for XYZ arrays Line 434  C      yFace (x=constant) for XYZ arrays
434         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
435          eeBootError = .TRUE.          eeBootError = .TRUE.
436          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I)')
437       &        'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r4)',
438       &        mpiRC       &        mpiRC
439          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
440         ENDIF         ENDIF
# Line 512  C      yFace (x=constant) for XYZ arrays Line 447  C      yFace (x=constant) for XYZ arrays
447         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
448          eeBootError = .TRUE.          eeBootError = .TRUE.
449          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I)')
450       &        'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r8)',
451       &        mpiRC       &        mpiRC
452          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
453         ENDIF         ENDIF
# Line 520  C      yFace (x=constant) for XYZ arrays Line 455  C      yFace (x=constant) for XYZ arrays
455         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
456          eeBootError = .TRUE.          eeBootError = .TRUE.
457          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I)')
458       &        'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r8)',
459       &        mpiRC       &        mpiRC
460          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
461         ENDIF         ENDIF
# Line 530  C--    Assign MPI values used in generat Line 465  C--    Assign MPI values used in generat
465         mpiTagE    = 2         mpiTagE    = 2
466         mpiTagS    = 3         mpiTagS    = 3
467         mpiTagN    = 4         mpiTagN    = 4
        mpiTagSW   = 5  
        mpiTagSE   = 6  
        mpiTagNW   = 7  
        mpiTagNE   = 8  
468    
469  C  C
470         CALL MPI_Barrier(MPI_COMM_WORLD,mpiRC)         CALL MPI_Barrier(MPI_COMM_MODEL,mpiRC)
471    
472    
473  C  C
# Line 549  C Line 480  C
480    
481        RETURN        RETURN
482        END        END
483    
484    C $Id$

Legend:
Removed from v.1.5  
changed lines
  Added in v.1.9

  ViewVC Help
Powered by ViewVC 1.1.22