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

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

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


Revision 1.1 - (show annotations) (download)
Tue May 12 19:40:32 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61o
new code to set-up W2-Exch2 topology (replace matlab-topology-generator)
 read parameter file "data.exch2" if it exist ; otherwise try default
 regular cube without blank-tile.

1 C $Header: /u/gcmpack/MITgcm/pkg/exch2/w2_e2setup.F,v 1.3 2008/07/29 20:25:23 jmc Exp $
2 C $Name: $
3
4 #include "CPP_EEOPTIONS.h"
5 #include "W2_OPTIONS.h"
6
7 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
8 CBOP 0
9 C !ROUTINE: W2_PRINT_E2SETUP
10
11 C !INTERFACE:
12 SUBROUTINE W2_PRINT_E2SETUP( myThid )
13
14 C !DESCRIPTION:
15 C Print out Wrapper-Exch2 Set-Up as defined by matlab generated source
16 C files (W2_EXCH2_SIZE.h & W2_E2SETUP). Allows a direct comparison
17 C with standard Fortran src generated topology.
18
19 C !USES:
20 IMPLICIT NONE
21
22 C Tile toplogy settings data structures
23 #include "SIZE.h"
24 #include "EEPARAMS.h"
25 #include "W2_EXCH2_SIZE.h"
26 #include "W2_EXCH2_PARAMS.h"
27 #include "W2_EXCH2_TOPOLOGY.h"
28
29 C !INPUT PARAMETERS:
30 C myThid :: my Thread Id number
31 C (Note: not relevant since threading has not yet started)
32 INTEGER myThid
33
34 C !LOCAL VARIABLES:
35 C === Local variables ===
36 C msgBuf :: Informational/error meesage buffer
37 CHARACTER*(MAX_LEN_MBUF) msgBuf
38 CHARACTER*1 edge(4), cc1
39 INTEGER tNx, tNy, fNx, fNy
40 INTEGER nbTx, nbTy
41 INTEGER ip(4), np(4)
42 INTEGER i, j, js, jp, jt, ii, is, it, ns, nt, k, tx, ty
43 LOGICAL prtFlag
44 CEOP
45 DATA edge / 'N' , 'S' , 'E' , 'W' /
46
47 tNx = sNx
48 tNy = sNy
49 prtFlag = ABS(W2_printMsg).GE.2
50 & .OR. ( W2_printMsg .NE.0 .AND. myProcId.EQ.0 )
51
52 C=================== from W2_SET_F2F_INDEX :
53 c WRITE(msgBuf,'(2A)') 'W2_SET_F2F_INDEX:',
54 WRITE(msgBuf,'(2A)') 'W2_PRINT_E2SETUP:',
55 & ' index matrix for connected Facet-Edges:'
56 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
57
58 jp = 0
59 IF ( prtFlag ) THEN
60 DO is=1,nTiles
61 js = exch2_myFace(is)
62 IF ( js.NE.0 ) THEN
63 C-- tile is is active
64 fNx = exch2_mydNx(is)
65 fNy = exch2_mydNy(is)
66 nbTx = fNx/tNx
67 nbTy = fNy/tNy
68 IF ( js.NE.jp ) THEN
69 IF ( jp.NE.0 ) THEN
70 C--- write
71 DO i=1,4
72 IF ( ip(i).NE.0 ) THEN
73 j = exch2_myFace(ip(i))
74 it = exch2_neighbourId (np(i),ip(i))
75 nt = exch2_opposingSend(np(i),ip(i))
76 jt = exch2_myFace(it)
77 ii = 0
78 IF ( exch2_jLo(nt,it).EQ.exch2_jHi(nt,it) )
79 & ii = 2 - MIN(1,exch2_jHi(nt,it))
80 IF ( exch2_iLo(nt,it).EQ.exch2_iHi(nt,it) )
81 & ii = 4 - MIN(1,exch2_iHi(nt,it))
82 cc1 = '?'
83 IF ( ii.NE.0 ) cc1 = edge(ii)
84 WRITE(W2_oUnit,'(2(3A,I3),A,4I3,A,2I6)')
85 & ' ', edge(i), '.Edge Facet', j, ' <-- ',
86 & cc1, '.Edge Facet', jt,
87 & ' : pij=', (exch2_pij(k,np(i),ip(i)),k=1,4),
88 & ' ; oi,oj=',exch2_oi(np(i),ip(i)),exch2_oj(np(i),ip(i))
89 ENDIF
90 ENDDO
91 C---
92 ENDIF
93 jp = js
94 DO i=1,4
95 ip(i) = 0
96 np(i) = 0
97 ENDDO
98 ENDIF
99 DO ns=1,exch2_nNeighbours(is)
100 IF ( ip(1).EQ.0 .AND. exch2_isNedge(is).EQ.1
101 & .AND. exch2_jLo(ns,is).EQ.(tNy+1)
102 & .AND. exch2_jHi(ns,is).EQ.(tNy+1) ) THEN
103 ip(1) = is
104 np(1) = ns
105 ENDIF
106 IF ( ip(2).EQ.0 .AND. exch2_isSedge(is).EQ.1
107 & .AND. exch2_jLo(ns,is).EQ. 0
108 & .AND. exch2_jHi(ns,is).EQ. 0 ) THEN
109 ip(2) = is
110 np(2) = ns
111 ENDIF
112 IF ( ip(3).EQ.0 .AND. exch2_isEedge(is).EQ.1
113 & .AND. exch2_iLo(ns,is).EQ.(tNx+1)
114 & .AND. exch2_iHi(ns,is).EQ.(tNx+1) ) THEN
115 ip(3) = is
116 np(3) = ns
117 ENDIF
118 IF ( ip(4).EQ.0 .AND. exch2_isWedge(is).EQ.1
119 & .AND. exch2_iLo(ns,is).EQ. 0
120 & .AND. exch2_iHi(ns,is).EQ. 0 ) THEN
121 ip(4) = is
122 np(4) = ns
123 ENDIF
124 ENDDO
125
126 C-- end if active tile
127 ENDIF
128 ENDDO
129 C--- write the last one:
130 DO i=1,4
131 IF ( ip(i).NE.0 ) THEN
132 j = exch2_myFace(ip(i))
133 it = exch2_neighbourId (np(i),ip(i))
134 nt = exch2_opposingSend(np(i),ip(i))
135 jt = exch2_myFace(it)
136 ii = 0
137 IF ( exch2_jLo(nt,it).EQ.exch2_jHi(nt,it) )
138 & ii = 2 - MIN(1,exch2_jHi(nt,it))
139 IF ( exch2_iLo(nt,it).EQ.exch2_iHi(nt,it) )
140 & ii = 4 - MIN(1,exch2_iHi(nt,it))
141 cc1 = '?'
142 IF ( ii.NE.0 ) cc1 = edge(ii)
143 WRITE(W2_oUnit,'(2(3A,I3),A,4I3,A,2I6)')
144 & ' ', edge(i), '.Edge Facet', j, ' <-- ',
145 & cc1, '.Edge Facet', jt,
146 & ' : pij=', (exch2_pij(k,np(i),ip(i)),k=1,4),
147 & ' ; oi,oj=',exch2_oi(np(i),ip(i)),exch2_oj(np(i),ip(i))
148 ENDIF
149 ENDDO
150 C---
151 ENDIF
152
153 C=================== from W2_SET_MAP_TILES :
154
155 C Set-up tiles mapping and IO global mapping
156 c WRITE(msgBuf,'(2A)') 'W2_SET_MAP_TILES:',
157 WRITE(msgBuf,'(2A)') 'W2_PRINT_E2SETUP:',
158 & ' tile mapping within facet and global Map:'
159 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
160
161 C-- Check that tile dims divise facet dims
162 C-- Check that domain size and (SIZE.h + blankList) match:
163 C-- Compact IO map (mostly in Y dir): search for Greatest Common Divisor
164 C of all x-size (faster to apply GCD to Nb of Tiles in X):
165
166 WRITE(msgBuf,'(A,2(A,I8))') ' Global Map (IO):',
167 & ' X-size=', exch2_global_Nx, ' , Y-size=', exch2_global_Ny
168 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
169
170 C-- Set tiles mapping within facet (sub-domain) and within Global Map
171 c WRITE(msgBuf,'(2A)') 'W2_SET_MAP_TILES:',
172 WRITE(msgBuf,'(2A)') 'W2_PRINT_E2SETUP:',
173 & ' tile offset within facet and global Map:'
174 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
175 jp = 0
176 DO is=1,nTiles
177 js = exch2_myFace(is)
178 IF ( js.NE.0 ) THEN
179 fNx = exch2_mydNx(is)
180 fNy = exch2_mydNy(is)
181 nbTx = fNx/tNx
182 nbTy = fNy/tNy
183 IF ( js .NE. jp )
184 & WRITE(W2_oUnit,'(A,I3,2(A,I6),A,I5,2(A,I4),A)')
185 & '- facet', js, ' : X-size=', fNx, ' , Y-size=', fNy,
186 & ' ;', nbTx*nbTy, ' tiles (Tx,Ty=', nbTx,',',nbTy,')'
187 jp = js
188 IF ( prtFlag ) THEN
189 tx = 1 + exch2_tBasex(is)/tNx
190 ty = 1 + exch2_tBasey(is)/tNy
191 WRITE(W2_oUnit,'(A,I5,3(A,I3),2A,2I5,2A,2I8)') ' tile',is,
192 & ' on facet', exch2_myFace(is),' (',tx,',',ty,'):',
193 & ' offset=', exch2_tBasex(is), exch2_tBasey(is),' ;',
194 & ' on Glob.Map=', exch2_txGlobalo(is),exch2_tyGlobalo(is)
195 ENDIF
196 ENDIF
197 ENDDO
198
199 C=================== from W2_SET_TILE2TILES :
200 c WRITE(msgBuf,'(2A)') 'W2_SET_TILE2TILES:',
201 WRITE(msgBuf,'(2A)') 'W2_PRINT_E2SETUP:',
202 & ' tile neighbours and index connection:'
203 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
204
205 it = 1
206 DO is=1,nTiles
207 js = exch2_myFace(is)
208 IF ( js.NE.0 ) THEN
209 IF ( exch2_nNeighbours(is).GT.exch2_nNeighbours(it) ) it = is
210 IF ( prtFlag ) THEN
211 WRITE(W2_oUnit,'(A,I5,A,I3,A,4(A,I2))') 'Tile',is,
212 & ' : nbNeighb=',exch2_nNeighbours(is),' ; is-at-Facet-Edge:',
213 & ' N=', exch2_isNedge(is), ' , S=', exch2_isSedge(is),
214 & ' , E=', exch2_isEedge(is), ' , W=', exch2_isWedge(is)
215 DO ns=1,exch2_nNeighbours(is)
216 WRITE(W2_oUnit,'(A,I3,A,I5,2(A,2I6),A,4I3,A,2I6,A)')
217 & ' ns:',ns,' it=',exch2_neighbourId(ns,is),
218 & ', iLo,iHi=', exch2_iLo(ns,is), exch2_iHi(ns,is),
219 & ', jLo,jHi=', exch2_jLo(ns,is), exch2_jHi(ns,is)
220 c & , ' (pij=',(exch2_pij(k,ns,is),k=1,4),
221 c & ', oi,oj=', exch2_oi(ns,is), exch2_oj(ns,is),')'
222 ENDDO
223 ENDIF
224 ENDIF
225 ENDDO
226 IF ( it.NE.0 ) THEN
227 WRITE(msgBuf,'(A,I5,A,I3)')
228 & 'current Max.Nb.Neighbours (e.g., on tile',it,
229 & ' ) =', exch2_nNeighbours(it)
230 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
231 ENDIF
232
233
234 RETURN
235 END

  ViewVC Help
Powered by ViewVC 1.1.22