/[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.9 - (hide annotations) (download)
Wed Apr 29 21:37:46 2009 UTC (15 years, 1 month ago) by jmc
Branch: MAIN
Changes since 1.8: +2 -3 lines
fix previous modif (typo in format, which did not bother g77)

1 jmc 1.9 C $Header: /u/gcmpack/MITgcm/pkg/exch2/w2_eeboot.F,v 1.8 2009/04/29 19:44:44 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 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.7 WRITE(msgBuf,'(A,I4)') ' TILE: ', myTileId
167 jmc 1.8 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
168 afe 1.1 DO J=1,exch2_nNeighbours(myTileId)
169     commFlag = 'M'
170     DO II=1,nSx
171     IF ( W2_myTileList(II) .EQ. exch2_neighbourId(J,myTileId) )
172     & commFlag = 'P'
173     ENDDO
174     IF ( commFlag .EQ. 'M' ) THEN
175 jmc 1.7 WRITE(msgBuf,'(A,I4,A,I4,A,A,I4,A)')
176     & ' NEIGHBOUR ',J,' = TILE ',
177 afe 1.1 & exch2_neighbourId(J,myTileId), ' Comm = MSG',
178     & ' ( PROC = ',exch2_tProc(exch2_neighbourId(J,myTileId)),')'
179 jmc 1.8 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
180 afe 1.1 ENDIF
181     IF ( commFlag .EQ. 'P' ) THEN
182 jmc 1.7 WRITE(msgBuf,'(A,I4,A,I4,A,A,I4,A)')
183     & ' NEIGHBOUR ',J,' = TILE ',
184 afe 1.1 & exch2_neighbourId(J,myTileId), ' Comm = PUT',
185     & ' ( PROC = ',exch2_tProc(exch2_neighbourId(J,myTileId)),')'
186 jmc 1.8 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
187 afe 1.1 ENDIF
188     W2_myCommFlag(J,I) = commFlag
189     ENDDO
190     ENDDO
191 dimitri 1.2
192 jmc 1.6 C Set filling value for face-corner halo regions
193     e2FillValue_RL = 0. _d 0
194     e2FillValue_RS = 0. _d 0
195     e2FillValue_R4 = 0.e0
196     e2FillValue_R8 = 0.d0
197     C- for testing only: put a large value (should not affects the results)
198     c e2FillValue_RL = 1. _d+20
199     c e2FillValue_RS = 1. _d+20
200     c e2FillValue_R4 = 1.e+20
201     c e2FillValue_R8 = 1.d+20
202    
203 afe 1.1 C Print out the topology communication schedule
204 jmc 1.8 CALL W2_PRINT_COMM_SEQUENCE( W2_oUnit )
205    
206     C Close message output-file (if needed)
207     IF ( W2_oUnit.NE.standardMessageUnit ) THEN
208     WRITE(msgBuf,'(A)') '=== End TOPOLOGY report ==='
209     CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_BOTH, myThid )
210     CLOSE( W2_oUnit )
211     ENDIF
212     WRITE(msgBuf,'(A)') '===== setting W2 TOPOLOGY: Done'
213     CALL PRINT_MESSAGE( msgBuf, stdUnit, SQUEEZE_RIGHT, myThid )
214     WRITE(msgBuf,'(A)') ' '
215     CALL PRINT_MESSAGE( msgBuf, stdUnit, SQUEEZE_RIGHT, myThid )
216 jmc 1.7
217 afe 1.1 RETURN
218     END

  ViewVC Help
Powered by ViewVC 1.1.22