/[MITgcm]/MITgcm_contrib/eh3_spgr/hs94.cs-32x32x5/code_v2/w2_eeboot.F
ViewVC logotype

Contents of /MITgcm_contrib/eh3_spgr/hs94.cs-32x32x5/code_v2/w2_eeboot.F

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


Revision 1.3 - (show annotations) (download)
Sat Sep 24 22:40:16 2005 UTC (19 years, 10 months ago) by edhill
Branch: MAIN
CVS Tags: HEAD
Changes since 1.2: +2 -2 lines
 o first working ASCII topology version

1 C $Header: /u/gcmpack/MITgcm_contrib/eh3_spgr/hs94.cs-32x32x5/code_v2/w2_eeboot.F,v 1.2 2005/09/24 19:38:18 edhill 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 IMPLICIT NONE
12
13 C !DESCRIPTION:
14 C *==========================================================*
15 C | SUBROUTINE W2_EEBOOT
16 C | o Setup execution "environment" for WRAPPER2
17 C *==========================================================*
18 C | WRAPPER2 provides complex topology support. In this routine
19 C | we setup the base topology for the default halo operations.
20 C *==========================================================*
21 #include "SIZE.h"
22 #include "EEPARAMS.h"
23 #include "EESUPPORT.h"
24 #include "W2_EXCH2_TOPOLOGY.h"
25 #include "W2_EXCH2_PARAMS.h"
26
27 C == Local variables ==
28 INTEGER nt_check, nt_perproc
29 INTEGER thisPtileLo, thisPtileHi
30 CHARACTER*(MAX_LEN_MBUF) msgBuffer
31 CHARACTER commFlag
32 INTEGER myTileId
33 INTEGER myThid, I, J, II
34 INTEGER iErr, tNx, tNy
35 INTEGER pRank
36 #ifdef ALLOW_USE_MPI
37 INTEGER npe,itemp(nSx),mpiBufSize,mpiRequest
38 INTEGER istatus(MPI_STATUS_SIZE)
39 #endif
40
41 C Set dummy myThid value (we are not multi-threaded here)
42 myThid = 1
43
44 IF ( W2_read_acsii_topo ) THEN
45 CALL W2_READ_ATOPO
46 ELSE
47 C Define toplogy for every tile
48 CALL W2_E2SETUP
49 ENDIF
50
51 C Decide which tiles this process handles - do this inline for now, but
52 C should go in subroutine.
53 C Total number of tiles should be divisible by nPx and nSx
54 C ( there is no two dimensional decomposition for W2 ) and
55 C number of tiles per process should be nSx
56 nt_check = NTILES/(nPx*nSx)
57 nt_check = nt_check*nPx*nSx
58 IF ( nt_check .NE. NTILES ) THEN
59 STOP
60 &'ERROR: W2_EEBOOT number of tiles is not divisible by nPx*nSx'
61 ENDIF
62 nt_perproc = NTILES/nPx
63 IF ( nt_perproc .NE. nSx ) THEN
64 STOP
65 &'ERROR: W2_EEBOOT tiles per process is not equal to nSx'
66 ENDIF
67 C Number of tiles I handle is nSx, range of tile numbers I handle
68 C depends on my rank.
69 #ifdef ALLOW_USE_MPI
70 thisPtileLo = myPid*nt_perproc+1
71 thisPtileHi = (myPid+1)*nt_perproc
72 #else
73 thisPtileLo = 1
74 thisPtileHi = nt_perproc
75 #endif
76 DO I=thisPtileLo, thisPtileHi
77 W2_myTileList(I-thisPtileLo+1)=I
78 ENDDO
79 iErr = 0
80
81 DO I=1,nSx
82 C Check tile sizes
83 myTileId = W2_myTileList(I)
84 tnx = exch2_tnx(myTileId)
85 tny = exch2_tny(myTileId)
86 IF ( tnx .NE. sNx ) THEN
87 WRITE(msgBuffer,'(A,I4,A,I4)')
88 & 'ERROR: S/R W2_EEBOOT Topology tnx=',
89 & tnx,
90 & ' is not equal to subgrid size sNx=',
91 & sNx
92 CALL PRINT_MESSAGE(msgBuffer,
93 & errorMessageUnit, SQUEEZE_RIGHT, 1 )
94 iErr = iErr+1
95 ENDIF
96 IF ( tny .NE. sNy ) THEN
97 WRITE(msgBuffer,'(A,I4,A,I4,A,I4)')
98 & 'ERROR: S/R W2_EEBOOT Topology for tile ',myTileId,
99 & ' tny=',
100 & tny,
101 & ' is not equal to subgrid size sNy=',
102 & sNy
103 CALL PRINT_MESSAGE(msgBuffer,
104 & errorMessageUnit, SQUEEZE_RIGHT, 1 )
105 iErr = iErr+1
106 ENDIF
107 ENDDO
108 IF ( iErr .NE. 0 ) THEN
109 STOP 'ABNORMAL END: W2_EEBOOT'
110 ENDIF
111
112 C Set which rank processes "own" which tiles. This should probably
113 C be queried as part of some hand-shaking but for now we use the
114 C functiional relationship that was used above.
115 DO I=1,nTiles
116 pRank = (I-1)/nt_perproc
117 exch2_tProc(I) = pRank+1
118 ENDDO
119
120 WRITE(msgBuffer,'(A)') '===== W2 TILE TOPLOGY ====='
121 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
122 & SQUEEZE_BOTH,myThid)
123 DO I=1,nSx
124 myTileId = W2_myTileList(I)
125 WRITE(msgBuffer,'(A,I4)') ' TILE: ', myTileId
126 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
127 & SQUEEZE_RIGHT,myThid)
128 DO J=1,exch2_nNeighbours(myTileId)
129 commFlag = 'M'
130 DO II=1,nSx
131 IF ( W2_myTileList(II) .EQ. exch2_neighbourId(J,myTileId) )
132 & commFlag = 'P'
133 ENDDO
134 IF ( commFlag .EQ. 'M' ) THEN
135 WRITE(msgBuffer,'(A,I4,A,I4,A,A,I4,A)')
136 & ' NEIGHBOUR ',J,' = TILE ',
137 & exch2_neighbourId(J,myTileId), ' Comm = MSG',
138 & ' ( PROC = ',exch2_tProc(exch2_neighbourId(J,myTileId)),')'
139 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
140 & SQUEEZE_RIGHT,myThid)
141 ENDIF
142 IF ( commFlag .EQ. 'P' ) THEN
143 WRITE(msgBuffer,'(A,I4,A,I4,A,A,I4,A)')
144 & ' NEIGHBOUR ',J,' = TILE ',
145 & exch2_neighbourId(J,myTileId), ' Comm = PUT',
146 & ' ( PROC = ',exch2_tProc(exch2_neighbourId(J,myTileId)),')'
147 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
148 & SQUEEZE_RIGHT,myThid)
149 ENDIF
150 W2_myCommFlag(J,I) = commFlag
151 ENDDO
152 ENDDO
153
154 C Fill in values for W2_mpi_myTileList
155 #ifdef ALLOW_USE_MPI
156 mpiBufSize=nSx
157 mpiRequest=0
158 DO npe = 0, numberOfProcs-1
159 CALL MPI_ISEND (W2_myTileList, mpiBufSize, MPI_INTEGER,
160 & npe, mpiMyId, MPI_COMM_MODEL, mpiRequest, ierr)
161 ENDDO
162 DO npe = 0, numberOfProcs-1
163 CALL MPI_RECV (itemp, mpiBufSize, MPI_INTEGER,
164 & npe, npe, MPI_COMM_MODEL, istatus, ierr)
165 DO I=1,nSx
166 W2_mpi_myTileList(npe+1,I)=itemp(I)
167 ENDDO
168 ENDDO
169 #else /* ALLOW_USE_MPI */
170 DO I=1,nSx
171 W2_mpi_myTileList(1,I)=W2_myTileList(I)
172 ENDDO
173 #endif /* ALLOW_USE_MPI */
174
175 C Set filling value for face-corner halo regions
176 e2FillValue_RL = 0. _d 0
177 e2FillValue_RS = 0. _d 0
178 e2FillValue_R4 = 0.e0
179 e2FillValue_R8 = 0.d0
180 C- for testing only: put a large value (should not affects the results)
181 c e2FillValue_RL = 1. _d+20
182 c e2FillValue_RS = 1. _d+20
183 c e2FillValue_R4 = 1.e+20
184 c e2FillValue_R8 = 1.d+20
185
186
187 #ifdef ALLOW_USE_MPI
188 IF ( myPid .EQ. 0 ) THEN
189 CALL W2_WRITE_ATOPO
190 ENDIF
191 #else
192 CALL W2_WRITE_ATOPO
193 #endif
194
195 C Print out the topology communication schedule
196 CALL W2_PRINT_COMM_SEQUENCE
197 C
198 RETURN
199 END

  ViewVC Help
Powered by ViewVC 1.1.22