/[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.16 by adcroft, Mon May 12 16:32:27 2003 UTC revision 1.23 by jmc, Sat Nov 5 00:51:06 2005 UTC
# Line 11  C     !INTERFACE: Line 11  C     !INTERFACE:
11    
12  C     !DESCRIPTION:  C     !DESCRIPTION:
13  C     *==========================================================*  C     *==========================================================*
14  C     | SUBROUTINE INI_PROCS                                        C     | SUBROUTINE INI\_PROCS                                      
15  C     | o Initialise multiple concurrent processes environment.    C     | o Initialise multiple concurrent processes environment.  
16  C     *==========================================================*  C     *==========================================================*
17  C     | Under MPI this routine calls various MPI service routines  C     | Under MPI this routine calls various MPI service routines
# Line 60  C                         units. Line 60  C                         units.
60        INTEGER elCount        INTEGER elCount
61        INTEGER elLen        INTEGER elLen
62        INTEGER elStride        INTEGER elStride
   
 C--   Variables needed for mpi gather scatter routines.  
       COMMON /GlobalLo/ mpi_myXGlobalLo, mpi_myYGlobalLo  
       INTEGER mpi_myXGlobalLo(nPx*nPy)  
       INTEGER mpi_myYGlobalLo(nPx*nPy)  
63        INTEGER npe,itemp,ierr,istatus(MPI_STATUS_SIZE)        INTEGER npe,itemp,ierr,istatus(MPI_STATUS_SIZE)
64        INTEGER mpiBufSize,mpiRequest        INTEGER mpiBufSize,mpiRequest
   
65  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
66        INTEGER myThid        INTEGER myThid
67  CEOP  CEOP
# Line 86  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 188  C--   To speed-up mpi gather and scatter Line 182  C--   To speed-up mpi gather and scatter
182  C     and myYGlobalLo from each process are transferred to  C     and myYGlobalLo from each process are transferred to
183  C     a common block array.  This allows process 0 to know  C     a common block array.  This allows process 0 to know
184  C     the location of the domains controlled by each process.  C     the location of the domains controlled by each process.
185           mpiBufSize=1
186           mpiRequest=0
187         DO npe = 0, numberOfProcs-1         DO npe = 0, numberOfProcs-1
           mpiBufSize=1  
           mpiRequest=0  
188            CALL MPI_ISEND (myXGlobalLo, mpiBufSize, MPI_INTEGER,            CALL MPI_ISEND (myXGlobalLo, mpiBufSize, MPI_INTEGER,
189       &         npe, mpiMyId, MPI_COMM_MODEL, mpiRequest, ierr)       &         npe, mpiMyId, MPI_COMM_MODEL, mpiRequest, ierr)
190         ENDDO         ENDDO
191         DO npe = 0, numberOfProcs-1         DO npe = 0, numberOfProcs-1
           mpiBufSize=1  
192            CALL MPI_RECV (itemp, mpiBufSize, MPI_INTEGER,            CALL MPI_RECV (itemp, mpiBufSize, MPI_INTEGER,
193       &         npe, npe, MPI_COMM_MODEL, istatus, ierr)       &         npe, npe, MPI_COMM_MODEL, istatus, ierr)
194            mpi_myXGlobalLo(npe+1) = itemp            mpi_myXGlobalLo(npe+1) = itemp
195         ENDDO         ENDDO
196         DO npe = 0, numberOfProcs-1         DO npe = 0, numberOfProcs-1
           mpiBufSize=1  
           mpiRequest=0  
197            CALL MPI_ISEND (myYGlobalLo, mpiBufSize, MPI_INTEGER,            CALL MPI_ISEND (myYGlobalLo, mpiBufSize, MPI_INTEGER,
198       &         npe, mpiMyId, MPI_COMM_MODEL, mpiRequest, ierr)       &         npe, mpiMyId, MPI_COMM_MODEL, mpiRequest, ierr)
199         ENDDO         ENDDO
200         DO npe = 0, numberOfProcs-1         DO npe = 0, numberOfProcs-1
           mpiBufSize=1  
201            CALL MPI_RECV (itemp, mpiBufSize, MPI_INTEGER,            CALL MPI_RECV (itemp, mpiBufSize, MPI_INTEGER,
202       &         npe, npe, MPI_COMM_MODEL, istatus, ierr)       &         npe, npe, MPI_COMM_MODEL, istatus, ierr)
203            mpi_myYGlobalLo(npe+1) = itemp            mpi_myYGlobalLo(npe+1) = itemp
# Line 340  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  #ifdef TARGET_SGI  #if (defined (TARGET_SGI) || defined (TARGET_AIX) || defined(TARGET_LAM))
334         CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_REAL,         CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_REAL,
335       &                       mpiTypeXFaceBlock_xy_r4, mpiRC)       &                       mpiTypeXFaceBlock_xy_r4, mpiRC)
336  #else  #else
# Line 364  C      xFace (y=constant) for XY arrays Line 354  C      xFace (y=constant) for XY arrays
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  #ifdef TARGET_SGI  #if (defined (TARGET_SGI) || defined (TARGET_AIX) || defined(TARGET_LAM))
358         CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_DOUBLE_PRECISION,         CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_DOUBLE_PRECISION,
359       &                       mpiTypeXFaceBlock_xy_r8, mpiRC)       &                       mpiTypeXFaceBlock_xy_r8, mpiRC)
360  #else  #else
# Line 438  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  #ifdef TARGET_SGI  #if (defined (TARGET_SGI) || defined (TARGET_AIX) || defined(TARGET_LAM))
432         CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_REAL,         CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_REAL,
433       &                          mpiTypeYFaceBlock_xy_r4, mpiRC)       &                          mpiTypeYFaceBlock_xy_r4, mpiRC)
434  #else  #else
# Line 461  C      yFace (x=constant) for XY arrays Line 451  C      yFace (x=constant) for XY arrays
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  #ifdef TARGET_SGI  #if (defined (TARGET_SGI) || defined (TARGET_AIX) || defined(TARGET_LAM))
455         CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_DOUBLE_PRECISION,         CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_DOUBLE_PRECISION,
456       &                          mpiTypeYFaceBlock_xy_r8, mpiRC)       &                          mpiTypeYFaceBlock_xy_r8, mpiRC)
457  #else  #else

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

  ViewVC Help
Powered by ViewVC 1.1.22