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

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

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


Revision 1.12 - (show annotations) (download)
Sun Jun 28 01:00:23 2009 UTC (14 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62e, checkpoint62d, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61s, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.11: +50 -41 lines
add bj in exch2 arrays and S/R.

1 C $Header: /u/gcmpack/MITgcm/pkg/exch2/w2_eeboot.F,v 1.11 2009/05/12 19:40:32 jmc Exp $
2 C $Name: $
3
4 #include "CPP_EEOPTIONS.h"
5
6 CBOP
7 C !ROUTINE: W2_EEBOOT
8
9 C !INTERFACE:
10 SUBROUTINE W2_EEBOOT
11
12 C !DESCRIPTION:
13 C *==========================================================*
14 C | SUBROUTINE W2_EEBOOT
15 C | o Setup execution "environment" for WRAPPER2
16 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
21 C !USES:
22 IMPLICIT NONE
23
24 #include "SIZE.h"
25 #include "EEPARAMS.h"
26 #include "EESUPPORT.h"
27 #include "W2_EXCH2_SIZE.h"
28 #include "W2_EXCH2_TOPOLOGY.h"
29 #include "W2_EXCH2_PARAMS.h"
30 #include "W2_EXCH2_BUFFER.h"
31 CEOP
32
33 C !FUNCTIONS:
34 INTEGER ILNBLNK
35 EXTERNAL ILNBLNK
36
37 C == Local variables ==
38 INTEGER nt_perProc, thisProc
39 CHARACTER*(MAX_LEN_MBUF) msgBuf
40 CHARACTER*(MAX_LEN_FNAM) fName
41 c INTEGER W2_oUnit
42 INTEGER stdUnit, iLen
43 CHARACTER commFlag
44 INTEGER myTileId
45 INTEGER myThid, I, J, II
46 INTEGER np, jp, bi, bj
47 INTEGER iErr, tNx, tNy
48
49 C Set dummy myThid value (we are not multi-threaded here)
50 myThid = 1
51
52 C Initialise to zero EXCH2_TOPOLOGY common blocks
53 DO I = 1,W2_maxNbTiles
54 exch2_tNx(I) = 0
55 exch2_tNy(I) = 0
56 exch2_tBasex(I) = 0
57 exch2_tBasey(I) = 0
58 exch2_txGlobalo(I) = 0
59 exch2_tyGlobalo(I) = 0
60 exch2_isWedge(I) = 0
61 exch2_isNedge(I) = 0
62 exch2_isEedge(I) = 0
63 exch2_isSedge(I) = 0
64 exch2_tProc(I) = 0
65 exch2_myFace(I) = 0
66 exch2_mydNx(I) = 0
67 exch2_mydNy(I) = 0
68 exch2_nNeighbours(I) = 0
69 DO J = 1,W2_maxNeighbours
70 exch2_neighbourId(J,I) = 0
71 exch2_opposingSend(J,I) = 0
72 DO II = 1,4
73 exch2_pij(II,J,I) = 0
74 ENDDO
75 exch2_oi(J,I) = 0
76 exch2_oj(J,I) = 0
77 exch2_iLo(J,I) = 0
78 exch2_iHi(J,I) = 0
79 exch2_jLo(J,I) = 0
80 exch2_jHi(J,I) = 0
81 ENDDO
82 ENDDO
83 W2_oUnit = standardMessageUnit
84
85 C Set W2-EXCH2 parameters
86 CALL W2_READPARMS( myThid )
87
88 stdUnit = standardMessageUnit
89 WRITE(msgBuf,'(A)') '===== Start setting W2 TOPOLOGY:'
90 CALL PRINT_MESSAGE( msgBuf, stdUnit, SQUEEZE_RIGHT, myThid )
91
92 C Open message output-file (if needed)
93 IF ( W2_printMsg .LT. 0 ) THEN
94 WRITE(fName,'(A,I4.4,A)')
95 & 'w2_tile_topology.',myProcId,'.log'
96 iLen = ILNBLNK(fName)
97 CALL MDSFINDUNIT( W2_oUnit, myThid )
98 OPEN( W2_oUnit, file=fName(1:iLen),
99 & status='unknown', form='formatted')
100 WRITE(msgBuf,'(2A)') ' write to log-file: ', fName(1:iLen)
101 CALL PRINT_MESSAGE( msgBuf, stdUnit, SQUEEZE_RIGHT, myThid )
102 ENDIF
103
104 C Define topology for every tile
105 CALL W2_E2SETUP( myThid )
106
107 C Decide which tiles this process handles - do this inline for now, but
108 C should go in subroutine.
109 C Set which rank processes "own" which tiles. This should probably
110 C be queried as part of some hand-shaking but for now we use the
111 C functional relationship that was used above.
112 C Fill also W2_procTileList for Single-CPU-IO.
113
114 C Number of tiles I handle is nSx*nSy
115 nt_perProc = nSx*nSy
116 thisProc = 1
117 #ifdef ALLOW_USE_MPI
118 thisProc = 1+myPid
119 #endif
120 J = 0
121 DO I=1,nTiles
122 IF ( exch2_myFace(I) .NE. 0 ) THEN
123 np = 1 + J/nt_perProc
124 jp = MOD(J,nt_perProc)
125 bj = 1 + jp/nSx
126 bi = 1 + MOD(jp,nSx)
127 exch2_tProc(I) = np
128 W2_procTileList(bi,bj,np) = I
129 IF ( np.EQ.thisProc ) W2_myTileList(bi,bj) = I
130 J = J + 1
131 ENDIF
132 ENDDO
133 IF ( J .NE. nSx*nSy*nPx*nPy ) THEN
134 STOP
135 & 'ERROR W2_EEBOOT: number of active tiles is not nPx*nSx*nPy*nSy'
136 ENDIF
137
138 C-- Check tile sizes
139 iErr = 0
140 DO bj=1,nSy
141 DO bi=1,nSx
142 myTileId = W2_myTileList(bi,bj)
143 tNx = exch2_tNx(myTileId)
144 tNy = exch2_tNy(myTileId)
145 IF ( tNx .NE. sNx ) THEN
146 WRITE(msgBuf,'(3(A,I5))')
147 & 'ERROR: S/R W2_EEBOOT Topology for tile', myTileId,
148 & 'tNx=', tNx, ' is not equal to subgrid size sNx=', sNx
149 CALL PRINT_MESSAGE(msgBuf,
150 & errorMessageUnit, SQUEEZE_RIGHT, 1 )
151 iErr = iErr+1
152 ENDIF
153 IF ( tNy .NE. sNy ) THEN
154 WRITE(msgBuf,'(3(A,I5))')
155 & 'ERROR: S/R W2_EEBOOT Topology for tile', myTileId,
156 & 'tNy=', tNy, ' is not equal to subgrid size sNy=', sNy
157 CALL PRINT_MESSAGE(msgBuf,
158 & errorMessageUnit, SQUEEZE_RIGHT, 1 )
159 iErr = iErr+1
160 ENDIF
161 ENDDO
162 ENDDO
163 IF ( iErr .NE. 0 ) THEN
164 STOP 'ABNORMAL END: W2_EEBOOT'
165 ENDIF
166
167 C-- Print tiles connection for this process and set myCommonFlag :
168 WRITE(msgBuf,'(A)') '===== W2 TILE TOPOLOGY ====='
169 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_BOTH, myThid )
170 DO bj=1,nSy
171 DO bi=1,nSx
172 myTileId = W2_myTileList(bi,bj)
173 c WRITE(msgBuf,'(A,I4)') ' TILE: ', myTileId
174 WRITE(msgBuf,'(A,I5,A,I3)') ' TILE: ', myTileId,
175 & ' , Nb of Neighbours =', exch2_nNeighbours(myTileId)
176 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
177 DO J=1,exch2_nNeighbours(myTileId)
178 commFlag = 'M'
179 DO II=1,nSy
180 DO I=1,nSx
181 IF ( W2_myTileList(I,II).EQ.exch2_neighbourId(J,myTileId) )
182 & commFlag = 'P'
183 ENDDO
184 ENDDO
185 IF ( commFlag .EQ. 'M' ) THEN
186 WRITE(msgBuf,'(A,I3,A,I5,A,I3,2A,I5,A)')
187 & ' NEIGHBOUR',J,' = TILE', exch2_neighbourId(J,myTileId),
188 & ' (n=', exch2_opposingSend(J,myTileId), ') Comm = MSG',
189 & ' (PROC=',exch2_tProc(exch2_neighbourId(J,myTileId)),')'
190 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
191 ENDIF
192 IF ( commFlag .EQ. 'P' ) THEN
193 WRITE(msgBuf,'(A,I3,A,I5,A,I3,2A,I5,A)')
194 & ' NEIGHBOUR',J,' = TILE', exch2_neighbourId(J,myTileId),
195 & ' (n=', exch2_opposingSend(J,myTileId), ') Comm = PUT',
196 & ' (PROC=',exch2_tProc(exch2_neighbourId(J,myTileId)),')'
197 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
198 ENDIF
199 W2_myCommFlag(J,bi,bj) = commFlag
200 ENDDO
201 ENDDO
202 ENDDO
203
204 C Set filling value for face-corner halo regions
205 e2FillValue_RL = 0. _d 0
206 e2FillValue_RS = 0. _d 0
207 e2FillValue_R4 = 0.e0
208 e2FillValue_R8 = 0.d0
209 C- for testing only: put a large value (should not affects the results)
210 c e2FillValue_RL = 1. _d+20
211 c e2FillValue_RS = 1. _d+20
212 c e2FillValue_R4 = 1.e+20
213 c e2FillValue_R8 = 1.d+20
214
215 C Print out the topology communication schedule
216 IF ( W2_printMsg .NE. 0 ) THEN
217 CALL W2_PRINT_COMM_SEQUENCE( myThid )
218 ENDIF
219
220 C Close message output-file (if needed)
221 IF ( W2_oUnit.NE.standardMessageUnit ) THEN
222 WRITE(msgBuf,'(A)') '=== End TOPOLOGY report ==='
223 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_BOTH, myThid )
224 CLOSE( W2_oUnit )
225 ENDIF
226 WRITE(msgBuf,'(A)') '===== setting W2 TOPOLOGY: Done'
227 CALL PRINT_MESSAGE( msgBuf, stdUnit, SQUEEZE_RIGHT, myThid )
228 WRITE(msgBuf,'(A)') ' '
229 CALL PRINT_MESSAGE( msgBuf, stdUnit, SQUEEZE_RIGHT, myThid )
230
231 RETURN
232 END

  ViewVC Help
Powered by ViewVC 1.1.22