/[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.10 - (hide annotations) (download)
Wed May 6 01:03:41 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61n
Changes since 1.9: +15 -13 lines
add Nb of Neighbours & target-tile neighbour number to printed list

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

  ViewVC Help
Powered by ViewVC 1.1.22