/[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.13 - (hide annotations) (download)
Fri Apr 16 18:14:24 2010 UTC (14 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62g, checkpoint62f, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.12: +24 -14 lines
change tile to processor setting (in case nSy*nPy > 1):
 allows default model mapping (myX and myYGlobalLow) to be used for simple
 (1 facet, no blank tile) config.

1 jmc 1.13 C $Header: /u/gcmpack/MITgcm/pkg/exch2/w2_eeboot.F,v 1.12 2009/06/28 01:00:23 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 jmc 1.11 #include "W2_EXCH2_SIZE.h"
28 afe 1.1 #include "W2_EXCH2_TOPOLOGY.h"
29     #include "W2_EXCH2_PARAMS.h"
30 jmc 1.11 #include "W2_EXCH2_BUFFER.h"
31 jmc 1.7 CEOP
32 afe 1.1
33 jmc 1.8 C !FUNCTIONS:
34     INTEGER ILNBLNK
35     EXTERNAL ILNBLNK
36    
37 afe 1.1 C == Local variables ==
38 jmc 1.13 INTEGER thisProc
39 jmc 1.7 CHARACTER*(MAX_LEN_MBUF) msgBuf
40 jmc 1.8 CHARACTER*(MAX_LEN_FNAM) fName
41 jmc 1.11 c INTEGER W2_oUnit
42 jmc 1.10 INTEGER stdUnit, iLen
43 afe 1.1 CHARACTER commFlag
44     INTEGER myTileId
45 jmc 1.13 INTEGER myThid, I, J
46     INTEGER np, ii, jj, bi, bj
47 afe 1.1 INTEGER iErr, tNx, tNy
48    
49 edhill 1.4 C Set dummy myThid value (we are not multi-threaded here)
50 afe 1.1 myThid = 1
51 jmc 1.7
52     C Initialise to zero EXCH2_TOPOLOGY common blocks
53 jmc 1.11 DO I = 1,W2_maxNbTiles
54 jmc 1.7 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 jmc 1.11 DO J = 1,W2_maxNeighbours
70 jmc 1.7 exch2_neighbourId(J,I) = 0
71     exch2_opposingSend(J,I) = 0
72 jmc 1.13 DO ii = 1,4
73     exch2_pij(ii,J,I) = 0
74 jmc 1.7 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 jmc 1.8 W2_oUnit = standardMessageUnit
84    
85     C Set W2-EXCH2 parameters
86 jmc 1.11 CALL W2_READPARMS( myThid )
87 jmc 1.8
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 jmc 1.11 IF ( W2_printMsg .LT. 0 ) THEN
94 jmc 1.8 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 jmc 1.9 WRITE(msgBuf,'(2A)') ' write to log-file: ', fName(1:iLen)
101 jmc 1.8 CALL PRINT_MESSAGE( msgBuf, stdUnit, SQUEEZE_RIGHT, myThid )
102     ENDIF
103 jmc 1.7
104     C Define topology for every tile
105 jmc 1.11 CALL W2_E2SETUP( myThid )
106 afe 1.1
107 dimitri 1.2 C Decide which tiles this process handles - do this inline for now, but
108 afe 1.1 C should go in subroutine.
109 jmc 1.7 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 jmc 1.11 C Fill also W2_procTileList for Single-CPU-IO.
113 jmc 1.7
114     C Number of tiles I handle is nSx*nSy
115     thisProc = 1
116 afe 1.1 #ifdef ALLOW_USE_MPI
117 jmc 1.7 thisProc = 1+myPid
118 afe 1.1 #endif
119 jmc 1.7 J = 0
120 jmc 1.11 DO I=1,nTiles
121 jmc 1.7 IF ( exch2_myFace(I) .NE. 0 ) THEN
122 jmc 1.13 C-- old ordering (makes no difference if nSy*nPy=1 )
123     c np = 1 + J/(nSx*nSy)
124     c jj = MOD(J,nSx*nSy)
125     c bj = 1 + jj/nSx
126     c bi = 1 + MOD(jj,nSx)
127     C-- new ordering: for single sub-domain (nFacets=1) case, match default setting
128     jj = J/(nSx*nPx)
129     ii = MOD(J,nSx*nPx)
130     C-- natural way to order processors:
131     c np = 1 + ii/nSx + (jj/nSy)*nPx
132     C-- switch processor order to match MPI_CART set-up
133     np = 1 + jj/nSy + (ii/nSx)*nPy
134     bj = 1 + MOD(jj,nSy)
135     bi = 1 + MOD(ii,nSx)
136     C--
137 jmc 1.7 exch2_tProc(I) = np
138 jmc 1.12 W2_procTileList(bi,bj,np) = I
139     IF ( np.EQ.thisProc ) W2_myTileList(bi,bj) = I
140 jmc 1.7 J = J + 1
141     ENDIF
142 afe 1.1 ENDDO
143 jmc 1.7 IF ( J .NE. nSx*nSy*nPx*nPy ) THEN
144     STOP
145     & 'ERROR W2_EEBOOT: number of active tiles is not nPx*nSx*nPy*nSy'
146     ENDIF
147    
148     C-- Check tile sizes
149 afe 1.1 iErr = 0
150 jmc 1.12 DO bj=1,nSy
151     DO bi=1,nSx
152     myTileId = W2_myTileList(bi,bj)
153     tNx = exch2_tNx(myTileId)
154     tNy = exch2_tNy(myTileId)
155     IF ( tNx .NE. sNx ) THEN
156     WRITE(msgBuf,'(3(A,I5))')
157 jmc 1.7 & 'ERROR: S/R W2_EEBOOT Topology for tile', myTileId,
158     & 'tNx=', tNx, ' is not equal to subgrid size sNx=', sNx
159     CALL PRINT_MESSAGE(msgBuf,
160 afe 1.1 & errorMessageUnit, SQUEEZE_RIGHT, 1 )
161     iErr = iErr+1
162 jmc 1.12 ENDIF
163     IF ( tNy .NE. sNy ) THEN
164     WRITE(msgBuf,'(3(A,I5))')
165 jmc 1.7 & 'ERROR: S/R W2_EEBOOT Topology for tile', myTileId,
166     & 'tNy=', tNy, ' is not equal to subgrid size sNy=', sNy
167     CALL PRINT_MESSAGE(msgBuf,
168 afe 1.1 & errorMessageUnit, SQUEEZE_RIGHT, 1 )
169     iErr = iErr+1
170 jmc 1.12 ENDIF
171     ENDDO
172 afe 1.1 ENDDO
173     IF ( iErr .NE. 0 ) THEN
174     STOP 'ABNORMAL END: W2_EEBOOT'
175     ENDIF
176    
177 jmc 1.7 C-- Print tiles connection for this process and set myCommonFlag :
178 jmc 1.8 WRITE(msgBuf,'(A)') '===== W2 TILE TOPOLOGY ====='
179     CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_BOTH, myThid )
180 jmc 1.12 DO bj=1,nSy
181     DO bi=1,nSx
182     myTileId = W2_myTileList(bi,bj)
183     c WRITE(msgBuf,'(A,I4)') ' TILE: ', myTileId
184     WRITE(msgBuf,'(A,I5,A,I3)') ' TILE: ', myTileId,
185     & ' , Nb of Neighbours =', exch2_nNeighbours(myTileId)
186     CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
187     DO J=1,exch2_nNeighbours(myTileId)
188     commFlag = 'M'
189 jmc 1.13 DO jj=1,nSy
190     DO ii=1,nSx
191     IF ( W2_myTileList(ii,jj).EQ.exch2_neighbourId(J,myTileId) )
192 jmc 1.12 & commFlag = 'P'
193     ENDDO
194     ENDDO
195     IF ( commFlag .EQ. 'M' ) THEN
196     WRITE(msgBuf,'(A,I3,A,I5,A,I3,2A,I5,A)')
197     & ' NEIGHBOUR',J,' = TILE', exch2_neighbourId(J,myTileId),
198     & ' (n=', exch2_opposingSend(J,myTileId), ') Comm = MSG',
199     & ' (PROC=',exch2_tProc(exch2_neighbourId(J,myTileId)),')'
200     CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
201     ENDIF
202     IF ( commFlag .EQ. 'P' ) THEN
203     WRITE(msgBuf,'(A,I3,A,I5,A,I3,2A,I5,A)')
204     & ' NEIGHBOUR',J,' = TILE', exch2_neighbourId(J,myTileId),
205     & ' (n=', exch2_opposingSend(J,myTileId), ') Comm = PUT',
206     & ' (PROC=',exch2_tProc(exch2_neighbourId(J,myTileId)),')'
207     CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
208     ENDIF
209     W2_myCommFlag(J,bi,bj) = commFlag
210 afe 1.1 ENDDO
211     ENDDO
212     ENDDO
213 dimitri 1.2
214 jmc 1.6 C Set filling value for face-corner halo regions
215     e2FillValue_RL = 0. _d 0
216     e2FillValue_RS = 0. _d 0
217     e2FillValue_R4 = 0.e0
218     e2FillValue_R8 = 0.d0
219     C- for testing only: put a large value (should not affects the results)
220     c e2FillValue_RL = 1. _d+20
221     c e2FillValue_RS = 1. _d+20
222     c e2FillValue_R4 = 1.e+20
223     c e2FillValue_R8 = 1.d+20
224    
225 afe 1.1 C Print out the topology communication schedule
226 jmc 1.11 IF ( W2_printMsg .NE. 0 ) THEN
227     CALL W2_PRINT_COMM_SEQUENCE( myThid )
228     ENDIF
229 jmc 1.8
230     C Close message output-file (if needed)
231     IF ( W2_oUnit.NE.standardMessageUnit ) THEN
232     WRITE(msgBuf,'(A)') '=== End TOPOLOGY report ==='
233     CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_BOTH, myThid )
234     CLOSE( W2_oUnit )
235     ENDIF
236     WRITE(msgBuf,'(A)') '===== setting W2 TOPOLOGY: Done'
237     CALL PRINT_MESSAGE( msgBuf, stdUnit, SQUEEZE_RIGHT, myThid )
238     WRITE(msgBuf,'(A)') ' '
239     CALL PRINT_MESSAGE( msgBuf, stdUnit, SQUEEZE_RIGHT, myThid )
240 jmc 1.7
241 afe 1.1 RETURN
242     END

  ViewVC Help
Powered by ViewVC 1.1.22