/[MITgcm]/MITgcm/pkg/debug/debug_cs_corner_uv.F
ViewVC logotype

Contents of /MITgcm/pkg/debug/debug_cs_corner_uv.F

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


Revision 1.7 - (show annotations) (download)
Sun Jun 28 01:05:41 2009 UTC (14 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64q, checkpoint64p, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint62, checkpoint63, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61s, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.6: +97 -95 lines
add bj in exch2 arrays and S/R

1 C $Header: /u/gcmpack/MITgcm/pkg/debug/debug_cs_corner_uv.F,v 1.6 2009/05/12 19:56:35 jmc Exp $
2 C $Name: $
3
4 #include "DEBUG_OPTIONS.h"
5
6 SUBROUTINE DEBUG_CS_CORNER_UV(
7 I word2print,
8 I uFld, vFld,
9 I k, ioUnit, bi,bj, myThid )
10 C *==========================================================*
11 C | S/R DEBUG_CS_CORNER_UV |
12 C | o check UV fields at Egdes of CS grid, near corners. |
13 C *==========================================================*
14 C | Values of U,V fields at the Edges of the CS grid |
15 C | are common to 2 faces, and are stored + used in 2 |
16 C | places (2 tiles): one in the interior of the 1rst tile, |
17 C | the other in the halo of the 2nd one. |
18 C | This S/R print the 2 values and check that they are |
19 C | identical (print the difference). |
20 C | This is specially usefull for checking that gU,gV are |
21 C | correct before entering solve_for_pressure. |
22 C *==========================================================*
23 C | Note: only works on a 1.cpu set up with square tiles |
24 C *==========================================================*
25 IMPLICIT NONE
26
27 C == Global variables ==
28 #include "SIZE.h"
29 #include "EEPARAMS.h"
30 #ifdef ALLOW_EXCH2
31 #include "W2_EXCH2_SIZE.h"
32 #include "W2_EXCH2_TOPOLOGY.h"
33 #endif
34 c #include "PARAMS.h"
35 c #include "GRID.h"
36
37 C == Routine arguments ==
38 C word2print :: a string to print
39 C uFld :: u component of 2D vector
40 C vFld :: v component of 2D vector
41 C k :: current level
42 C ioUnit :: I/O unit number
43 C bi,bj :: tile indices
44 C myThid :: Instance number for this invocation of
45 CHARACTER*(*) word2print
46 _RL uFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
47 _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
48 INTEGER k, ioUnit
49 INTEGER bi, bj
50 INTEGER myThid
51
52 #ifdef ALLOW_DEBUG
53
54 C == Local variables in common block :
55 COMMON / DEBUG_CS_CORNER_UV_LOCAL / tmpU, tmpV
56 _RL tmpU(4,Nr,nSx,nSy)
57 _RL tmpV(4,Nr,nSx,nSy)
58
59 C == Local variables ==
60 C edgeIndex :: index (in X or Y) from the W. or S. edge of the tile
61 C :: of the U,V field to write
62 C n1 :: tile index
63 C n2,n3 :: W. and S. neigbour tile indices
64 INTEGER n1,n2,n3
65 INTEGER edgeIndex
66 INTEGER ic, i, j
67
68 EXTERNAL ILNBLNK
69 INTEGER ILNBLNK
70
71 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
72
73 edgeIndex = 1
74
75 j = MIN(MAX(1-Olx,edgeIndex),Olx)
76 1010 FORMAT(2A,I2,1PE12.4,I3,1P2E12.4)
77 c IF (k.EQ.4 .AND. myIter.EQ.nIter0 ) THEN
78 tmpU(1,k,bi,bj)= uFld(1,j)
79 tmpU(2,k,bi,bj)= uFld(1,sNy+1-j)
80 tmpU(3,k,bi,bj)= uFld(sNx+1,j)
81 tmpU(4,k,bi,bj)= uFld(sNx+1,sNy+1-j)
82 tmpV(1,k,bi,bj)= vFld(j,1)
83 tmpV(2,k,bi,bj)= vFld(sNx+1-j,1)
84 tmpV(3,k,bi,bj)= vFld(j,sNy+1)
85 tmpV(4,k,bi,bj)= vFld(sNx+1-j,sNy+1)
86 _BARRIER
87 #ifdef ALLOW_EXCH2
88 IF (bi.EQ.nSx .AND. bj.EQ.nSy .AND. sNx.EQ.sNy) THEN
89 #else /* ALLOW_EXCH2 */
90 IF (bi.EQ.nSx .AND. nSy.EQ.1 .AND. nSx.EQ.6) THEN
91 #endif /* ALLOW_EXCH2 */
92 WRITE(ioUnit,'(2A)') 'DEBUG_CS_CORNER_UV: ',
93 & '------------------------------------------------------------'
94 ic = MAX(1,ILNBLNK(word2print))
95 WRITE(ioUnit,'(3A,I3)') 'DEBUG_CS_CORNER_UV: ',
96 & word2print(1:ic), ' , index=', j
97 WRITE(ioUnit,'(2A,I4)') 'DEBUG_CS_CORNER_UV: ',
98 & ' Edges values near a corner, lev=',k
99 WRITE(ioUnit,'(2A)') 'DEBUG_CS_CORNER_UV: ',
100 & ' tile_1, value_1, tile_2, value_2, difference v1-v2:'
101 DO j=1,nSy
102 DO i=1,nSx
103 #ifdef ALLOW_EXCH2
104 n1 = W2_myTileList(i,j)
105 n2 = exch2_neighbourId(4,n1)
106 n3 = exch2_neighbourId(2,n1)
107 IF ( exch2_pij(3,4,n1).eq.-1 ) THEN
108 WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'W edge, S:',
109 & n1,tmpU(1,k,n1,1), n2,tmpV(4,k,n2,1),
110 & tmpU(1,k,n1,1) - tmpV(4,k,n2,1)
111 WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'W edge, N:',
112 & n1,tmpU(2,k,n1,1), n2,tmpV(3,k,n2,1),
113 & tmpU(2,k,n1,1) - tmpV(3,k,n2,1)
114 ENDIF
115 IF ( exch2_pij(4,4,n1).eq.1 ) THEN
116 WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'W edge, S:',
117 & n1,tmpU(1,k,n1,1), n2,tmpU(3,k,n2,1),
118 & tmpU(1,k,n1,1) - tmpU(3,k,n2,1)
119 WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'W edge, N:',
120 & n1,tmpU(2,k,n1,1), n2,tmpU(4,k,n2,1),
121 & tmpU(2,k,n1,1) - tmpU(4,k,n2,1)
122 ENDIF
123 IF ( exch2_pij(1,2,n1).eq.1 ) THEN
124 WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'S edge, W:',
125 & n1,tmpV(1,k,n1,1), n3,tmpV(3,k,n3,1),
126 & tmpV(1,k,n1,1) - tmpV(3,k,n3,1)
127 WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'S edge, E:',
128 & n1,tmpV(2,k,n1,1), n3,tmpV(4,k,n3,1),
129 & tmpV(2,k,n1,1) - tmpV(4,k,n3,1)
130 ENDIF
131 IF ( exch2_pij(2,2,n1).eq.-1 ) THEN
132 WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'S edge, W:',
133 & n1,tmpV(1,k,n1,1), n3,tmpU(4,k,n3,1),
134 & tmpV(1,k,n1,1) - tmpU(4,k,n3,1)
135 WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'S edge, E:',
136 & n1,tmpV(2,k,n1,1), n3,tmpU(3,k,n3,1),
137 & tmpV(2,k,n1,1) - tmpU(3,k,n3,1)
138 ENDIF
139 #else /* ALLOW_EXCH2 */
140 n1 = i
141 IF (MOD(n1,2).EQ.1 ) THEN
142 c n1=1 n2=5,+v,-
143 c n1=1 n3=6,+v,+
144 c n1=3 n2=1,+v,-
145 c n1=3 n3=2,+v,+
146 c n1=5 n2=3,+v,-
147 c n1=5 n3=4,+v,+
148 n2=1+mod(n1-2+5,6)
149 n3=1+mod(n1-1+5,6)
150 WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'W edge, S:',
151 & n1,tmpU(1,k,n1,1), n2,tmpV(4,k,n2,1),
152 & tmpU(1,k,n1,1) - tmpV(4,k,n2,1)
153 WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'W edge, N:',
154 & n1,tmpU(2,k,n1,1), n2,tmpV(3,k,n2,1),
155 & tmpU(2,k,n1,1) - tmpV(3,k,n2,1)
156 WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'S edge, W:',
157 & n1,tmpV(1,k,n1,1), n3,tmpV(3,k,n3,1),
158 & tmpV(1,k,n1,1) - tmpV(3,k,n3,1)
159 WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'S edge, E:',
160 & n1,tmpV(2,k,n1,1), n3,tmpV(4,k,n3,1),
161 & tmpV(2,k,n1,1) - tmpV(4,k,n3,1)
162 ELSE
163 c n1=2 n2=1,+u,+
164 c n1=2 n3=6,+u,-
165 c n1=4 n2=3,+u,+
166 c n1=4 n3=2,+u,-
167 c n1=6 n2=5,+u,+
168 c n1=6 n3=4,+u,-
169 n2=1+mod(n1-1+5,6)
170 n3=1+mod(n1-2+5,6)
171 WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'W edge, S:',
172 & n1,tmpU(1,k,n1,1), n2,tmpU(3,k,n2,1),
173 & tmpU(1,k,n1,1) - tmpU(3,k,n2,1)
174 WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'W edge, N:',
175 & n1,tmpU(2,k,n1,1), n2,tmpU(4,k,n2,1),
176 & tmpU(2,k,n1,1) - tmpU(4,k,n2,1)
177 WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'S edge, W:',
178 & n1,tmpV(1,k,n1,1), n3,tmpU(4,k,n3,1),
179 & tmpV(1,k,n1,1) - tmpU(4,k,n3,1)
180 WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'S edge, E:',
181 & n1,tmpV(2,k,n1,1), n3,tmpU(3,k,n3,1),
182 & tmpV(2,k,n1,1) - tmpU(3,k,n3,1)
183 ENDIF
184 #endif /* ALLOW_EXCH2 */
185 ENDDO
186 ENDDO
187 WRITE(ioUnit,'(2A)') 'DEBUG_CS_CORNER_UV: ',
188 & '------------------------------------------------------------'
189 ENDIF
190 c ENDIF
191
192 #endif /* ALLOW_DEBUG */
193
194 RETURN
195 END

  ViewVC Help
Powered by ViewVC 1.1.22