/[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.9 by adcroft, Mon May 3 21:37:55 1999 UTC revision 1.23 by jmc, Sat Nov 5 00:51:06 2005 UTC
# Line 1  Line 1 
1    C $Header$
2    C $Name$
3  #include "CPP_EEOPTIONS.h"  #include "CPP_EEOPTIONS.h"
4  CStartOfInterface  CBOP
5    
6    C     !ROUTINE: INI_PROCS
7    
8    C     !INTERFACE:
9        SUBROUTINE INI_PROCS        SUBROUTINE INI_PROCS
10  C     /==========================================================\        IMPLICIT NONE
 C     | SUBROUTINE INI_PROCS                                     |  
 C     | o Initialise multiple concurrent processes environment.  |  
 C     |==========================================================|  
 C     | Under MPI this routine calls various MPI service routines|  
 C     | that map the model grid to MPI processes. The information|  
 C     | is then stored in a common block for later use.          |  
 C     | Note: This routine can also be compiled with CPP         |  
 C     | directives set so that no multi-processing is initialise.|  
 C     | This is OK and should work fine.                         |  
 C     \==========================================================/  
11    
12    C     !DESCRIPTION:
13    C     *==========================================================*
14    C     | SUBROUTINE INI\_PROCS                                      
15    C     | o Initialise multiple concurrent processes environment.  
16    C     *==========================================================*
17    C     | Under MPI this routine calls various MPI service routines
18    C     | that map the model grid to MPI processes. The information
19    C     | is then stored in a common block for later use.          
20    C     | Note: This routine can also be compiled with CPP          
21    C     | directives set so that no multi-processing is initialise.
22    C     | This is OK and should work fine.                          
23    C     *==========================================================*
24    
25    C     !USES:
26  C     === Global data ===  C     === Global data ===
27  #include "SIZE.h"  #include "SIZE.h"
28  #include "EEPARAMS.h"  #include "EEPARAMS.h"
29  #include "EESUPPORT.h"  #include "EESUPPORT.h"
 CEndOfInterface  
30    
31    C     !LOCAL VARIABLES:
32  C     === Local variables ===  C     === Local variables ===
33  #ifdef ALLOW_USE_MPI  #ifdef ALLOW_USE_MPI
34  C     msgBuffer        - IO buffer  C     msgBuffer        :: IO buffer
35  C     myThid           - Dummy thread id  C     myThid           :: Dummy thread id
36  C     mpiRC            - Error code reporting variable used  C     mpiRC            :: Error code reporting variable used
37  C                        with MPI.  C                         with MPI.
38  C     mpiGridSpec      - No. of processes in X and Y.  C     mpiGridSpec      :: No. of processes in X and Y.
39  C     mpiPeriodicity   - Flag indicating XY priodicity to MPI.  C     mpiPeriodicity   :: Flag indicating XY priodicity to MPI.
40  C     arrElSize        - Size of an array element in bytes used  C     arrElSize        :: Size of an array element in bytes used
41  C                        to define MPI datatypes for communication  C                         to define MPI datatypes for communication
42  C                        operations.  C                         operations.
43  C     arrElSep         - Separation in units of array elements between  C     arrElSep         :: Separation in units of array elements between
44  C                        blocks to be communicated.  C                         blocks to be communicated.
45  C     elCount          - No. of blocks that are associated with MPI  C     elCount          :: No. of blocks that are associated with MPI
46  C                        datatype.  C                         datatype.
47  C     elLen            - Length of an MPI datatype in terms of preexisting  C     elLen            :: Length of an MPI datatype in terms of preexisting
48  C                        datatype.  C                         datatype.
49  C     elStride         - Distance between starting location of elements  C     elStride         :: Distance between starting location of elements
50  C                        in an MPI datatype - can be bytes of datatype  C                         in an MPI datatype - can be bytes of datatype
51  C                        units.  C                         units.
52        CHARACTER*(MAX_LEN_MBUF) msgBuffer        CHARACTER*(MAX_LEN_MBUF) msgBuffer
53        INTEGER mpiRC        INTEGER mpiRC
54        INTEGER mpiGridSpec(2)        INTEGER mpiGridSpec(2)
# Line 50  C                        units. Line 60  C                        units.
60        INTEGER elCount        INTEGER elCount
61        INTEGER elLen        INTEGER elLen
62        INTEGER elStride        INTEGER elStride
63          INTEGER npe,itemp,ierr,istatus(MPI_STATUS_SIZE)
64          INTEGER mpiBufSize,mpiRequest
65  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
66        INTEGER myThid        INTEGER myThid
67    CEOP
68    
69  C--   Default values set to single processor case  C--   Default values set to single processor case
70  C     pid[W-SE] are the MPI process id of the neighbor  C     pid[W-SE] are the MPI process id of the neighbor
# Line 67  C     processes. A process can be its ow Line 80  C     processes. A process can be its ow
80        pidE        = 1        pidE        = 1
81        pidN        = 1        pidN        = 1
82        pidS        = 1        pidS        = 1
83        errorMessageUnit    = 0  c     errorMessageUnit    = 0
84        standardMessageUnit = 6  c     standardMessageUnit = 6
85    
86  #ifdef ALLOW_USE_MPI  #ifdef ALLOW_USE_MPI
87  C--  C--
# Line 140  C      Could be periodic in X and/or Y - Line 153  C      Could be periodic in X and/or Y -
153       O  mpiComm, mpiRC )       O  mpiComm, mpiRC )
154         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
155          eeBootError = .TRUE.          eeBootError = .TRUE.
156          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
157       &        'S/R INI_PROCS: MPI_CART_CREATE return code',       &        'S/R INI_PROCS: MPI_CART_CREATE return code',
158       &        mpiRC       &        mpiRC
159          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 151  C--    Get my location on the grid Line 164  C--    Get my location on the grid
164         CALL MPI_CART_COORDS( mpiComm, mpiMyId, 2, mpiGridSpec, mpiRC )         CALL MPI_CART_COORDS( mpiComm, mpiMyId, 2, mpiGridSpec, mpiRC )
165         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
166          eeBootError = .TRUE.          eeBootError = .TRUE.
167          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
168       &        'S/R INI_PROCS: MPI_CART_COORDS return code',       &        'S/R INI_PROCS: MPI_CART_COORDS return code',
169       &        mpiRC       &        mpiRC
170          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 164  C--    Get my location on the grid Line 177  C--    Get my location on the grid
177         mpiYGlobalLo = 1 + sNy*nSy*(mpiPy)         mpiYGlobalLo = 1 + sNy*nSy*(mpiPy)
178         myXGlobalLo  = mpiXGlobalLo         myXGlobalLo  = mpiXGlobalLo
179         myYGlobalLo  = mpiYGlobalLo         myYGlobalLo  = mpiYGlobalLo
180    
181    C--   To speed-up mpi gather and scatter routines, myXGlobalLo
182    C     and myYGlobalLo from each process are transferred to
183    C     a common block array.  This allows process 0 to know
184    C     the location of the domains controlled by each process.
185           mpiBufSize=1
186           mpiRequest=0
187           DO npe = 0, numberOfProcs-1
188              CALL MPI_ISEND (myXGlobalLo, mpiBufSize, MPI_INTEGER,
189         &         npe, mpiMyId, MPI_COMM_MODEL, mpiRequest, ierr)
190           ENDDO
191           DO npe = 0, numberOfProcs-1
192              CALL MPI_RECV (itemp, mpiBufSize, MPI_INTEGER,
193         &         npe, npe, MPI_COMM_MODEL, istatus, ierr)
194              mpi_myXGlobalLo(npe+1) = itemp
195           ENDDO
196           DO npe = 0, numberOfProcs-1
197              CALL MPI_ISEND (myYGlobalLo, mpiBufSize, MPI_INTEGER,
198         &         npe, mpiMyId, MPI_COMM_MODEL, mpiRequest, ierr)
199           ENDDO
200           DO npe = 0, numberOfProcs-1
201              CALL MPI_RECV (itemp, mpiBufSize, MPI_INTEGER,
202         &         npe, npe, MPI_COMM_MODEL, istatus, ierr)
203              mpi_myYGlobalLo(npe+1) = itemp
204           ENDDO
205    
206         myPx = mpiPx+1         myPx = mpiPx+1
207         myPy = mpiPy+1         myPy = mpiPy+1
208  C--    Get MPI id for neighboring procs.  C--    Get MPI id for neighboring procs.
# Line 175  C--    Get MPI id for neighboring procs. Line 214  C--    Get MPI id for neighboring procs.
214         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidW , mpiRC )         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidW , mpiRC )
215         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
216          eeBootError = .TRUE.          eeBootError = .TRUE.
217          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
218       &        'S/R INI_PROCS: MPI_CART_RANK (pidW) return code',       &        'S/R INI_PROCS: MPI_CART_RANK (pidW) return code',
219       &        mpiRC       &        mpiRC
220          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 190  C--    Get MPI id for neighboring procs. Line 229  C--    Get MPI id for neighboring procs.
229         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidE , mpiRC )         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidE , mpiRC )
230         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
231          eeBootError = .TRUE.          eeBootError = .TRUE.
232          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
233       &        'S/R INI_PROCS: MPI_CART_RANK (pidE) return code',       &        'S/R INI_PROCS: MPI_CART_RANK (pidE) return code',
234       &        mpiRC       &        mpiRC
235          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 205  C--    Get MPI id for neighboring procs. Line 244  C--    Get MPI id for neighboring procs.
244         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidS , mpiRC )         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidS , mpiRC )
245         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
246          eeBootError = .TRUE.          eeBootError = .TRUE.
247          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
248       &        'S/R INI_PROCS: MPI_CART_RANK (pidS) return code',       &        'S/R INI_PROCS: MPI_CART_RANK (pidS) return code',
249       &        mpiRC       &        mpiRC
250          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 220  C--    Get MPI id for neighboring procs. Line 259  C--    Get MPI id for neighboring procs.
259         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidN , mpiRC )         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidN , mpiRC )
260         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
261          eeBootError = .TRUE.          eeBootError = .TRUE.
262          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
263       &        'S/R INI_PROCS: MPI_CART_RANK (pidN) return code',       &        'S/R INI_PROCS: MPI_CART_RANK (pidN) return code',
264       &        mpiRC       &        mpiRC
265          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 232  C--    Print summary of processor mappin Line 271  C--    Print summary of processor mappin
271         CALL MPI_GET_PROCESSOR_NAME( mpiProcNam, mpilProcNam, mpiRC )         CALL MPI_GET_PROCESSOR_NAME( mpiProcNam, mpilProcNam, mpiRC )
272         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
273          eeBootError = .TRUE.          eeBootError = .TRUE.
274          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
275       &        'S/R INI_PROCS: MPI_GET_PROCESSOR_NAME return code',       &        'S/R INI_PROCS: MPI_GET_PROCESSOR_NAME return code',
276       &        mpiRC       &        mpiRC
277          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 291  C      xFace (y=constant) for XY arrays Line 330  C      xFace (y=constant) for XY arrays
330         elCount   = sNy+OLy*2         elCount   = sNy+OLy*2
331         elLen     = OLx         elLen     = OLx
332         elStride  = arrElSep         elStride  = arrElSep
333    #if (defined (TARGET_SGI) || defined (TARGET_AIX) || defined(TARGET_LAM))
334           CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_REAL,
335         &                       mpiTypeXFaceBlock_xy_r4, mpiRC)
336    #else
337         CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_REAL4,         CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_REAL4,
338       &                       mpiTypeXFaceBlock_xy_r4, mpiRC)       &                       mpiTypeXFaceBlock_xy_r4, mpiRC)
339    #endif
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,I5)')
343       &   'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r4)',
344       &        mpiRC       &        mpiRC
345          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 303  C      xFace (y=constant) for XY arrays Line 347  C      xFace (y=constant) for XY arrays
347         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r4, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r4, mpiRC)
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,I5)')
351       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r4)',
352       &        mpiRC       &        mpiRC
353          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
354         ENDIF         ENDIF
355    
356  C      xFace (y=constant) for XY arrays with real*8 declaration.  C      xFace (y=constant) for XY arrays with real*8 declaration.
357    #if (defined (TARGET_SGI) || defined (TARGET_AIX) || defined(TARGET_LAM))
358           CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_DOUBLE_PRECISION,
359         &                       mpiTypeXFaceBlock_xy_r8, mpiRC)
360    #else
361         CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_REAL8,         CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_REAL8,
362       &                       mpiTypeXFaceBlock_xy_r8, mpiRC)       &                       mpiTypeXFaceBlock_xy_r8, mpiRC)
363    #endif
364         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
365          eeBootError = .TRUE.          eeBootError = .TRUE.
366          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
367       &   'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r8)',
368       &        mpiRC       &        mpiRC
369          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 322  C      xFace (y=constant) for XY arrays Line 371  C      xFace (y=constant) for XY arrays
371         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r8, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r8, mpiRC)
372         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
373          eeBootError = .TRUE.          eeBootError = .TRUE.
374          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
375       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r8)',
376       &        mpiRC       &        mpiRC
377          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 339  C      xFace (y=constant) for XYZ arrays Line 388  C      xFace (y=constant) for XYZ arrays
388       &                       mpiTypeXFaceBlock_xyz_r4, mpiRC)       &                       mpiTypeXFaceBlock_xyz_r4, mpiRC)
389         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
390          eeBootError = .TRUE.          eeBootError = .TRUE.
391          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
392       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r4)',
393       &        mpiRC       &        mpiRC
394          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 347  C      xFace (y=constant) for XYZ arrays Line 396  C      xFace (y=constant) for XYZ arrays
396         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r4, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r4, mpiRC)
397         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
398          eeBootError = .TRUE.          eeBootError = .TRUE.
399          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
400       &   'S/R INI_PROCS: MPI_TYPE_COMMIT  (mpiTypeXFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT  (mpiTypeXFaceBlock_xyz_r4)',
401       &        mpiRC       &        mpiRC
402          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 361  C      xFace (y=constant) for XYZ arrays Line 410  C      xFace (y=constant) for XYZ arrays
410       &                       mpiTypeXFaceBlock_xyz_r8, mpiRC)       &                       mpiTypeXFaceBlock_xyz_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_HVECTOR (mpiTypeXFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r8)',
415       &        mpiRC       &        mpiRC
416          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 369  C      xFace (y=constant) for XYZ arrays Line 418  C      xFace (y=constant) for XYZ arrays
418         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r8, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r8, mpiRC)
419         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
420          eeBootError = .TRUE.          eeBootError = .TRUE.
421          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
422       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xyz_r8)',
423       &        mpiRC       &        mpiRC
424          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 379  C--    yFace datatypes (north<-->south m Line 428  C--    yFace datatypes (north<-->south m
428  C--  C--
429  C      yFace (x=constant) for XY arrays with real*4 declaration  C      yFace (x=constant) for XY arrays with real*4 declaration
430         elCount  = OLy*(sNx+OLx*2)         elCount  = OLy*(sNx+OLx*2)
431    #if (defined (TARGET_SGI) || defined (TARGET_AIX) || defined(TARGET_LAM))
432           CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_REAL,
433         &                          mpiTypeYFaceBlock_xy_r4, mpiRC)
434    #else
435         CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_REAL4,         CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_REAL4,
436       &                          mpiTypeYFaceBlock_xy_r4, mpiRC)       &                          mpiTypeYFaceBlock_xy_r4, mpiRC)
437    #endif
438         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
439          eeBootError = .TRUE.          eeBootError = .TRUE.
440          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
441       &   'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r4)',
442       &        mpiRC       &        mpiRC
443          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 391  C      yFace (x=constant) for XY arrays Line 445  C      yFace (x=constant) for XY arrays
445         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r4, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r4, mpiRC)
446         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
447          eeBootError = .TRUE.          eeBootError = .TRUE.
448          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
449       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r4)',
450       &        mpiRC       &        mpiRC
451          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
452         ENDIF         ENDIF
453  C      yFace (x=constant) for XY arrays with real*8 declaration  C      yFace (x=constant) for XY arrays with real*8 declaration
454    #if (defined (TARGET_SGI) || defined (TARGET_AIX) || defined(TARGET_LAM))
455           CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_DOUBLE_PRECISION,
456         &                          mpiTypeYFaceBlock_xy_r8, mpiRC)
457    #else
458         CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_REAL8,         CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_REAL8,
459       &                          mpiTypeYFaceBlock_xy_r8, mpiRC)       &                          mpiTypeYFaceBlock_xy_r8, mpiRC)
460    #endif
461         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
462          eeBootError = .TRUE.          eeBootError = .TRUE.
463          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
464       &   'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r8)',
465       &        mpiRC       &        mpiRC
466          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 409  C      yFace (x=constant) for XY arrays Line 468  C      yFace (x=constant) for XY arrays
468         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r8, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r8, mpiRC)
469         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
470          eeBootError = .TRUE.          eeBootError = .TRUE.
471          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
472       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r8)',
473       &        mpiRC       &        mpiRC
474          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 425  C      yFace (x=constant) for XYZ arrays Line 484  C      yFace (x=constant) for XYZ arrays
484       &                       mpiTypeYFaceBlock_xyz_r4, mpiRC)       &                       mpiTypeYFaceBlock_xyz_r4, mpiRC)
485         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
486          eeBootError = .TRUE.          eeBootError = .TRUE.
487          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
488       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r4)',
489       &        mpiRC       &        mpiRC
490          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 433  C      yFace (x=constant) for XYZ arrays Line 492  C      yFace (x=constant) for XYZ arrays
492         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r4, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r4, mpiRC)
493         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
494          eeBootError = .TRUE.          eeBootError = .TRUE.
495          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
496       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r4)',
497       &        mpiRC       &        mpiRC
498          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 446  C      yFace (x=constant) for XYZ arrays Line 505  C      yFace (x=constant) for XYZ arrays
505       &                       mpiTypeYFaceBlock_xyz_r8, mpiRC)       &                       mpiTypeYFaceBlock_xyz_r8, mpiRC)
506         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
507          eeBootError = .TRUE.          eeBootError = .TRUE.
508          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
509       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r8)',
510       &        mpiRC       &        mpiRC
511          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
# Line 454  C      yFace (x=constant) for XYZ arrays Line 513  C      yFace (x=constant) for XYZ arrays
513         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r8, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r8, mpiRC)
514         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
515          eeBootError = .TRUE.          eeBootError = .TRUE.
516          WRITE(msgBuffer,'(A,I)')          WRITE(msgBuffer,'(A,I5)')
517       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r8)',
518       &        mpiRC       &        mpiRC
519          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)

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

  ViewVC Help
Powered by ViewVC 1.1.22