/[MITgcm]/MITgcm/pkg/monitor/mon_vort3.F
ViewVC logotype

Annotation of /MITgcm/pkg/monitor/mon_vort3.F

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


Revision 1.11 - (hide annotations) (download)
Sat Nov 5 01:01:51 2005 UTC (18 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58e_post, mitgcm_mapl_00, checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint57y_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint57y_pre, checkpoint58q_post, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59h, checkpoint59, checkpoint58, checkpoint58f_post, checkpoint57x_post, checkpoint58d_post, checkpoint58c_post, checkpoint58a_post, checkpoint58i_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint58b_post, checkpoint58m_post
Changes since 1.10: +5 -2 lines
remove unused variables (reduces number of compiler warnings)

1 jmc 1.11 C $Header: /u/gcmpack/MITgcm/pkg/monitor/mon_vort3.F,v 1.10 2005/04/27 14:10:06 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4 adcroft 1.2 #include "MONITOR_OPTIONS.h"
5 jmc 1.1
6 edhill 1.8 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7     CBOP
8     C !ROUTINE: MON_VORT3
9    
10     C !INTERFACE:
11 jmc 1.1 SUBROUTINE MON_VORT3(
12 edhill 1.8 I myIter, myThid )
13    
14     C !DESCRIPTION:
15     C Calculates stats for Vorticity (z-component).
16    
17     C !USES:
18 jmc 1.1 IMPLICIT NONE
19     #include "SIZE.h"
20     #include "EEPARAMS.h"
21     #include "PARAMS.h"
22     #include "DYNVARS.h"
23     #include "MONITOR.h"
24     #include "GRID.h"
25 adcroft 1.6 #ifdef ALLOW_EXCH2
26 afe 1.3 #include "W2_EXCH2_TOPOLOGY.h"
27     #include "W2_EXCH2_PARAMS.h"
28 adcroft 1.6 #endif /* ALLOW_EXCH2 */
29 jmc 1.1
30 edhill 1.8 C !INPUT PARAMETERS:
31 jmc 1.1 INTEGER myIter, myThid
32 edhill 1.8 CEOP
33 jmc 1.1
34 edhill 1.8 C !LOCAL VARIABLES:
35 jmc 1.1 INTEGER bi,bj,i,j,k
36     INTEGER iMax,jMax
37 jmc 1.9 _RL theVol, theArea, tmpVal, tmpAre, tmpVol
38 jmc 1.1 _RL theMin, theMax, theMean, theVar, volMean, volVar, theSD
39 jmc 1.9 _RL areaTile, volTile, sumTile, sqsTile, vSumTile, vSqsTile
40 jmc 1.1 _RL vort3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
41     _RS hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
42     _RL AZcorner
43     #ifdef MONITOR_TEST_HFACZ
44     _RL tmpFac
45     _RL etaFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
46     #endif
47 jmc 1.5 LOGICAL northWestCorner, northEastCorner
48     LOGICAL southWestCorner, southEastCorner
49 jmc 1.11 INTEGER iG
50     #ifdef ALLOW_EXCH2
51     INTEGER myTile
52     #endif
53 jmc 1.1
54     theMin = 1. _d 20
55     theMax =-1. _d 20
56     theArea= 0. _d 0
57     theMean= 0. _d 0
58     theVar = 0. _d 0
59     theVol = 0. _d 0
60     volMean= 0. _d 0
61     volVar = 0. _d 0
62     theSD = 0. _d 0
63     AZcorner = 1. _d 0
64    
65     DO bj=myByLo(myThid),myByHi(myThid)
66     DO bi=myBxLo(myThid),myBxHi(myThid)
67 jmc 1.9 areaTile= 0. _d 0
68     volTile = 0. _d 0
69     sumTile = 0. _d 0
70     sqsTile = 0. _d 0
71     vSumTile= 0. _d 0
72     vSqsTile= 0. _d 0
73 jmc 1.1 #ifdef MONITOR_TEST_HFACZ
74     tmpFac = 0.
75     IF( implicDiv2Dflow.GT.0 .AND. abEps.GT.-0.5 )
76     & tmpFac = (0.5+abEps) / implicDiv2Dflow
77     DO j=1-Oly,sNy+Oly
78     DO i=1-Olx,sNx+Olx
79     etaFld(i,j) = etaH(i,j,bi,bj)
80     & + tmpFac*(etaN(i,j,bi,bj)-etaH(i,j,bi,bj))
81     ENDDO
82     ENDDO
83     #endif
84     DO k=1,Nr
85    
86     iMax = sNx
87     jMax = sNy
88     DO j=1,sNy
89     DO i=1,sNx
90     #ifdef MONITOR_TEST_HFACZ
91     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
92     C- Test various definitions of hFacZ (for 1 layer, flat bottom ocean):
93     c hFacZ(i,j) = 1. +
94     c & 0.25 _d 0*( etaFld(i-1,j-1)
95     c & + etaFld( i ,j-1)
96     c & + etaFld(i-1, j )
97     c & + etaFld( i , j )
98     c & )*recip_drF(k)
99     c hFacZ(i,j) = 1. +
100     c & 0.25 _d 0*( etaFld(i-1,j-1)*rA(i-1,j-1,bi,bj)
101     c & + etaFld( i ,j-1)*rA( i ,j-1,bi,bj)
102     c & + etaFld(i-1, j )*rA(i-1, j ,bi,bj)
103     c & + etaFld( i , j )*rA( i , j ,bi,bj)
104     c & )*recip_drF(k)*recip_rAz(i,j,bi,bj)
105     hFacZ(i,j) = 1. + 0.125 _d 0*
106     & ( ( etaFld(i-1,j-1)*rA(i-1,j-1,bi,bj)
107     & +etaFld( i ,j-1)*rA( i ,j-1,bi,bj)
108     & )*recip_rAw(i,j-1,bi,bj)
109     & + ( etaFld(i-1, j )*rA(i-1, j ,bi,bj)
110     & +etaFld( i , j )*rA( i , j ,bi,bj)
111     & )*recip_rAw(i, j ,bi,bj)
112     & + ( etaFld(i-1,j-1)*rA(i-1,j-1,bi,bj)
113     & +etaFld(i-1, j )*rA(i-1, j ,bi,bj)
114     & )*recip_rAs(i-1,j,bi,bj)
115     & + ( etaFld( i ,j-1)*rA( i ,j-1,bi,bj)
116     & + etaFld( i , j )*rA( i , j ,bi,bj)
117     & )*recip_rAs( i ,j,bi,bj)
118     & )*recip_drF(k)
119     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
120     #else
121     C- Standard definition of hFac at vorticity point:
122     hFacZ(i,j) =
123     & 0.25 _d 0*( _hFacW(i,j-1,k,bi,bj)
124     & + _hFacW(i, j ,k,bi,bj)
125     & + _hFacS(i-1,j,k,bi,bj)
126     & + _hFacS( i ,j,k,bi,bj)
127     & )
128     #endif /* MONITOR_TEST_HFACZ */
129     vort3(i,j) = recip_rAz(i,j,bi,bj)*(
130     & vVel( i ,j,k,bi,bj)*dyC( i ,j,bi,bj)
131     & -vVel(i-1,j,k,bi,bj)*dyC(i-1,j,bi,bj)
132     & -uVel(i, j ,k,bi,bj)*dxC(i, j ,bi,bj)
133     & +uVel(i,j-1,k,bi,bj)*dxC(i,j-1,bi,bj)
134     & )
135     ENDDO
136     ENDDO
137    
138     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
139     C Special stuff for Cubed Sphere:
140     IF (useCubedSphereExchange) THEN
141     c AZcorner = 0.75 _d 0
142     iMax = sNx+1
143     jMax = sNy+1
144     DO i=1,iMax
145     hFacZ(i,jMax)=0.
146     vort3(i,jMax)=0.
147     ENDDO
148     DO j=1,jMax
149     hFacZ(iMax,j)=0.
150     vort3(iMax,j)=0.
151     ENDDO
152 jmc 1.5
153     southWestCorner = .TRUE.
154     southEastCorner = .TRUE.
155     northWestCorner = .TRUE.
156     northEastCorner = .TRUE.
157     iG = bi+(myXGlobalLo-1)/sNx
158 adcroft 1.6 #ifdef ALLOW_EXCH2
159 jmc 1.5 myTile = W2_myTileList(bi)
160     iG = exch2_myFace(myTile)
161     southWestCorner = exch2_isWedge(myTile).EQ.1
162     & .AND. exch2_isSedge(myTile).EQ.1
163     southEastCorner = exch2_isEedge(myTile).EQ.1
164     & .AND. exch2_isSedge(myTile).EQ.1
165     northEastCorner = exch2_isEedge(myTile).EQ.1
166     & .AND. exch2_isNedge(myTile).EQ.1
167     northWestCorner = exch2_isWedge(myTile).EQ.1
168     & .AND. exch2_isNedge(myTile).EQ.1
169 adcroft 1.6 #endif /* ALLOW_EXCH2 */
170 jmc 1.5
171     C-- avoid to count 3 times the same corner:
172     southEastCorner = southEastCorner .AND. iG.EQ.2
173     northWestCorner = northWestCorner .AND. iG.EQ.1
174     northEastCorner = .FALSE.
175    
176 afe 1.3 C-- S.W. corner:
177     IF ( southWestCorner ) THEN
178 jmc 1.1 i=1
179     j=1
180     vort3(i,j)=
181     & +recip_rAz(i,j,bi,bj)/AZcorner*(
182     & vVel(i,j,k,bi,bj)*dyC(i,j,bi,bj)
183     & -uVel(i,j,k,bi,bj)*dxC(i,j,bi,bj)
184     & +uVel(i,j-1,k,bi,bj)*dxC(i,j-1,bi,bj)
185     & )
186     hFacZ(i,j) = ( _hFacW(i,j-1,k,bi,bj)
187     & + _hFacW(i, j ,k,bi,bj)
188     & + _hFacS( i ,j,k,bi,bj)
189     & )/3. _d 0
190 afe 1.3 ENDIF
191     IF ( southEastCorner ) THEN
192 jmc 1.1 C-- S.E. corner:
193     i=iMax
194     j=1
195     vort3(I,J)=
196     & +recip_rAz(I,J,bi,bj)/AZcorner*(
197     & -vVel(i-1,j,k,bi,bj)*dyC(i-1,j,bi,bj)
198     & -uVel(i,j,k,bi,bj)*dxC(i,j,bi,bj)
199     & +uVel(i,j-1,k,bi,bj)*dxC(i,j-1,bi,bj)
200     & )
201     hFacZ(i,j) = ( _hFacW(i,j-1,k,bi,bj)
202     & + _hFacW(i, j ,k,bi,bj)
203     & + _hFacS(i-1,j,k,bi,bj)
204     & )/3. _d 0
205 afe 1.3 ENDIF
206     IF ( northWestCorner ) THEN
207 jmc 1.1 C-- N.W. corner:
208     i=1
209     j=jMax
210     vort3(i,j)=
211     & +recip_rAz(i,j,bi,bj)/AZcorner*(
212     & vVel(i,j,k,bi,bj)*dyC(i,j,bi,bj)
213     & -uVel(i,j,k,bi,bj)*dxC(i,j,bi,bj)
214     & +uVel(i,j-1,k,bi,bj)*dxC(i,j-1,bi,bj)
215     & )
216     hFacZ(i,j) = ( _hFacW(i,j-1,k,bi,bj)
217     & + _hFacW(i, j ,k,bi,bj)
218     & + _hFacS( i ,j,k,bi,bj)
219     & )/3. _d 0
220 afe 1.3 ENDIF
221     IF ( northEastCorner ) THEN
222 jmc 1.1 C-- N.E. corner:
223     i=iMax
224     j=jMax
225     vort3(i,j)=
226     & +recip_rAz(i,j,bi,bj)/AZcorner*(
227     & -vVel(i-1,j,k,bi,bj)*dyC(i-1,j,bi,bj)
228     & -uVel(i,j,k,bi,bj)*dxC(i,j,bi,bj)
229     & +uVel(i,j-1,k,bi,bj)*dxC(i,j-1,bi,bj)
230     & )
231     hFacZ(i,j) = ( _hFacW(i,j-1,k,bi,bj)
232     & + _hFacW(i, j ,k,bi,bj)
233     & + _hFacS(i-1,j,k,bi,bj)
234     & )/3. _d 0
235 afe 1.3 ENDIF
236 jmc 1.1 ENDIF
237    
238     C- Special stuff for North & South Poles, LatLon grid
239     IF ( usingSphericalPolarGrid ) THEN
240     IF (yG(1,sNy+1,bi,bj).EQ.90.) THEN
241     jMax = sNy+1
242     j = jMax
243     DO i=1,sNx
244     vort3(i,j) = 0.
245     vort3(1,j) = vort3(1,j)
246     & + uVel(i,j-1,k,bi,bj)*dxC(i,j-1,bi,bj)
247     hFacZ(i,j) = 0.
248     #ifndef MONITOR_TEST_HFACZ
249     hFacZ(1,j) = hFacZ(1,j) + _hFacW(i,j-1,k,bi,bj)
250     ENDDO
251     #else
252     hFacZ(1,j) = hFacZ(1,j) + etaFld(i,j-1)
253     ENDDO
254     hFacZ(1,j) = sNx + hFacZ(1,j)*recip_drF(k)
255     #endif
256     hFacZ(1,j) = hFacZ(1,j) / FLOAT(sNx)
257     vort3(1,j) = vort3(1,j)*recip_rAz(1,j,bi,bj)
258     ENDIF
259     IF (yG(1,1,bi,bj).EQ.-90.) THEN
260     j = 1
261     DO i=1,sNx
262     vort3(i,j) = 0.
263     vort3(1,j) = vort3(1,j)
264     & - uVel(i,j,k,bi,bj)*dxC(i,j,bi,bj)
265     hFacZ(i,j) = 0.
266     #ifndef MONITOR_TEST_HFACZ
267     hFacZ(1,j) = hFacZ(1,j) + _hFacW(i,j,k,bi,bj)
268     ENDDO
269     #else
270     hFacZ(1,j) = hFacZ(1,j) + etaFld(i,j)
271     ENDDO
272     hFacZ(1,j) = sNx + hFacZ(1,j)*recip_drF(k)
273     #endif
274     hFacZ(1,j) = hFacZ(1,j) / FLOAT(sNx)
275     vort3(1,j) = vort3(1,j)*recip_rAz(1,j,bi,bj)
276     ENDIF
277     ENDIF
278    
279     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
280    
281     DO J=1,jMax
282     DO I=1,iMax
283     IF (hFacZ(i,j).GT.0. _d 0) THEN
284     tmpVal = vort3(i,j)
285     tmpAre = rAz(i,j,bi,bj)*drF(k)
286     tmpVol = rAz(i,j,bi,bj)*drF(k)*hFacZ(i,j)
287 jmc 1.9 areaTile = areaTile + tmpAre
288 jmc 1.1 C- min,max of relative vorticity ("r")
289     theMin = MIN(theMin,tmpVal)
290     theMax = MAX(theMax,tmpVal)
291     C- average & std.dev of absolute vorticity ("a")
292     tmpVal = tmpVal + fCoriG(i,j,bi,bj)
293 jmc 1.9 sumTile = sumTile + tmpAre*tmpVal
294     sqsTile = sqsTile + tmpAre*tmpVal*tmpVal
295 jmc 1.1 C- average & std.dev of potential vorticity ("p")
296     tmpVal = tmpVal / hFacZ(i,j)
297 jmc 1.9 volTile = volTile + tmpVol
298     vSumTile = vSumTile + tmpVol*tmpVal
299     vSqsTile = vSqsTile + tmpVol*tmpVal*tmpVal
300 jmc 1.1 ENDIF
301     ENDDO
302     ENDDO
303    
304     ENDDO
305 jmc 1.9 theArea= theArea + areaTile
306     theVol = theVol + volTile
307     theMean= theMean + sumTile
308     theVar = theVar + sqsTile
309     volMean= volMean + vSumTile
310     volVar = volVar + vSqsTile
311 jmc 1.1 ENDDO
312     ENDDO
313    
314     theMin = -theMin
315     _GLOBAL_MAX_R8(theMin, myThid)
316     _GLOBAL_MAX_R8(theMax, myThid)
317     _GLOBAL_SUM_R8(theArea,myThid)
318     _GLOBAL_SUM_R8(theVol, myThid)
319     _GLOBAL_SUM_R8(theMean,myThid)
320     _GLOBAL_SUM_R8(theVar, myThid)
321     _GLOBAL_SUM_R8(volMean,myThid)
322     _GLOBAL_SUM_R8(volVar ,myThid)
323     theMin = -theMin
324     IF (theArea.GT.0.) THEN
325     theMean= theMean/theArea
326     theVar = theVar /theArea
327     theVar = theVar - theMean*theMean
328     c IF (theVar.GT.0.) theSD = SQRT(theVar)
329     IF (theVar.GT.0.) theVar = SQRT(theVar)
330     ENDIF
331     IF (theVol.GT.0.) THEN
332     volMean= volMean/theVol
333     volVar = volVar /theVol
334     volVar = volVar - volMean*volMean
335     IF (volVar.GT.0.) theSD = SQRT(volVar)
336     ENDIF
337    
338     C- Print stats for (relative/absolute) Vorticity AND Pot.Vort.
339     CALL MON_SET_PREF('vort',myThid)
340     CALL MON_OUT_RL(mon_string_none,theMin, '_r_min', myThid)
341     CALL MON_OUT_RL(mon_string_none,theMax, '_r_max', myThid)
342     CALL MON_OUT_RL(mon_string_none,theMean,'_a_mean', myThid)
343     CALL MON_OUT_RL(mon_string_none,theVar, '_a_sd', myThid)
344     CALL MON_OUT_RL(mon_string_none,volMean,'_p_mean', myThid)
345     CALL MON_OUT_RL(mon_string_none,theSD, '_p_sd', myThid)
346     c CALL MON_OUT_RL(mon_string_none,theVol,mon_foot_vol,myThid)
347    
348     RETURN
349     END

  ViewVC Help
Powered by ViewVC 1.1.22