/[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.11 by adcroft, Tue May 13 18:18:05 2003 UTC revision 1.13 by jmc, Thu Jan 27 16:38:22 2005 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "MONITOR_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 "DYNVARS.h"  #include "DYNVARS.h"
# Line 20  C     === Global data === Line 23  C     === Global data ===
23  #include "GRID.h"  #include "GRID.h"
24  #include "SURFACE.h"  #include "SURFACE.h"
25    
26  C     === Routine arguments ===  C     !INPUT PARAMETERS:
27        INTEGER myIter, myThid        INTEGER myIter, myThid
28    CEOP
29    
30  C     === Local variables ====  C     !LOCAL VARIABLES:
31        INTEGER bi,bj,I,J,K        INTEGER bi,bj,I,J,K
32        _RL numPnts,theVol,tmpVal,tmpVol        _RL numPnts,theVol,tmpVal,tmpVol
33        _RL theMax,theMean,theVolMean,potEnMean        _RL theMax,theMean,theVolMean,potEnMean
34          _RL meanTile, volMeanTile, potEnMnTile, volTile
35    
36        numPnts=0.        numPnts=0.
37        theVol=0.        theVol=0.
# Line 37  C     === Local variables ==== Line 42  C     === Local variables ====
42    
43        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
44         DO bi=myBxLo(myThid),myBxHi(myThid)         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          DO K=1,Nr
50           DO J=1,sNy           DO J=1,sNy
51            DO I=1,sNx            DO I=1,sNx
52             theVol=theVol+rA(i,j,bi,bj)*drF(k)*hFacC(i,j,k,bi,bj)             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)  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)  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)  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)  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) )  c    &                  +vVel( I ,J+1,K,bi,bj)*vVel( I ,J+1,K,bi,bj) )
59  c          theVolMean=theVolMean+tmpVal  c          volMeanTile=volMeanTile+tmpVal
60  c    &           *ra(i,j,bi,bj)*drf(k)*hFacC(i,j,k,bi,bj)  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)  C- Energy conservative form (like in pkg/mom_fluxform/mom_calc_ke.F)
# Line 63  C    with no assumption on how grid spac Line 72  C    with no assumption on how grid spac
72       &      +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)
73       &         *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)
74       &        )       &        )
75             theVolMean= theVolMean + tmpVal*drF(k)             volMeanTile= volMeanTile + tmpVal*drF(k)
76             tmpVal= tmpVal*recip_hFacC(i,j,k,bi,bj)*recip_rA(i,j,bi,bj)             tmpVal= tmpVal*recip_hFacC(i,j,k,bi,bj)*recip_rA(i,j,bi,bj)
77    
78             theMax=max(theMax,tmpVal)             theMax=max(theMax,tmpVal)
79             IF (tmpVal.NE.0.) THEN             IF (tmpVal.NE.0.) THEN
80              theMean=theMean+tmpVal              meanTile=meanTile+tmpVal
81              numPnts=numPnts+1.              numPnts=numPnts+1.
82             ENDIF             ENDIF
83    
# Line 84  C- jmc: if geoid not flat (phi0surf), ne Line 93  C- jmc: if geoid not flat (phi0surf), ne
93  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
94             tmpVal = tmpVal             tmpVal = tmpVal
95       &            + phi0surf(i,j,bi,bj)*etaN(i,j,bi,bj)       &            + phi0surf(i,j,bi,bj)*etaN(i,j,bi,bj)
96             potEnMean = potEnMean             potEnMnTile = potEnMnTile
97       &               + tmpVal*rA(i,j,bi,bj)*maskH(i,j,bi,bj)       &               + tmpVal*rA(i,j,bi,bj)*maskH(i,j,bi,bj)
98  c          tmpVal = etaN(i,j,bi,bj)  c          tmpVal = etaN(i,j,bi,bj)
99  c    &            + phi0surf(i,j,bi,bj)*recip_Bo(i,j,bi,bj)  c    &            + phi0surf(i,j,bi,bj)*recip_Bo(i,j,bi,bj)
100  c          potEnMean = potEnMean  c          potEnMnTile = potEnMnTile
101  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
102  c    &                  *rA(i,j,bi,bj)*maskH(i,j,bi,bj)  c    &                  *rA(i,j,bi,bj)*maskH(i,j,bi,bj)
103            ENDDO            ENDDO
104           ENDDO           ENDDO
105             theMean    = theMean    + meanTile
106             theVol     = theVol     + volTile
107             theVolMean = theVolMean + volMeanTile
108             potEnMean  = potEnMean  + potEnMnTile
109  C- end bi,bj loops  C- end bi,bj loops
110         ENDDO         ENDDO
111        ENDDO        ENDDO
# Line 124  c     CALL MON_OUT_RL(mon_string_none,th Line 137  c     CALL MON_OUT_RL(mon_string_none,th
137    
138        RETURN        RETURN
139        END        END
140    
141    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

Legend:
Removed from v.1.11  
changed lines
  Added in v.1.13

  ViewVC Help
Powered by ViewVC 1.1.22