/[MITgcm]/MITgcm/pkg/exch2/w2_eeboot.F
ViewVC logotype

Annotation of /MITgcm/pkg/exch2/w2_eeboot.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.7 - (hide annotations) (download)
Sat Apr 11 05:34:02 2009 UTC (15 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61m
Changes since 1.6: +95 -97 lines
- handle incomplete list of tile (with blank tiles ignored)
- set directly "W2_mpi_myTileList" (without MPI calls).
Note: modifs are backward compatible (i.e., can still use previous Exch2
 topology files: W2_EXCH2_TOPOLOGY.h & w2_e2setup.F)

1 jmc 1.7 C $Header: /u/gcmpack/MITgcm/pkg/exch2/w2_eeboot.F,v 1.6 2005/07/24 01:24:56 jmc Exp $
2 afe 1.1 C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5    
6 jmc 1.7 CBOP
7 afe 1.1 C !ROUTINE: W2_EEBOOT
8    
9     C !INTERFACE:
10     SUBROUTINE W2_EEBOOT
11    
12     C !DESCRIPTION:
13     C *==========================================================*
14 jmc 1.7 C | SUBROUTINE W2_EEBOOT
15     C | o Setup execution "environment" for WRAPPER2
16 afe 1.1 C *==========================================================*
17     C | WRAPPER2 provides complex topology support. In this routine
18     C | we setup the base topology for the default halo operations.
19     C *==========================================================*
20 jmc 1.7
21     C !USES:
22     IMPLICIT NONE
23    
24 afe 1.1 #include "SIZE.h"
25     #include "EEPARAMS.h"
26     #include "EESUPPORT.h"
27     #include "W2_EXCH2_TOPOLOGY.h"
28     #include "W2_EXCH2_PARAMS.h"
29 jmc 1.7 CEOP
30 afe 1.1
31     C == Local variables ==
32 jmc 1.7 INTEGER nt_perProc, thisProc
33     CHARACTER*(MAX_LEN_MBUF) msgBuf
34 afe 1.1 CHARACTER commFlag
35     INTEGER myTileId
36 jmc 1.7 INTEGER myThid, I, J, II, np, jp
37 afe 1.1 INTEGER iErr, tNx, tNy
38     INTEGER pRank
39    
40 edhill 1.4 C Set dummy myThid value (we are not multi-threaded here)
41 afe 1.1 myThid = 1
42 jmc 1.7
43     C Initialise to zero EXCH2_TOPOLOGY common blocks
44     DO I = 1,NTILES
45     exch2_tNx(I) = 0
46     exch2_tNy(I) = 0
47     exch2_tBasex(I) = 0
48     exch2_tBasey(I) = 0
49     exch2_txGlobalo(I) = 0
50     exch2_tyGlobalo(I) = 0
51     exch2_isWedge(I) = 0
52     exch2_isNedge(I) = 0
53     exch2_isEedge(I) = 0
54     exch2_isSedge(I) = 0
55     exch2_tProc(I) = 0
56     exch2_myFace(I) = 0
57     exch2_mydNx(I) = 0
58     exch2_mydNy(I) = 0
59     exch2_nNeighbours(I) = 0
60     DO J = 1,MAX_NEIGHBOURS
61     exch2_neighbourId(J,I) = 0
62     exch2_opposingSend(J,I) = 0
63     DO II = 1,4
64     exch2_pij(II,J,I) = 0
65     ENDDO
66     exch2_oi(J,I) = 0
67     exch2_oj(J,I) = 0
68     exch2_iLo(J,I) = 0
69     exch2_iHi(J,I) = 0
70     exch2_jLo(J,I) = 0
71     exch2_jHi(J,I) = 0
72     ENDDO
73     ENDDO
74    
75     C Define topology for every tile
76 afe 1.1 CALL W2_E2SETUP
77    
78 dimitri 1.2 C Decide which tiles this process handles - do this inline for now, but
79 afe 1.1 C should go in subroutine.
80 jmc 1.7 C Set which rank processes "own" which tiles. This should probably
81     C be queried as part of some hand-shaking but for now we use the
82     C functional relationship that was used above.
83     C Fill also W2_mpi_myTileList for Single-CPU-IO.
84    
85     C Number of tiles I handle is nSx*nSy
86     nt_perProc = nSx*nSy
87     thisProc = 1
88 afe 1.1 #ifdef ALLOW_USE_MPI
89 jmc 1.7 thisProc = 1+myPid
90 afe 1.1 #endif
91 jmc 1.7 J = 0
92     DO I=1,NTILES
93     IF ( exch2_myFace(I) .NE. 0 ) THEN
94     np = 1 + J/nt_perProc
95     jp = 1 + MOD(J,nt_perProc)
96     exch2_tProc(I) = np
97     W2_mpi_myTileList(np,jp) = I
98     IF ( np.EQ.thisProc ) W2_myTileList(jp) = I
99     J = J + 1
100     ENDIF
101 afe 1.1 ENDDO
102 jmc 1.7 IF ( J .NE. nSx*nSy*nPx*nPy ) THEN
103     STOP
104     & 'ERROR W2_EEBOOT: number of active tiles is not nPx*nSx*nPy*nSy'
105     ENDIF
106    
107     C-- Check tile sizes
108 afe 1.1 iErr = 0
109     DO I=1,nSx
110     myTileId = W2_myTileList(I)
111 jmc 1.7 tNx = exch2_tNx(myTileId)
112     tNy = exch2_tNy(myTileId)
113     IF ( tNx .NE. sNx ) THEN
114     WRITE(msgBuf,'(3(A,I5))')
115     & 'ERROR: S/R W2_EEBOOT Topology for tile', myTileId,
116     & 'tNx=', tNx, ' is not equal to subgrid size sNx=', sNx
117     CALL PRINT_MESSAGE(msgBuf,
118 afe 1.1 & errorMessageUnit, SQUEEZE_RIGHT, 1 )
119     iErr = iErr+1
120     ENDIF
121 jmc 1.7 IF ( tNy .NE. sNy ) THEN
122     WRITE(msgBuf,'(3(A,I5))')
123     & 'ERROR: S/R W2_EEBOOT Topology for tile', myTileId,
124     & 'tNy=', tNy, ' is not equal to subgrid size sNy=', sNy
125     CALL PRINT_MESSAGE(msgBuf,
126 afe 1.1 & errorMessageUnit, SQUEEZE_RIGHT, 1 )
127     iErr = iErr+1
128     ENDIF
129     ENDDO
130     IF ( iErr .NE. 0 ) THEN
131     STOP 'ABNORMAL END: W2_EEBOOT'
132     ENDIF
133    
134 jmc 1.7 C-- Print tiles connection for this process and set myCommonFlag :
135     WRITE(msgBuf,'(A)') '===== W2 TILE TOPLOGY ====='
136     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
137 afe 1.1 & SQUEEZE_BOTH,myThid)
138     DO I=1,nSx
139     myTileId = W2_myTileList(I)
140 jmc 1.7 WRITE(msgBuf,'(A,I4)') ' TILE: ', myTileId
141     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
142 afe 1.1 & SQUEEZE_RIGHT,myThid)
143     DO J=1,exch2_nNeighbours(myTileId)
144     commFlag = 'M'
145     DO II=1,nSx
146     IF ( W2_myTileList(II) .EQ. exch2_neighbourId(J,myTileId) )
147     & commFlag = 'P'
148     ENDDO
149     IF ( commFlag .EQ. 'M' ) THEN
150 jmc 1.7 WRITE(msgBuf,'(A,I4,A,I4,A,A,I4,A)')
151     & ' NEIGHBOUR ',J,' = TILE ',
152 afe 1.1 & exch2_neighbourId(J,myTileId), ' Comm = MSG',
153     & ' ( PROC = ',exch2_tProc(exch2_neighbourId(J,myTileId)),')'
154 jmc 1.7 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
155 afe 1.1 & SQUEEZE_RIGHT,myThid)
156     ENDIF
157     IF ( commFlag .EQ. 'P' ) THEN
158 jmc 1.7 WRITE(msgBuf,'(A,I4,A,I4,A,A,I4,A)')
159     & ' NEIGHBOUR ',J,' = TILE ',
160 afe 1.1 & exch2_neighbourId(J,myTileId), ' Comm = PUT',
161     & ' ( PROC = ',exch2_tProc(exch2_neighbourId(J,myTileId)),')'
162 jmc 1.7 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
163 afe 1.1 & SQUEEZE_RIGHT,myThid)
164     ENDIF
165     W2_myCommFlag(J,I) = commFlag
166     ENDDO
167     ENDDO
168 dimitri 1.2
169 jmc 1.6 C Set filling value for face-corner halo regions
170     e2FillValue_RL = 0. _d 0
171     e2FillValue_RS = 0. _d 0
172     e2FillValue_R4 = 0.e0
173     e2FillValue_R8 = 0.d0
174     C- for testing only: put a large value (should not affects the results)
175     c e2FillValue_RL = 1. _d+20
176     c e2FillValue_RS = 1. _d+20
177     c e2FillValue_R4 = 1.e+20
178     c e2FillValue_R8 = 1.d+20
179    
180 afe 1.1 C Print out the topology communication schedule
181     CALL W2_PRINT_COMM_SEQUENCE
182 jmc 1.7
183 afe 1.1 RETURN
184     END

  ViewVC Help
Powered by ViewVC 1.1.22