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

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

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


Revision 1.15 - (show annotations) (download)
Wed Jun 7 01:55:15 2006 UTC (17 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint59, checkpoint58y_post, checkpoint58t_post, checkpoint58m_post, checkpoint58w_post, checkpoint58o_post, checkpoint58p_post, checkpoint58q_post, mitgcm_mapl_00, checkpoint58r_post, checkpoint58n_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59h, checkpoint58k_post, checkpoint58v_post, checkpoint58l_post, checkpoint58x_post, checkpoint58h_post, checkpoint58j_post, checkpoint58i_post, checkpoint58u_post, checkpoint58s_post
Changes since 1.14: +7 -7 lines
Modifications for bottom topography control
o replace hFacC by _hFacC at various places
o replace ALLOW_HFACC_CONTROL by ALLOW_DEPTH_CONTROL
o add non-self-adjoint cg2d_nsa
o update autodiff support routines
o re-initialise hfac after ctrl_depth_ini
o works for 5x5 box, doesnt work for global_ocean.90x40x15

1 C $Header: /u/gcmpack/MITgcm/pkg/monitor/mon_ke.F,v 1.14 2005/11/04 01:33:05 jmc Exp $
2 C $Name: $
3
4 #include "MONITOR_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP
8 C !ROUTINE: MON_KE
9
10 C !INTERFACE:
11 SUBROUTINE MON_KE(
12 I myIter, myThid )
13
14 C !DESCRIPTION:
15 C Calculates stats for Kinetic energy
16
17 C !USES:
18 IMPLICIT NONE
19 #include "SIZE.h"
20 #include "EEPARAMS.h"
21 #include "DYNVARS.h"
22 #include "MONITOR.h"
23 #include "GRID.h"
24 #include "SURFACE.h"
25
26 C !INPUT PARAMETERS:
27 INTEGER myIter, myThid
28 CEOP
29
30 C !LOCAL VARIABLES:
31 INTEGER bi,bj,I,J,K
32 _RL numPnts,theVol,tmpVal
33 _RL theMax,theMean,theVolMean,potEnMean
34 _RL meanTile, volMeanTile, potEnMnTile, volTile
35
36 numPnts=0.
37 theVol=0.
38 theMax=0.
39 theMean=0.
40 theVolMean=0.
41 potEnMean =0.
42
43 DO bj=myByLo(myThid),myByHi(myThid)
44 DO bi=myBxLo(myThid),myBxHi(myThid)
45 volTile = 0. _d 0
46 meanTile = 0. _d 0
47 volMeanTile = 0. _d 0
48 potEnMnTile = 0. _d 0
49 DO K=1,Nr
50 DO J=1,sNy
51 DO I=1,sNx
52 volTile=volTile+rA(i,j,bi,bj)*drF(k)*_hFacC(i,j,k,bi,bj)
53
54 C- Vector Invariant form (like in pkg/mom_vecinv/mom_vi_calc_ke.F)
55 c tmpVal=0.25*( uVel( I , J ,K,bi,bj)*uVel( I , J ,K,bi,bj)
56 c & +uVel(I+1, J ,K,bi,bj)*uVel(I+1, J ,K,bi,bj)
57 c & +vVel( I , J ,K,bi,bj)*vVel( I , J ,K,bi,bj)
58 c & +vVel( I ,J+1,K,bi,bj)*vVel( I ,J+1,K,bi,bj) )
59 c volMeanTile=volMeanTile+tmpVal
60 c & *ra(i,j,bi,bj)*drf(k)*hFacC(i,j,k,bi,bj)
61
62 C- Energy conservative form (like in pkg/mom_fluxform/mom_calc_ke.F)
63 C this is the safe way to check the energy conservation
64 C with no assumption on how grid spacing & area are defined.
65 tmpVal=0.25*(
66 & uVel( i ,j,k,bi,bj)*uVel( i ,j,k,bi,bj)
67 & *dyG( i ,j,bi,bj)*dxC( i ,j,bi,bj)*_hFacW( i ,j,k,bi,bj)
68 & +uVel(i+1,j,k,bi,bj)*uVel(i+1,j,k,bi,bj)
69 & *dyG(i+1,j,bi,bj)*dxC(i+1,j,bi,bj)*_hFacW(i+1,j,k,bi,bj)
70 & +vVel(i, j ,k,bi,bj)*vVel(i, j ,k,bi,bj)
71 & *dxG(i, j ,bi,bj)*dyC(i, j ,bi,bj)*_hFacS(i, j ,k,bi,bj)
72 & +vVel(i,j+1,k,bi,bj)*vVel(i,j+1,k,bi,bj)
73 & *dxG(i,j+1,bi,bj)*dyC(i,j+1,bi,bj)*_hFacS(i,j+1,k,bi,bj)
74 & )
75 volMeanTile= volMeanTile + tmpVal*drF(k)
76 tmpVal= tmpVal*_recip_hFacC(i,j,k,bi,bj)*recip_rA(i,j,bi,bj)
77
78 theMax=max(theMax,tmpVal)
79 IF (tmpVal.NE.0.) THEN
80 meanTile=meanTile+tmpVal
81 numPnts=numPnts+1.
82 ENDIF
83
84 ENDDO
85 ENDDO
86 ENDDO
87 C- Potential Energy (external mode):
88 DO J=1,sNy
89 DO I=1,sNx
90 tmpVal = 0.5 _d 0*Bo_surf(i,j,bi,bj)
91 & *etaN(i,j,bi,bj)*etaN(i,j,bi,bj)
92 C- jmc: if geoid not flat (phi0surf), needs to add this term.
93 C not sure for atmos/ocean in P ; or atmos. loading in ocean-Z
94 tmpVal = tmpVal
95 & + phi0surf(i,j,bi,bj)*etaN(i,j,bi,bj)
96 potEnMnTile = potEnMnTile
97 & + tmpVal*rA(i,j,bi,bj)*maskH(i,j,bi,bj)
98 c tmpVal = etaN(i,j,bi,bj)
99 c & + phi0surf(i,j,bi,bj)*recip_Bo(i,j,bi,bj)
100 c potEnMnTile = potEnMnTile
101 c & + 0.5 _d 0*Bo_surf(i,j,bi,bj)*tmpVal*tmpVal
102 c & *rA(i,j,bi,bj)*maskH(i,j,bi,bj)
103 ENDDO
104 ENDDO
105 theMean = theMean + meanTile
106 theVol = theVol + volTile
107 theVolMean = theVolMean + volMeanTile
108 potEnMean = potEnMean + potEnMnTile
109 C- end bi,bj loops
110 ENDDO
111 ENDDO
112 _GLOBAL_SUM_R8(numPnts,myThid)
113 _GLOBAL_MAX_R8(theMax,myThid)
114 _GLOBAL_SUM_R8(theMean,myThid)
115 IF (numPnts.NE.0.) theMean=theMean/numPnts
116 _GLOBAL_SUM_R8(theVol,myThid)
117 _GLOBAL_SUM_R8(theVolMean,myThid)
118 _GLOBAL_SUM_R8(potEnMean, myThid)
119 IF (theVol.NE.0.) THEN
120 theVolMean=theVolMean/theVol
121 potEnMean = potEnMean/theVol
122 ENDIF
123
124 C-- Print stats for (barotropic) Potential Energy:
125 CALL MON_SET_PREF('pe_b',myThid)
126 CALL MON_OUT_RL(mon_string_none,potEnMean,
127 & mon_foot_mean,myThid)
128
129 C-- Print stats for KE
130 CALL MON_SET_PREF('ke',myThid)
131 CALL MON_OUT_RL(mon_string_none,theMax,mon_foot_max,myThid)
132 c CALL MON_OUT_RL(mon_string_none,theMean,mon_foot_mean,myThid)
133 CALL MON_OUT_RL(mon_string_none,theVolMean,
134 & mon_foot_mean,myThid)
135 CALL MON_OUT_RL(mon_string_none,theVol,
136 & mon_foot_vol,myThid)
137
138 RETURN
139 END
140
141 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22