/[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.7 - (show annotations) (download)
Mon Mar 15 01:37:23 2004 UTC (20 years, 3 months ago) by cnh
Branch: MAIN
Changes since 1.6: +2 -1 lines
o Fixes for ALLOW_EXCH2 as a packages_conf entry.

o Validation configurations for testing a variety of cube tilings including
  tiles that are left out over land. This second set of items needs
  mods to genmake2 to be automatically included in regression tests - until
  then it can be tested by hand. The file
  verification/global_ocean.cs32x15/code_alt/README
  shows how to do this manually with genmake2

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

  ViewVC Help
Powered by ViewVC 1.1.22