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

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

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


Revision 1.6 - (show annotations) (download)
Mon Mar 8 21:20:03 2004 UTC (20 years, 3 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint52l_pre, checkpoint52l_post, hrcube5
Changes since 1.5: +5 -5 lines
Renamed "USE_W2" to "ALLOW_EXCH2" so that it is no longer necessary to edit
CPP_EEOPTION.h as well as packages.conf to turn on/off exch2.
 - you can control the use of exch2 through packages.conf or -enable/disable.
 + need to add a run-time flag for this

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

  ViewVC Help
Powered by ViewVC 1.1.22