Back to home page

MITgcm

 
 

    


File indexing completed on 2018-03-02 18:36:10 UTC

view on githubraw file Latest commit add29e06 on 2018-01-31 20:35:05 UTC
0deb8b4619 Jean*0001 #include "PACKAGES_CONFIG.h"
048ce7bdb7 Chri*0002 #include "CPP_EEOPTIONS.h"
                0003 
4c563c2ee9 Chri*0004 CBOP
                0005 C     !ROUTINE: INI_COMMUNICATION_PATTERNS
                0006 
                0007 C     !INTERFACE:
048ce7bdb7 Chri*0008       SUBROUTINE INI_COMMUNICATION_PATTERNS( myThid )
4c563c2ee9 Chri*0009 C     !DESCRIPTION:
                0010 C     *==========================================================*
0deb8b4619 Jean*0011 C     | SUBROUTINE INI\_COMMUNICATION\_PATTERNS
                0012 C     | o Initialise between tile communication data structures.
4c563c2ee9 Chri*0013 C     *==========================================================*
0deb8b4619 Jean*0014 C     | This routine assigns identifiers to each tile and then
                0015 C     | defines a map of neighbors for each tile.
                0016 C     | For each neighbor a communication method is defined.
4c563c2ee9 Chri*0017 C     *==========================================================*
048ce7bdb7 Chri*0018 
4c563c2ee9 Chri*0019 C     !USES:
af17b772b4 Jean*0020       IMPLICIT NONE
048ce7bdb7 Chri*0021 C     === Global data ===
                0022 #include "SIZE.h"
                0023 #include "EEPARAMS.h"
                0024 #include "EESUPPORT.h"
                0025 #include "EXCH.h"
                0026 
4c563c2ee9 Chri*0027 C     !INPUT/OUTPUT PARAMETERS:
048ce7bdb7 Chri*0028 C     === Routine arguments ===
4c563c2ee9 Chri*0029 C     myThid :: Thread number we are dealing with in this call
048ce7bdb7 Chri*0030       INTEGER myThid
                0031 
4c563c2ee9 Chri*0032 C     !LOCAL VARIABLES:
048ce7bdb7 Chri*0033 C     === Local variables ===
4c563c2ee9 Chri*0034 C     pxW   :: Process X coord of process to west.
                0035 C     pxE   :: Process X coord of process to west.
                0036 C     pyN   :: Process Y coord of process to north.
                0037 C     pyS   :: Process Y coord of process to south.
                0038 C     procW :: Process Id of process to west.
                0039 C     procE :: Process Id of process to east.
                0040 C     procN :: Process Id of process to north.
                0041 C     procS :: Process Id of process to south.
                0042 C     totalTileCount :: Total number of tiles
0deb8b4619 Jean*0043 C     tagW0, tagE0, tagS0, tagN0, theTag :: Working variables for
4c563c2ee9 Chri*0044 C                                           calculating message tags.
                0045 C     biW, biE, bjN, bjS :: Tile x and y indices to west, east,
                0046 C                           south and north.
                0047 C     bi, bj   :: Tile loop counter
9333d0f1ff Patr*0048 C     picnt, pjcnt   :: Process loop counter
4c563c2ee9 Chri*0049 C     bi0, bj0 :: Base global index coordinate ( on CS there is no global
                0050 C                 coord).
048ce7bdb7 Chri*0051       INTEGER bi0(nPx)
                0052       INTEGER bj0(nPy)
e5bdfc29a0 Patr*0053       INTEGER bi, bj, picnt, pjcnt
048ce7bdb7 Chri*0054       INTEGER pxW, pxE, pyN, pyS
                0055       INTEGER procW, procE, procN, procS
                0056       INTEGER totalTileCount
                0057       INTEGER tagW0, tagE0, tagS0, tagN0, theTag
                0058       INTEGER biE, biW, bjN, bjS
                0059       INTEGER thePx, thePy, theBj, theBi
4c563c2ee9 Chri*0060 CEOP
048ce7bdb7 Chri*0061 
                0062 C--   Define a globally unique tile numbers for each tile.
                0063 C--   We aslo define the tile numbers for our east, west, south
                0064 C--   and north neighbor tiles here. As coded below this is done from
                0065 C--   a simple cartesian formula. To handle irregular tile distributions
0deb8b4619 Jean*0066 C--   the code below would be changed. For instance we could read
048ce7bdb7 Chri*0067 C--   the neighbor tile information from a file rather than deriving
                0068 C--   it in-line. This allows general tile distributions and connectivity
                0069 C--   both within a thread, between threads and between processors.
                0070 C     Notes --
                0071 C     1. The cartesian based formula coded below works as follows:
                0072 C       i. Each tile has one west neighbor, one east neighbor
                0073 C          one north neignbor and one south neighbor.
                0074 C      ii. For each of my neighbors store the following
                0075 C          - neighbor tile id
0deb8b4619 Jean*0076 C          - neighbor process id
048ce7bdb7 Chri*0077 C     2. The information that is stored is then used to determine
                0078 C        the between tile communication method. The method used
                0079 C        depends on whether the tile is part of the same process,
                0080 C        on the same machine etc...
                0081 C     3. To initialise a tile distribution with holes in it
                0082 C        i.e. tiles that are not computed on. Set tile number to
                0083 C        the value NULL_TILE. This must also be done for tileNoW,
                0084 C        tileNoE, tileNoS, tileNoN.
                0085 C     4. The default formula below assigns tile numbers sequentially
                0086 C        in X on the **global** grid. Within a process the tile numbers
0deb8b4619 Jean*0087 C        will not necessairily be sequential. This means that the tile
048ce7bdb7 Chri*0088 C        numbering label does not change when nTx, nTy, nPx or nPy change.
                0089 C        It will only change if the tile size changes or the global
                0090 C        grid changes.
                0091 C     bi0 and bj0 are the base global tile grid coordinate for the first
                0092 C     tile in this process.
9333d0f1ff Patr*0093       DO picnt = 1, nPx
                0094        bi0(picnt) = picnt
048ce7bdb7 Chri*0095       ENDDO
9333d0f1ff Patr*0096       DO pjcnt = 1, nPy
                0097        bj0(pjcnt) = pjcnt
048ce7bdb7 Chri*0098       ENDDO
                0099       DO bj=myByLo(myThid),myByHi(myThid)
                0100        DO bi=myBxLo(myThid),myBxHi(myThid)
                0101 C       o My tile identifier
d171732194 Alis*0102 Crg     tileNo(bi,bj) = (bj0(myPy)-1+bj-1)*nSx*nPx+bi0(myPx)+bi-1
048ce7bdb7 Chri*0103         thePx = myPx
                0104         thePy = myPy
                0105         theBj = bj
                0106         theBi = bi
                0107         tileNo(bi,bj) =
0deb8b4619 Jean*0108      &    ((thePy-1)*nSy+theBj-1)*nSx*nPx
048ce7bdb7 Chri*0109      &   + (thePx-1)*nSx
                0110      &   + theBi
                0111 C       o My west neighbor tile and process identifier
                0112         biW   = bi-1
                0113         pxW   = myPx
                0114         procW = myPid
                0115         IF ( biW .LT. 1 ) THEN
                0116          biW   = nSx
                0117          pxW   = myPx-1
                0118          procW = pidW
                0119          IF ( pxW .LT. 1 ) pxW   = nPx
                0120         ENDIF
d171732194 Alis*0121 Crg     tileNoW (bi,bj) = (bj0(myPy)-1+bj-1)*nSx*nPx+bi0(pxW)+biW-1
048ce7bdb7 Chri*0122         thePx = pxW
                0123         thePy = myPy
                0124         theBj = bj
                0125         theBi = biW
0deb8b4619 Jean*0126         tileNoW (bi,bj) =
048ce7bdb7 Chri*0127      &    ((thePy-1)*nSy+theBj-1)*nSx*nPx
                0128      &   + (thePx-1)*nSx
                0129      &   + theBi
0deb8b4619 Jean*0130 #ifdef ALLOW_NEST_CHILD
                0131 #ifndef ALLOW_USE_MPI
                0132         tileNoW (bi,bj) = NULL_TILE
                0133 #endif
                0134 #endif
048ce7bdb7 Chri*0135         tilePidW(bi,bj) = procW
                0136         tileBiW (bi,bj) = biW
0deb8b4619 Jean*0137         tileBjW (bi,bj) = bj
048ce7bdb7 Chri*0138 C       o My east neighbor tile and process identifier
                0139         biE   = bi+1
                0140         pxE   = myPx
                0141         procE = myPid
                0142         IF ( biE .GT. nSx ) THEN
                0143          biE = 1
                0144          pxE = myPx+1
                0145          procE = pidE
                0146          IF ( pxE .GT. nPx ) pxE   = 1
                0147         ENDIF
d171732194 Alis*0148 Crg     tileNoE(bi,bj)  = (bj0(myPy)-1+bj-1)*nSx*nPx+bi0(pxE)+biE-1
048ce7bdb7 Chri*0149         thePx = pxE
                0150         thePy = myPy
                0151         theBi = biE
                0152         theBj = bj
0deb8b4619 Jean*0153         tileNoE(bi,bj) =
048ce7bdb7 Chri*0154      &    ((thePy-1)*nSy+theBj-1)*nSx*nPx
                0155      &   + (thePx-1)*nSx
                0156      &   + theBi
0deb8b4619 Jean*0157 #ifdef ALLOW_NEST_CHILD
                0158 #ifndef ALLOW_USE_MPI
                0159         tileNoE (bi,bj) = NULL_TILE
                0160 #endif
                0161 #endif
048ce7bdb7 Chri*0162         tilePidE(bi,bj) = procE
                0163         tileBiE (bi,bj) = biE
0deb8b4619 Jean*0164         tileBjE (bi,bj) = bj
048ce7bdb7 Chri*0165 C       o My north neighbor tile and process identifier
                0166         bjN   = bj+1
                0167         pyN   = myPy
                0168         procN = myPid
                0169         IF ( bjN .GT. nSy ) THEN
                0170          bjN = 1
                0171          pyN = myPy+1
                0172          procN = pidN
                0173          IF ( pyN .GT. nPy ) pyN   = 1
                0174         ENDIF
d171732194 Alis*0175 Crg     tileNoN(bi,bj) = (bj0(pyN)-1+bjN-1)*nSx*nPx+bi0(myPx)+bi-1
048ce7bdb7 Chri*0176         thePx = myPx
0deb8b4619 Jean*0177         thePy = pyN
048ce7bdb7 Chri*0178         theBi = bi
                0179         theBj = bjN
                0180         tileNoN(bi,bj) =
                0181      &    ((thePy-1)*nSy+theBj-1)*nSx*nPx
                0182      &   + (thePx-1)*nSx
                0183      &   + theBi
                0184         tilePidN(bi,bj) = procN
                0185          tileBiN(bi,bj) = bi
                0186          tileBjN(bi,bj) = bjN
                0187 C       o My south neighbor tile and process identifier
                0188         bjS   = bj-1
                0189         pyS   = myPy
                0190         procS = myPid
                0191         IF ( bjS .LT. 1 ) THEN
                0192          bjS = nSy
                0193          pyS = pyS-1
                0194          procS = pidS
                0195          IF ( pyS .LT. 1 ) pyS = nPy
                0196         ENDIF
d171732194 Alis*0197 Crg     tileNoS(bi,bj) = (bj0(pyS+1)-1+bjS-1)*nSx*nPx+bi0(myPx+1)+bi-1
048ce7bdb7 Chri*0198         thePx = myPx
                0199         thePy = pyS
                0200         theBi = bi
                0201         theBj = bjS
0deb8b4619 Jean*0202         tileNoS(bi,bj) =
048ce7bdb7 Chri*0203      &    ((thePy-1)*nSy+theBj-1)*nSx*nPx
                0204      &   + (thePx-1)*nSx
                0205      &   + theBi
                0206         tilePidS(bi,bj) = procS
                0207          tileBiS(bi,bj) = bi
                0208          tileBjS(bi,bj) = bjS
                0209        ENDDO
                0210       ENDDO
                0211 
                0212 C--   Define the total count of tiles.
                0213       totalTileCount = nSx*nSy*nPx*nPy
                0214 
                0215 C--   Set tags for each tile face.
0deb8b4619 Jean*0216 C     Tags are used to distinguish exchanges from particular
048ce7bdb7 Chri*0217 C     faces of particular tiles.
                0218 C     Tag numbers are based on
                0219 C      i - The tile number
                0220 C     ii - The direction (N,S,W,E) of the message
                0221 C     We dont check for the NULL_TILE tile number here as it
                0222 C     should not actually be used.
                0223       TagW0=1
                0224       TagE0=2
                0225       TagN0=3
                0226       TagS0=4
                0227       DO bj=myByLo(myThid),myByHi(myThid)
                0228        DO bi=myBxLo(myThid),myBxHi(myThid)
                0229 C       Send tags
                0230 C       o Tag I use for messages I send to west
                0231         theTag = TagW0*totalTileCount+tileNo(bi,bj)-1
                0232         tileTagSendW(bi,bj) = theTag
                0233 C       o Tag I use for messages I send to east
                0234         theTag = TagE0*totalTileCount+tileNo(bi,bj)-1
                0235         tileTagSendE(bi,bj) = theTag
                0236 C       o Tag I use for messages I send to north
                0237         theTag = TagN0*totalTileCount+tileNo(bi,bj)-1
                0238         tileTagSendN(bi,bj) = theTag
                0239 C       o Tag I use for messages I send to south
                0240         theTag = TagS0*totalTileCount+tileNo(bi,bj)-1
                0241         tileTagSendS(bi,bj) = theTag
                0242 C       Receive tags
                0243 C       o Tag on messages I receive from my east
                0244         theTag = TagW0*totalTileCount+tileNoE(bi,bj)-1
                0245         tileTagRecvE(bi,bj) = theTag
                0246 C       o Tag on messages I receive from my west
                0247         theTag = TagE0*totalTileCount+tileNoW(bi,bj)-1
                0248         tileTagRecvW(bi,bj) = theTag
                0249 C       o Tag on messages I receive from my north
                0250         theTag = TagS0*totalTileCount+tileNoN(bi,bj)-1
                0251         tileTagRecvN(bi,bj) = theTag
                0252 C       o Tag on messages I receive from my north
                0253         theTag = TagN0*totalTileCount+tileNoS(bi,bj)-1
                0254         tileTagRecvS(bi,bj) = theTag
                0255        ENDDO
                0256       ENDDO
                0257 
af17b772b4 Jean*0258 C--   Set the form of excahnge to use between neighboring tiles.
0deb8b4619 Jean*0259 C     For now use either shared memory, messages or nothing. Further
af17b772b4 Jean*0260 C     rules can be added later to allow shm regions and ump regions etc...
0deb8b4619 Jean*0261 C     Notes -
                0262 C     1. We require symmetry here. If one face of a tile uses
                0263 C        communication method A then the matching face on its neighbor
048ce7bdb7 Chri*0264 C        tile must also use communication method A.
                0265       DO bj=myByLo(myThid),myByHi(myThid)
                0266        DO bi=myBxLo(myThid),myBxHi(myThid)
                0267 C      o West face communication
                0268        IF ( tileNoW(bi,bj) .EQ. NULL_TILE ) THEN
                0269         tileCommModeW(bi,bj) = COMM_NONE
                0270        ELSE
                0271         IF ( myPid .EQ. tilePidW(bi,bj) ) THEN
                0272          tileCommModeW(bi,bj) = COMM_PUT
                0273         ELSE
                0274          tileCommModeW(bi,bj) = COMM_MSG
                0275         ENDIF
                0276        ENDIF
                0277 C      o East face communication
                0278        IF ( tileNoE(bi,bj) .EQ. NULL_TILE ) THEN
                0279         tileCommModeE(bi,bj) = COMM_NONE
                0280        ELSE
                0281         IF ( myPid .EQ. tilePidE(bi,bj) ) THEN
                0282          tileCommModeE(bi,bj) = COMM_PUT
                0283         ELSE
                0284          tileCommModeE(bi,bj) = COMM_MSG
                0285         ENDIF
                0286        ENDIF
                0287 C      o South face communication
                0288        IF ( tileNoS(bi,bj) .EQ. NULL_TILE ) THEN
                0289         tileCommModeS(bi,bj) = COMM_NONE
                0290        ELSE
                0291         IF ( myPid .EQ. tilePidS(bi,bj) ) THEN
                0292          tileCommModeS(bi,bj) = COMM_PUT
                0293         ELSE
                0294          tileCommModeS(bi,bj) = COMM_MSG
                0295         ENDIF
                0296        ENDIF
                0297 C      o North face communication
                0298        IF ( tileNoN(bi,bj) .EQ. NULL_TILE ) THEN
                0299         tileCommModeN(bi,bj) = COMM_NONE
                0300        ELSE
                0301         IF ( myPid .EQ. tilePidN(bi,bj) ) THEN
                0302          tileCommModeN(bi,bj) = COMM_PUT
                0303         ELSE
                0304          tileCommModeN(bi,bj) = COMM_MSG
                0305         ENDIF
                0306        ENDIF
0deb8b4619 Jean*0307 
048ce7bdb7 Chri*0308        ENDDO
                0309       ENDDO
                0310 
                0311 C     Initialise outstanding exchange request counter
                0312       DO bj=myByLo(myThid),myByHi(myThid)
                0313        DO bi=myBxLo(myThid),myBxHi(myThid)
                0314         exchNReqsX(1,bi,bj) = 0
                0315         exchNReqsY(1,bi,bj) = 0
                0316        ENDDO
                0317       ENDDO
                0318 
                0319       RETURN
                0320       END