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

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

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


Revision 1.3 - (hide annotations) (download)
Thu Feb 10 23:44:06 2005 UTC (19 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, mitgcm_mapl_00, checkpoint58u_post, checkpoint58w_post, checkpoint57m_post, checkpoint57s_post, checkpoint57k_post, checkpoint57d_post, checkpoint57g_post, checkpoint58r_post, checkpoint57i_post, checkpoint57y_post, checkpoint57e_post, checkpoint58n_post, checkpoint58x_post, checkpoint57g_pre, checkpoint58t_post, checkpoint58h_post, checkpoint57y_pre, checkpoint57f_pre, checkpoint58q_post, checkpoint57v_post, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint57r_post, checkpoint59, checkpoint58, eckpoint57e_pre, checkpoint57h_done, checkpoint58f_post, checkpoint57x_post, checkpoint57n_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint57f_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint57j_post, checkpoint58b_post, checkpoint57h_pre, checkpoint58m_post, checkpoint57l_post, checkpoint57h_post
Changes since 1.2: +76 -21 lines
extended to more that 6 (square) tiles ; tested with 24 tiles.

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/pkg/debug/debug_cs_corner_uv.F,v 1.2 2004/09/24 17:01:09 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4 jmc 1.3 #include "DEBUG_OPTIONS.h"
5 jmc 1.1
6     SUBROUTINE DEBUG_CS_CORNER_UV(
7 jmc 1.2 I word2print,
8 jmc 1.1 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 jmc 1.3 C | Note: only works on a 1.cpu set up with square tiles |
24 jmc 1.1 C *==========================================================*
25     IMPLICIT NONE
26    
27     C == Global variables ==
28     #include "SIZE.h"
29     #include "EEPARAMS.h"
30 jmc 1.3 #ifdef ALLOW_EXCH2
31     #include "W2_EXCH2_TOPOLOGY.h"
32     #include "W2_EXCH2_PARAMS.h"
33     #endif
34 jmc 1.1 c #include "PARAMS.h"
35     c #include "GRID.h"
36    
37     C == Routine arguments ==
38 jmc 1.2 C word2print - a string to print
39 jmc 1.1 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 jmc 1.2 CHARACTER*(*) word2print
46 jmc 1.1 _RL uFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
47     _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
48 jmc 1.3 INTEGER k, ioUnit
49     INTEGER bi, bj
50 jmc 1.1 INTEGER myThid
51    
52 jmc 1.3 #ifdef ALLOW_DEBUG
53 jmc 1.1
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 jmc 1.3 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 n,n1,n2,n3
65     INTEGER edgeIndex
66     INTEGER ic, j
67 jmc 1.1
68 jmc 1.2 EXTERNAL ILNBLNK
69     INTEGER ILNBLNK
70    
71 jmc 1.1 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
72    
73 jmc 1.3 edgeIndex = 1
74    
75     j = MIN(MAX(1-Olx,edgeIndex),Olx)
76 jmc 1.1 1010 FORMAT(2A,I2,1PE12.4,I3,1P2E12.4)
77     c IF (k.EQ.4 .AND. myIter.EQ.nIter0 ) THEN
78 jmc 1.3 tmpU(1,k,bi,bj)= uFld(j,1)
79     tmpU(2,k,bi,bj)= uFld(j,sNy)
80     tmpU(3,k,bi,bj)= uFld(sNx+j,1)
81     tmpU(4,k,bi,bj)= uFld(sNx+j,sNy)
82     tmpV(1,k,bi,bj)= vFld(1,j)
83     tmpV(2,k,bi,bj)= vFld(sNx,j)
84     tmpV(3,k,bi,bj)= vFld(1,sNy+j)
85     tmpV(4,k,bi,bj)= vFld(sNx,sNy+j)
86 jmc 1.1 _BARRIER
87 jmc 1.3 #ifdef ALLOW_EXCH2
88     IF (bi.EQ.nSx .AND. sNx.EQ.sNy) THEN
89     #else /* ALLOW_EXCH2 */
90 jmc 1.1 IF (bi.EQ.nSx .AND. nSx.EQ.6) THEN
91 jmc 1.3 #endif /* ALLOW_EXCH2 */
92 jmc 1.1 WRITE(ioUnit,'(2A)') 'DEBUG_CS_CORNER_UV: ',
93     & '------------------------------------------------------------'
94 jmc 1.2 ic = MAX(1,ILNBLNK(word2print))
95 jmc 1.3 WRITE(ioUnit,'(3A,I3)') 'DEBUG_CS_CORNER_UV: ',
96     & word2print(1:ic), ' , index=', j
97 jmc 1.1 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 jmc 1.3 & ' tile_1, value_1, tile_2, value_2, difference v1-v2:'
101     DO n=1,nSx
102     #ifdef ALLOW_EXCH2
103     n1 = W2_myTileList(n)
104     n2 = exch2_neighbourId(4,n1)
105     n3 = exch2_neighbourId(2,n1)
106     IF ( exch2_pj(1,4,n1).eq.-1 ) THEN
107     WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'W edge, S:',
108     & n1,tmpU(1,k,n1,1), n2,tmpV(4,k,n2,1),
109     & tmpU(1,k,n1,1) - tmpV(4,k,n2,1)
110     WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'W edge, N:',
111     & n1,tmpU(2,k,n1,1), n2,tmpV(3,k,n2,1),
112     & tmpU(2,k,n1,1) - tmpV(3,k,n2,1)
113     ENDIF
114     IF ( exch2_pj(2,4,n1).eq.1 ) THEN
115     WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'W edge, S:',
116     & n1,tmpU(1,k,n1,1), n2,tmpU(3,k,n2,1),
117     & tmpU(1,k,n1,1) - tmpU(3,k,n2,1)
118     WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'W edge, N:',
119     & n1,tmpU(2,k,n1,1), n2,tmpU(4,k,n2,1),
120     & tmpU(2,k,n1,1) - tmpU(4,k,n2,1)
121     ENDIF
122     IF ( exch2_pi(1,2,n1).eq.1 ) THEN
123     WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'S edge, W:',
124     & n1,tmpV(1,k,n1,1), n3,tmpV(3,k,n3,1),
125     & tmpV(1,k,n1,1) - tmpV(3,k,n3,1)
126     WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'S edge, E:',
127     & n1,tmpV(2,k,n1,1), n3,tmpV(4,k,n3,1),
128     & tmpV(2,k,n1,1) - tmpV(4,k,n3,1)
129     ENDIF
130     IF ( exch2_pi(2,2,n1).eq.-1 ) THEN
131     WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'S edge, W:',
132     & n1,tmpV(1,k,n1,1), n3,tmpU(4,k,n3,1),
133     & tmpV(1,k,n1,1) - tmpU(4,k,n3,1)
134     WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'S edge, E:',
135     & n1,tmpV(2,k,n1,1), n3,tmpU(3,k,n3,1),
136     & tmpV(2,k,n1,1) - tmpU(3,k,n3,1)
137     ENDIF
138     #else /* ALLOW_EXCH2 */
139     n1 = n
140 jmc 1.1 IF (MOD(n1,2).EQ.1 ) THEN
141     c n1=1 n2=5,+v,-
142     c n1=1 n3=6,+v,+
143     c n1=3 n2=1,+v,-
144     c n1=3 n3=2,+v,+
145     c n1=5 n2=3,+v,-
146     c n1=5 n3=4,+v,+
147     n2=1+mod(n1-2+5,6)
148     n3=1+mod(n1-1+5,6)
149     WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'W edge, S:',
150     & n1,tmpU(1,k,n1,1), n2,tmpV(4,k,n2,1),
151     & tmpU(1,k,n1,1) - tmpV(4,k,n2,1)
152     WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'W edge, N:',
153     & n1,tmpU(2,k,n1,1), n2,tmpV(3,k,n2,1),
154     & tmpU(2,k,n1,1) - tmpV(3,k,n2,1)
155     WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'S edge, W:',
156     & n1,tmpV(1,k,n1,1), n3,tmpV(3,k,n3,1),
157     & tmpV(1,k,n1,1) - tmpV(3,k,n3,1)
158     WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'S edge, E:',
159     & n1,tmpV(2,k,n1,1), n3,tmpV(4,k,n3,1),
160     & tmpV(2,k,n1,1) - tmpV(4,k,n3,1)
161     ELSE
162     c n1=2 n2=1,+u,+
163     c n1=2 n3=6,+u,-
164     c n1=4 n2=3,+u,+
165     c n1=4 n3=2,+u,-
166     c n1=6 n2=5,+u,+
167     c n1=6 n3=4,+u,-
168     n2=1+mod(n1-1+5,6)
169     n3=1+mod(n1-2+5,6)
170     WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'W edge, S:',
171     & n1,tmpU(1,k,n1,1), n2,tmpU(3,k,n2,1),
172     & tmpU(1,k,n1,1) - tmpU(3,k,n2,1)
173     WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'W edge, N:',
174     & n1,tmpU(2,k,n1,1), n2,tmpU(4,k,n2,1),
175     & tmpU(2,k,n1,1) - tmpU(4,k,n2,1)
176     WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'S edge, W:',
177     & n1,tmpV(1,k,n1,1), n3,tmpU(4,k,n3,1),
178     & tmpV(1,k,n1,1) - tmpU(4,k,n3,1)
179     WRITE(ioUnit,1010) 'DEBUG_CS_CORNER_UV: ', 'S edge, E:',
180     & n1,tmpV(2,k,n1,1), n3,tmpU(3,k,n3,1),
181     & tmpV(2,k,n1,1) - tmpU(3,k,n3,1)
182     ENDIF
183 jmc 1.3 #endif /* ALLOW_EXCH2 */
184 jmc 1.1 ENDDO
185     WRITE(ioUnit,'(2A)') 'DEBUG_CS_CORNER_UV: ',
186     & '------------------------------------------------------------'
187     ENDIF
188     c ENDIF
189    
190 jmc 1.3 #endif /* ALLOW_DEBUG */
191 jmc 1.1
192     RETURN
193     END

  ViewVC Help
Powered by ViewVC 1.1.22