/[MITgcm]/MITgcm/pkg/exch2/w2_eeboot.F
ViewVC logotype

Contents of /MITgcm/pkg/exch2/w2_eeboot.F

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


Revision 1.1 - (show annotations) (download)
Fri Jan 9 20:46:10 2004 UTC (20 years, 4 months ago) by afe
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube4, checkpoint52j_post, checkpoint52l_post, checkpoint52k_post, checkpoint52f_post, hrcube5, checkpoint52i_post, checkpoint52j_pre, checkpoint52i_pre, checkpoint52h_pre, hrcube_2, hrcube_3
Added exch2 routines and pointed hs94.cs-32x32x5 at them

1 C $Header: /u/u0/gcmpack/MITgcm_contrib/high_res_cube/code-mods/w2_eeboot.F,v 1.2 2003/11/22 01:16:18 dimitri 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
37 C Set dummy myThid value (we aren't multi-threaded here)
38 myThid = 1
39
40 C Define toplogy for every tile
41 CALL W2_E2SETUP
42
43 C Decide which tiles this process handles - do this inline for now, but
44 C should go in subroutine.
45 C Total number of tiles should be divisible by nPx and nSx
46 C ( there is no two dimensional decomposition for W2 ) and
47 C number of tiles per process should be nSx
48 nt_check = NTILES/(nPx*nSx)
49 nt_check = nt_check*nPx*nSx
50 IF ( nt_check .NE. NTILES ) THEN
51 STOP
52 &'ERROR: W2_EEBOOT number of tiles is not divisible by nPx*nSx'
53 ENDIF
54 nt_perproc = NTILES/nPx
55 IF ( nt_perproc .NE. nSx ) THEN
56 STOP
57 &'ERROR: W2_EEBOOT tiles per process is not equal to nSx'
58 ENDIF
59 C Number of tiles I handle is nSx, range of tile numbers I handle
60 C depends on my rank.
61 #ifdef ALLOW_USE_MPI
62 thisPtileLo = myPid*nt_perproc+1
63 thisPtileHi = (myPid+1)*nt_perproc
64 #else
65 thisPtileLo = 1
66 thisPtileHi = nt_perproc
67 #endif
68 DO I=thisPtileLo, thisPtileHi
69 W2_myTileList(I-thisPtileLo+1)=I
70 ENDDO
71 iErr = 0
72
73 DO I=1,nSx
74 C Check tile sizes
75 myTileId = W2_myTileList(I)
76 tnx = exch2_tnx(myTileId)
77 tny = exch2_tny(myTileId)
78 IF ( tnx .NE. sNx ) THEN
79 WRITE(msgBuffer,'(A,I4,A,I4)')
80 & 'ERROR: S/R W2_EEBOOT Topology tnx=',
81 & tnx,
82 & ' is not equal to subgrid size sNx=',
83 & sNx
84 CALL PRINT_MESSAGE(msgBuffer,
85 & errorMessageUnit, SQUEEZE_RIGHT, 1 )
86 iErr = iErr+1
87 ENDIF
88 IF ( tny .NE. sNy ) THEN
89 WRITE(msgBuffer,'(A,I4,A,I4,A,I4)')
90 & 'ERROR: S/R W2_EEBOOT Topology for tile ',myTileId,
91 & 'tny=',
92 & tny,
93 & ' is not equal to subgrid size sNy=',
94 & sNy
95 CALL PRINT_MESSAGE(msgBuffer,
96 & errorMessageUnit, SQUEEZE_RIGHT, 1 )
97 iErr = iErr+1
98 ENDIF
99 ENDDO
100 IF ( iErr .NE. 0 ) THEN
101 STOP 'ABNORMAL END: W2_EEBOOT'
102 ENDIF
103
104 C Set which rank processes "own" which tiles. This should probably
105 C be queried as part of some hand-shaking but for now we use the
106 C functiional relationship that was used above.
107 DO I=1,nTiles
108 pRank = (I-1)/nt_perproc
109 exch2_tProc(I) = pRank+1
110 ENDDO
111
112 WRITE(msgBuffer,'(A)') '===== W2 TILE TOPLOGY ====='
113 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
114 & SQUEEZE_BOTH,myThid)
115 DO I=1,nSx
116 myTileId = W2_myTileList(I)
117 WRITE(msgBuffer,'(A,I4)') ' TILE: ', myTileId
118 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
119 & SQUEEZE_RIGHT,myThid)
120 DO J=1,exch2_nNeighbours(myTileId)
121 commFlag = 'M'
122 DO II=1,nSx
123 IF ( W2_myTileList(II) .EQ. exch2_neighbourId(J,myTileId) )
124 & commFlag = 'P'
125 ENDDO
126 IF ( commFlag .EQ. 'M' ) THEN
127 WRITE(msgBuffer,'(A,I4,A,I4,A,A,I4,A)')
128 & ' NEIGHBOUR ',J,' = TILE ',
129 & exch2_neighbourId(J,myTileId), ' Comm = MSG',
130 & ' ( PROC = ',exch2_tProc(exch2_neighbourId(J,myTileId)),')'
131 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
132 & SQUEEZE_RIGHT,myThid)
133 ENDIF
134 IF ( commFlag .EQ. 'P' ) THEN
135 WRITE(msgBuffer,'(A,I4,A,I4,A,A,I4,A)')
136 & ' NEIGHBOUR ',J,' = TILE ',
137 & exch2_neighbourId(J,myTileId), ' Comm = PUT',
138 & ' ( PROC = ',exch2_tProc(exch2_neighbourId(J,myTileId)),')'
139 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
140 & SQUEEZE_RIGHT,myThid)
141 ENDIF
142 W2_myCommFlag(J,I) = commFlag
143 ENDDO
144 ENDDO
145 C
146 C Print out the topology communication schedule
147 CALL W2_PRINT_COMM_SEQUENCE
148 C
149 RETURN
150 END

  ViewVC Help
Powered by ViewVC 1.1.22