/[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.6 by cnh, Tue Sep 29 18:50:56 1998 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's 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 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_ .AND. mpiGridSpec(1) .LT. 0 )
# Line 221  C--    Get MPI id for neighboring procs. Line 223  C--    Get MPI id for neighboring procs.
223          GOTO 999          GOTO 999
224         ENDIF         ENDIF
225         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  
226    
227  C--    Print summary of processor mapping on standard output  C--    Print summary of processor mapping on standard output
228         CALL MPI_GET_PROCESSOR_NAME( mpiProcNam, mpilProcNam, mpiRC )         CALL MPI_GET_PROCESSOR_NAME( mpiProcNam, mpilProcNam, mpiRC )
# Line 325  C--    Print summary of processor mappin Line 263  C--    Print summary of processor mappin
263         WRITE(msgBuffer,'(A,I4.4)') '  West neighbor = processor ', mpiPidW         WRITE(msgBuffer,'(A,I4.4)') '  West neighbor = processor ', mpiPidW
264         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
265       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
        WRITE(msgBuffer,'(A,I4.4)') '    NW neighbor = processor ', mpiPidNW  
        CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,  
      &  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  
        CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,  
      &  SQUEEZE_RIGHT , myThid)  
266  C  C
267  C--    Create MPI types for transfer of array edges.  C--    Create MPI types for transfer of array edges.
268  C--    Four and eight byte primitive (one block only) datatypes.  C--    Four and eight byte primitive (one block only) datatypes.
# Line 530  C--    Assign MPI values used in generat Line 456  C--    Assign MPI values used in generat
456         mpiTagE    = 2         mpiTagE    = 2
457         mpiTagS    = 3         mpiTagS    = 3
458         mpiTagN    = 4         mpiTagN    = 4
        mpiTagSW   = 5  
        mpiTagSE   = 6  
        mpiTagNW   = 7  
        mpiTagNE   = 8  
459    
460  C  C
461         CALL MPI_Barrier(MPI_COMM_WORLD,mpiRC)         CALL MPI_Barrier(MPI_COMM_WORLD,mpiRC)
# Line 549  C Line 471  C
471    
472        RETURN        RETURN
473        END        END
474    
475    C $Id$

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

  ViewVC Help
Powered by ViewVC 1.1.22