/[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.8 - (hide annotations) (download)
Wed Apr 29 19:44:44 2009 UTC (15 years, 1 month ago) by jmc
Branch: MAIN
Changes since 1.7: +47 -12 lines
option (Off for now) to print topology report in a log-file (instead of STDOUT);
 skip suffix (PID.TID...) when printing most of the topology report.

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

  ViewVC Help
Powered by ViewVC 1.1.22