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

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

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

revision 1.10 by jmc, Fri May 2 22:29:07 2003 UTC revision 1.19 by jmc, Mon Nov 30 03:58:22 2009 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4  #include "CPP_OPTIONS.h"  #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(        SUBROUTINE MON_KE(
12       I                  myIter, myThid )       I     myIter, myThid )
13  C     /==========================================================\  
14  C     | SUBROUTINE MON_KE                                        |  C     !DESCRIPTION:
15  C     | o Calculates stats for Kinetic energy                    |  C     Calculates stats for Kinetic energy
 C     |==========================================================|  
 C     \==========================================================/  
       IMPLICIT NONE  
16    
17  C     === Global data ===  C     !USES:
18          IMPLICIT NONE
19  #include "SIZE.h"  #include "SIZE.h"
20  #include "EEPARAMS.h"  #include "EEPARAMS.h"
21    #include "PARAMS.h"
22  #include "DYNVARS.h"  #include "DYNVARS.h"
23  #include "MONITOR.h"  #include "MONITOR.h"
24  #include "GRID.h"  #include "GRID.h"
25  #include "SURFACE.h"  #include "SURFACE.h"
26    
27  C     === Routine arguments ===  C     !INPUT PARAMETERS:
28        INTEGER myIter, myThid        INTEGER myIter, myThid
29    CEOP
30    
31  C     === Local variables ====  C     !LOCAL VARIABLES:
32        INTEGER bi,bj,I,J,K        INTEGER bi,bj,i,j,k,kp1
33        _RL numPnts,theVol,tmpVal,tmpVol        _RL numPnts,theVol,tmpVal, mskp1, msk_1
34        _RL theMax,theMean,theVolMean,potEnMean        _RL theMax,theMean,theVolMean,potEnMean
35          _RL tileMean(nSx,nSy)
36          _RL tileVlAv(nSx,nSy)
37          _RL tilePEav(nSx,nSy)
38          _RL tileVol (nSx,nSy)
39    #ifdef ALLOW_NONHYDROSTATIC
40          _RL tmpWke
41    #endif
42    
43        numPnts=0.        numPnts=0.
44        theVol=0.        theVol=0.
# Line 37  C     === Local variables ==== Line 49  C     === Local variables ====
49    
50        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
51         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
52          DO K=1,Nr          tileVol(bi,bj)  = 0. _d 0
53           DO J=1,sNy          tileMean(bi,bj) = 0. _d 0
54            DO I=1,sNx          tileVlAv(bi,bj) = 0. _d 0
55             theVol=theVol+rA(i,j,bi,bj)*drF(k)*hFacC(i,j,k,bi,bj)          tilePEav(bi,bj) = 0. _d 0
56            DO k=1,Nr
57             kp1 = MIN(k+1,Nr)
58             mskp1 = 1.
59             IF ( k.GE.Nr ) mskp1 = 0.
60    C- Note: Present NH implementation does not account for D.w/dt at k=1.
61    C        Consequently, wVel(k=1) does not contribute to NH KE (msk_1=0).
62             msk_1 = 1.
63             IF ( k.EQ. 1 ) msk_1 = 0.
64             DO j=1,sNy
65              DO i=1,sNx
66               tileVol(bi,bj) = tileVol(bi,bj)
67         &                    + rA(i,j,bi,bj)*deepFac2C(k)
68         &                     *rhoFacC(k)*drF(k)*_hFacC(i,j,k,bi,bj)
69    
70  C- Vector Invariant form (like in pkg/mom_vecinv/mom_vi_calc_ke.F)  C- Vector Invariant form (like in pkg/mom_vecinv/mom_vi_calc_ke.F)
71  c          tmpVal=0.25*( uVel( I , J ,K,bi,bj)*uVel( I , J ,K,bi,bj)  c          tmpVal=0.25*( uVel( i , j ,k,bi,bj)*uVel( i , j ,k,bi,bj)
72  c    &                  +uVel(I+1, J ,K,bi,bj)*uVel(I+1, J ,K,bi,bj)  c    &                  +uVel(i+1, j ,k,bi,bj)*uVel(i+1, j ,k,bi,bj)
73  c    &                  +vVel( I , J ,K,bi,bj)*vVel( I , J ,K,bi,bj)  c    &                  +vVel( i , j ,k,bi,bj)*vVel( i , j ,k,bi,bj)
74  c    &                  +vVel( I ,J+1,K,bi,bj)*vVel( I ,J+1,K,bi,bj) )  c    &                  +vVel( i ,j+1,k,bi,bj)*vVel( i ,j+1,k,bi,bj) )
75  c          theVolMean=theVolMean+tmpVal  c          tileVlAv(bi,bj) = tileVlAv(bi,bj)
76  c    &           *ra(i,j,bi,bj)*drf(k)*hFacC(i,j,k,bi,bj)  c    &              +tmpVal*rA(i,j,bi,bj)*drF(k)*hFacC(i,j,k,bi,bj)
77    
78  C- Energy conservative form (like in pkg/mom_fluxform/mom_calc_ke.F)  C- Energy conservative form (like in pkg/mom_fluxform/mom_calc_ke.F)
79  C    this is the safe way to check the energy conservation  C    this is the safe way to check the energy conservation
80  C    with no assumption on how grid spacing & area are defined.  C    with no assumption on how grid spacing & area are defined.
81             tmpVal=0.25*(             tmpVal=0.25*(
82       &       uVel( i ,j,k,bi,bj)*uVel( i ,j,k,bi,bj)       &       uVel( i ,j,k,bi,bj)*uVel( i ,j,k,bi,bj)
83       &         *dyG( i ,j,bi,bj)*dxC( i ,j,bi,bj)*hFacW( i ,j,k,bi,bj)       &         *dyG( i ,j,bi,bj)*dxC( i ,j,bi,bj)*_hFacW( i ,j,k,bi,bj)
84       &      +uVel(i+1,j,k,bi,bj)*uVel(i+1,j,k,bi,bj)       &      +uVel(i+1,j,k,bi,bj)*uVel(i+1,j,k,bi,bj)
85       &         *dyG(i+1,j,bi,bj)*dxC(i+1,j,bi,bj)*hFacW(i+1,j,k,bi,bj)       &         *dyG(i+1,j,bi,bj)*dxC(i+1,j,bi,bj)*_hFacW(i+1,j,k,bi,bj)
86       &      +vVel(i, j ,k,bi,bj)*vVel(i, j ,k,bi,bj)       &      +vVel(i, j ,k,bi,bj)*vVel(i, j ,k,bi,bj)
87       &         *dxG(i, j ,bi,bj)*dyC(i, j ,bi,bj)*hFacS(i, j ,k,bi,bj)       &         *dxG(i, j ,bi,bj)*dyC(i, j ,bi,bj)*_hFacS(i, j ,k,bi,bj)
88       &      +vVel(i,j+1,k,bi,bj)*vVel(i,j+1,k,bi,bj)       &      +vVel(i,j+1,k,bi,bj)*vVel(i,j+1,k,bi,bj)
89       &         *dxG(i,j+1,bi,bj)*dyC(i,j+1,bi,bj)*hFacS(i,j+1,k,bi,bj)       &         *dxG(i,j+1,bi,bj)*dyC(i,j+1,bi,bj)*_hFacS(i,j+1,k,bi,bj)
90       &        )       &        )
91             theVolMean= theVolMean + tmpVal*drF(k)             tileVlAv(bi,bj) = tileVlAv(bi,bj)
92             tmpVal= tmpVal*recip_hFacC(i,j,k,bi,bj)*recip_rA(i,j,bi,bj)       &                     + tmpVal*deepFac2C(k)*rhoFacC(k)*drF(k)
93               tmpVal= tmpVal*_recip_hFacC(i,j,k,bi,bj)*recip_rA(i,j,bi,bj)
94    
95    #ifdef ALLOW_NONHYDROSTATIC
96               IF ( nonHydrostatic ) THEN
97                tmpWke = 0.25*
98         &        ( wVel(i,j, k, bi,bj)*wVel(i,j, k, bi,bj)*msk_1
99         &                             *deepFac2F( k )*rhoFacF( k )
100         &         +wVel(i,j,kp1,bi,bj)*wVel(i,j,kp1,bi,bj)*mskp1
101         &                             *deepFac2F(kp1)*rhoFacF(kp1)
102         &        )*maskC(i,j,k,bi,bj)
103                tileVlAv(bi,bj) = tileVlAv(bi,bj)
104         &             + tmpWke*rA(i,j,bi,bj)*drF(k)*_hFacC(i,j,k,bi,bj)
105                tmpVal = tmpVal
106         &             + tmpWke*recip_deepFac2C(k)*recip_rhoFacC(k)
107               ENDIF
108    #endif
109    
110             theMax=max(theMax,tmpVal)             theMax=MAX(theMax,tmpVal)
111             IF (tmpVal.NE.0.) THEN             IF (tmpVal.NE.0.) THEN
112              theMean=theMean+tmpVal              tileMean(bi,bj)=tileMean(bi,bj)+tmpVal
113              numPnts=numPnts+1.              numPnts=numPnts+1.
114             ENDIF             ENDIF
115    
# Line 76  C    with no assumption on how grid spac Line 117  C    with no assumption on how grid spac
117           ENDDO           ENDDO
118          ENDDO          ENDDO
119  C- Potential Energy (external mode):  C- Potential Energy (external mode):
120           DO J=1,sNy           DO j=1,sNy
121            DO I=1,sNx            DO i=1,sNx
122             tmpVal = 0.5 _d 0*Bo_surf(i,j,bi,bj)             tmpVal = 0.5 _d 0*Bo_surf(i,j,bi,bj)
123       &                      *etaN(i,j,bi,bj)*etaN(i,j,bi,bj)       &                      *etaN(i,j,bi,bj)*etaN(i,j,bi,bj)
124  C- jmc: if geoid not flat (phi0surf), needs to add this term.  C- jmc: if geoid not flat (phi0surf), needs to add this term.
125  C       not sure for atmos/ocean in P ; or atmos. loading in ocean-Z  C       not sure for atmos/ocean in P ; or atmos. loading in ocean-Z
126             tmpVal = tmpVal             tmpVal = tmpVal
127       &            + phi0surf(i,j,bi,bj)*etaN(i,j,bi,bj)       &            + phi0surf(i,j,bi,bj)*etaN(i,j,bi,bj)
128             potEnMean = potEnMean             tilePEav(bi,bj) = tilePEav(bi,bj)
129       &               + tmpVal*rA(i,j,bi,bj)*maskH(i,j,bi,bj)       &            + tmpVal*rA(i,j,bi,bj)*deepFac2F(1)*maskH(i,j,bi,bj)
130  c          tmpVal = etaN(i,j,bi,bj)  c          tmpVal = etaN(i,j,bi,bj)
131  c    &            + phi0surf(i,j,bi,bj)*recip_Bo(i,j,bi,bj)  c    &            + phi0surf(i,j,bi,bj)*recip_Bo(i,j,bi,bj)
132  c          potEnMean = potEnMean  c          tilePEav(bi,bj) = tilePEav(bi,bj)
133  c    &        + 0.5 _d 0*Bo_surf(i,j,bi,bj)*tmpVal*tmpVal  c    &        + 0.5 _d 0*Bo_surf(i,j,bi,bj)*tmpVal*tmpVal
134  c    &                  *rA(i,j,bi,bj)*maskH(i,j,bi,bj)  c    &                  *rA(i,j,bi,bj)*maskH(i,j,bi,bj)
135            ENDDO            ENDDO
136           ENDDO           ENDDO
137    c        theMean    = theMean    + tileMean(bi,bj)
138    c        theVol     = theVol     + tileVol(bi,bj)
139    c        theVolMean = theVolMean + tileVlAv(bi,bj)
140    c        potEnMean  = potEnMean  + tilePEav(bi,bj)
141  C- end bi,bj loops  C- end bi,bj loops
142         ENDDO         ENDDO
143        ENDDO        ENDDO
144        _GLOBAL_SUM_R8(numPnts,myThid)        _GLOBAL_SUM_RL(numPnts,myThid)
145        _GLOBAL_MAX_R8(theMax,myThid)        _GLOBAL_MAX_RL(theMax,myThid)
146        _GLOBAL_SUM_R8(theMean,myThid)  c     _GLOBAL_SUM_RL(theMean,myThid)
147    c     _GLOBAL_SUM_RL(theVol,myThid)
148    c     _GLOBAL_SUM_RL(theVolMean,myThid)
149    c     _GLOBAL_SUM_RL(potEnMean, myThid)
150          CALL GLOBAL_SUM_TILE_RL( tileMean, theMean   , myThid )
151          CALL GLOBAL_SUM_TILE_RL( tileVol , theVol    , myThid )
152          CALL GLOBAL_SUM_TILE_RL( tileVlAv, theVolMean, myThid )
153          CALL GLOBAL_SUM_TILE_RL( tilePEav, potEnMean , myThid )
154        IF (numPnts.NE.0.) theMean=theMean/numPnts        IF (numPnts.NE.0.) theMean=theMean/numPnts
       _GLOBAL_SUM_R8(theVol,myThid)  
       _GLOBAL_SUM_R8(theVolMean,myThid)  
       _GLOBAL_SUM_R8(potEnMean, myThid)  
155        IF (theVol.NE.0.) THEN        IF (theVol.NE.0.) THEN
156          theVolMean=theVolMean/theVol          theVolMean=theVolMean/theVol
157          potEnMean = potEnMean/theVol          potEnMean = potEnMean/theVol
# Line 124  c     CALL MON_OUT_RL(mon_string_none,th Line 173  c     CALL MON_OUT_RL(mon_string_none,th
173    
174        RETURN        RETURN
175        END        END
176    
177    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

Legend:
Removed from v.1.10  
changed lines
  Added in v.1.19

  ViewVC Help
Powered by ViewVC 1.1.22