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

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

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


Revision 1.1 - (show annotations) (download)
Sun Aug 28 18:18:09 2005 UTC (19 years, 11 months ago) by edhill
Branch: MAIN
CVS Tags: HEAD
 o initial check-in of an example to test some new exch2 bits

1 C $Header: /u/gcmpack/MITgcm/pkg/exch2/w2_eeboot.F,v 1.6 2005/07/24 01:24:56 jmc 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 C Define toplogy for every tile
45 IF ( .NOT. useAsciiW2Reader ) THEN
46 CALL W2_E2SETUP
47 ELSE
48 STOP 'ERROR: "useAsciiW2Reader" is not yet implemented'
49 CALL W2_AREAD_SETUP()
50 ENDIF
51
52 C Decide which tiles this process handles - do this inline for now, but
53 C should go in subroutine.
54 C Total number of tiles should be divisible by nPx and nSx
55 C ( there is no two dimensional decomposition for W2 ) and
56 C number of tiles per process should be nSx
57 nt_check = NTILES/(nPx*nSx)
58 nt_check = nt_check*nPx*nSx
59 IF ( nt_check .NE. NTILES ) THEN
60 STOP
61 &'ERROR: W2_EEBOOT number of tiles is not divisible by nPx*nSx'
62 ENDIF
63 nt_perproc = NTILES/nPx
64 IF ( nt_perproc .NE. nSx ) THEN
65 STOP
66 &'ERROR: W2_EEBOOT tiles per process is not equal to nSx'
67 ENDIF
68 C Number of tiles I handle is nSx, range of tile numbers I handle
69 C depends on my rank.
70 #ifdef ALLOW_USE_MPI
71 thisPtileLo = myPid*nt_perproc+1
72 thisPtileHi = (myPid+1)*nt_perproc
73 #else
74 thisPtileLo = 1
75 thisPtileHi = nt_perproc
76 #endif
77 DO I=thisPtileLo, thisPtileHi
78 W2_myTileList(I-thisPtileLo+1)=I
79 ENDDO
80 iErr = 0
81
82 DO I=1,nSx
83 C Check tile sizes
84 myTileId = W2_myTileList(I)
85 tnx = exch2_tnx(myTileId)
86 tny = exch2_tny(myTileId)
87 IF ( tnx .NE. sNx ) THEN
88 WRITE(msgBuffer,'(A,I4,A,I4)')
89 & 'ERROR: S/R W2_EEBOOT Topology tnx=',
90 & tnx,
91 & ' is not equal to subgrid size sNx=',
92 & sNx
93 CALL PRINT_MESSAGE(msgBuffer,
94 & errorMessageUnit, SQUEEZE_RIGHT, 1 )
95 iErr = iErr+1
96 ENDIF
97 IF ( tny .NE. sNy ) THEN
98 WRITE(msgBuffer,'(A,I4,A,I4,A,I4)')
99 & 'ERROR: S/R W2_EEBOOT Topology for tile ',myTileId,
100 & 'tny=',
101 & tny,
102 & ' is not equal to subgrid size sNy=',
103 & sNy
104 CALL PRINT_MESSAGE(msgBuffer,
105 & errorMessageUnit, SQUEEZE_RIGHT, 1 )
106 iErr = iErr+1
107 ENDIF
108 ENDDO
109 IF ( iErr .NE. 0 ) THEN
110 STOP 'ABNORMAL END: W2_EEBOOT'
111 ENDIF
112
113 C Set which rank processes "own" which tiles. This should probably
114 C be queried as part of some hand-shaking but for now we use the
115 C functiional relationship that was used above.
116 DO I=1,nTiles
117 pRank = (I-1)/nt_perproc
118 exch2_tProc(I) = pRank+1
119 ENDDO
120
121 WRITE(msgBuffer,'(A)') '===== W2 TILE TOPLOGY ====='
122 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
123 & SQUEEZE_BOTH,myThid)
124 DO I=1,nSx
125 myTileId = W2_myTileList(I)
126 WRITE(msgBuffer,'(A,I4)') ' TILE: ', myTileId
127 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
128 & SQUEEZE_RIGHT,myThid)
129 DO J=1,exch2_nNeighbours(myTileId)
130 commFlag = 'M'
131 DO II=1,nSx
132 IF ( W2_myTileList(II) .EQ. exch2_neighbourId(J,myTileId) )
133 & commFlag = 'P'
134 ENDDO
135 IF ( commFlag .EQ. 'M' ) THEN
136 WRITE(msgBuffer,'(A,I4,A,I4,A,A,I4,A)')
137 & ' NEIGHBOUR ',J,' = TILE ',
138 & exch2_neighbourId(J,myTileId), ' Comm = MSG',
139 & ' ( PROC = ',exch2_tProc(exch2_neighbourId(J,myTileId)),')'
140 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
141 & SQUEEZE_RIGHT,myThid)
142 ENDIF
143 IF ( commFlag .EQ. 'P' ) THEN
144 WRITE(msgBuffer,'(A,I4,A,I4,A,A,I4,A)')
145 & ' NEIGHBOUR ',J,' = TILE ',
146 & exch2_neighbourId(J,myTileId), ' Comm = PUT',
147 & ' ( PROC = ',exch2_tProc(exch2_neighbourId(J,myTileId)),')'
148 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
149 & SQUEEZE_RIGHT,myThid)
150 ENDIF
151 W2_myCommFlag(J,I) = commFlag
152 ENDDO
153 ENDDO
154
155 C Fill in values for W2_mpi_myTileList
156 #ifdef ALLOW_USE_MPI
157 mpiBufSize=nSx
158 mpiRequest=0
159 DO npe = 0, numberOfProcs-1
160 CALL MPI_ISEND (W2_myTileList, mpiBufSize, MPI_INTEGER,
161 & npe, mpiMyId, MPI_COMM_MODEL, mpiRequest, ierr)
162 ENDDO
163 DO npe = 0, numberOfProcs-1
164 CALL MPI_RECV (itemp, mpiBufSize, MPI_INTEGER,
165 & npe, npe, MPI_COMM_MODEL, istatus, ierr)
166 DO I=1,nSx
167 W2_mpi_myTileList(npe+1,I)=itemp(I)
168 ENDDO
169 ENDDO
170 #else /* ALLOW_USE_MPI */
171 DO I=1,nSx
172 W2_mpi_myTileList(1,I)=W2_myTileList(I)
173 ENDDO
174 #endif /* ALLOW_USE_MPI */
175
176 C Set filling value for face-corner halo regions
177 e2FillValue_RL = 0. _d 0
178 e2FillValue_RS = 0. _d 0
179 e2FillValue_R4 = 0.e0
180 e2FillValue_R8 = 0.d0
181 C- for testing only: put a large value (should not affects the results)
182 c e2FillValue_RL = 1. _d+20
183 c e2FillValue_RS = 1. _d+20
184 c e2FillValue_R4 = 1.e+20
185 c e2FillValue_R8 = 1.d+20
186
187 C Print out the topology communication schedule
188 CALL W2_PRINT_COMM_SEQUENCE
189 C
190 RETURN
191 END

  ViewVC Help
Powered by ViewVC 1.1.22