/[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.3 by adcroft, Mon Jun 4 14:25:53 2001 UTC revision 1.12 by edhill, Sat Apr 3 04:57:11 2004 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                myThid )       I     myIter, myThid )
 C     /==========================================================\  
 C     | SUBROUTINE MON_KE                                        |  
 C     | o Calculates stats for Kinetic energy                    |  
 C     |==========================================================|  
 C     \==========================================================/  
       IMPLICIT NONE  
13    
14  C     === Global data ===  C     !DESCRIPTION:
15    C     Calculates stats for Kinetic energy                    
16    
17    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"
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     === Routine arguments ===  C     !LOCAL VARIABLES:
       INTEGER myThid  
   
 C     === Local variables ====  
31        INTEGER bi,bj,I,J,K        INTEGER bi,bj,I,J,K
32        _RL tmpVal,theMax,theMean        _RL numPnts,theVol,tmpVal,tmpVol
33        INTEGER numPnts        _RL theMax,theMean,theVolMean,potEnMean
34    
35          numPnts=0.
36          theVol=0.
37        theMax=0.        theMax=0.
38        theMean=0.        theMean=0.
39        numPnts=0        theVolMean=0.
40          potEnMean =0.
41    
42        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
43         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
44          DO K=1,Nr          DO K=1,Nr
45           DO J=1,sNy           DO J=1,sNy
46            DO I=1,sNx            DO I=1,sNx
47             tmpVal=0.25*( uVel( I , J ,K,bi,bj)*uVel( I , J ,K,bi,bj)             theVol=theVol+rA(i,j,bi,bj)*drF(k)*hFacC(i,j,k,bi,bj)
48       &                  +uVel(I+1, J ,K,bi,bj)*uVel(I+1, J ,K,bi,bj)  
49       &                  +vVel( I , J ,K,bi,bj)*vVel( I , J ,K,bi,bj)  C- Vector Invariant form (like in pkg/mom_vecinv/mom_vi_calc_ke.F)
50       &                  +vVel( I ,J+1,K,bi,bj)*vVel( I ,J+1,K,bi,bj) )  c          tmpVal=0.25*( uVel( I , J ,K,bi,bj)*uVel( I , J ,K,bi,bj)
51    c    &                  +uVel(I+1, J ,K,bi,bj)*uVel(I+1, J ,K,bi,bj)
52    c    &                  +vVel( I , J ,K,bi,bj)*vVel( I , J ,K,bi,bj)
53    c    &                  +vVel( I ,J+1,K,bi,bj)*vVel( I ,J+1,K,bi,bj) )
54    c          theVolMean=theVolMean+tmpVal
55    c    &           *ra(i,j,bi,bj)*drf(k)*hFacC(i,j,k,bi,bj)
56    
57    C- Energy conservative form (like in pkg/mom_fluxform/mom_calc_ke.F)
58    C    this is the safe way to check the energy conservation
59    C    with no assumption on how grid spacing & area are defined.
60               tmpVal=0.25*(
61         &       uVel( i ,j,k,bi,bj)*uVel( i ,j,k,bi,bj)
62         &         *dyG( i ,j,bi,bj)*dxC( i ,j,bi,bj)*hFacW( i ,j,k,bi,bj)
63         &      +uVel(i+1,j,k,bi,bj)*uVel(i+1,j,k,bi,bj)
64         &         *dyG(i+1,j,bi,bj)*dxC(i+1,j,bi,bj)*hFacW(i+1,j,k,bi,bj)
65         &      +vVel(i, j ,k,bi,bj)*vVel(i, j ,k,bi,bj)
66         &         *dxG(i, j ,bi,bj)*dyC(i, j ,bi,bj)*hFacS(i, j ,k,bi,bj)
67         &      +vVel(i,j+1,k,bi,bj)*vVel(i,j+1,k,bi,bj)
68         &         *dxG(i,j+1,bi,bj)*dyC(i,j+1,bi,bj)*hFacS(i,j+1,k,bi,bj)
69         &        )
70               theVolMean= theVolMean + tmpVal*drF(k)
71               tmpVal= tmpVal*recip_hFacC(i,j,k,bi,bj)*recip_rA(i,j,bi,bj)
72    
73             theMax=max(theMax,tmpVal)             theMax=max(theMax,tmpVal)
74             IF (tmpVal.NE.0.) THEN             IF (tmpVal.NE.0.) THEN
75              theMean=theMean+tmpVal              theMean=theMean+tmpVal
76              numPnts=numPnts+1              numPnts=numPnts+1.
77             ENDIF             ENDIF
78    
79            ENDDO            ENDDO
80           ENDDO           ENDDO
81          ENDDO          ENDDO
82    C- Potential Energy (external mode):
83             DO J=1,sNy
84              DO I=1,sNx
85               tmpVal = 0.5 _d 0*Bo_surf(i,j,bi,bj)
86         &                      *etaN(i,j,bi,bj)*etaN(i,j,bi,bj)
87    C- jmc: if geoid not flat (phi0surf), needs to add this term.
88    C       not sure for atmos/ocean in P ; or atmos. loading in ocean-Z
89               tmpVal = tmpVal
90         &            + phi0surf(i,j,bi,bj)*etaN(i,j,bi,bj)
91               potEnMean = potEnMean
92         &               + tmpVal*rA(i,j,bi,bj)*maskH(i,j,bi,bj)
93    c          tmpVal = etaN(i,j,bi,bj)
94    c    &            + phi0surf(i,j,bi,bj)*recip_Bo(i,j,bi,bj)
95    c          potEnMean = potEnMean
96    c    &        + 0.5 _d 0*Bo_surf(i,j,bi,bj)*tmpVal*tmpVal
97    c    &                  *rA(i,j,bi,bj)*maskH(i,j,bi,bj)
98              ENDDO
99             ENDDO
100    C- end bi,bj loops
101         ENDDO         ENDDO
102        ENDDO        ENDDO
103          _GLOBAL_SUM_R8(numPnts,myThid)
104        _GLOBAL_MAX_R8(theMax,myThid)        _GLOBAL_MAX_R8(theMax,myThid)
105        _GLOBAL_SUM_R8(theMean,myThid)        _GLOBAL_SUM_R8(theMean,myThid)
106        tmpVal=float(numPnts)        IF (numPnts.NE.0.) theMean=theMean/numPnts
107        _GLOBAL_SUM_R8(tmpVal,myThid)        _GLOBAL_SUM_R8(theVol,myThid)
108        IF (tmpVal.NE.0.) theMean=theMean*tmpVal        _GLOBAL_SUM_R8(theVolMean,myThid)
109          _GLOBAL_SUM_R8(potEnMean, myThid)
110        _BEGIN_MASTER( myThid )        IF (theVol.NE.0.) THEN
111        WRITE(*,'(A,24x,A,1PE22.14)')          theVolMean=theVolMean/theVol
112       &      'MON_KE: ','  max=',theMax          potEnMean = potEnMean/theVol
113        WRITE(*,'(A,24x,A,1PE22.14)')        ENDIF
114       &      'MON_KE: ',' mean=',theMean  
115        _END_MASTER( )  C--   Print stats for (barotropic) Potential Energy:
116          CALL MON_SET_PREF('pe_b',myThid)
117          CALL MON_OUT_RL(mon_string_none,potEnMean,
118         &         mon_foot_mean,myThid)
119    
120    C--   Print stats for KE
121          CALL MON_SET_PREF('ke',myThid)
122          CALL MON_OUT_RL(mon_string_none,theMax,mon_foot_max,myThid)
123    c     CALL MON_OUT_RL(mon_string_none,theMean,mon_foot_mean,myThid)
124          CALL MON_OUT_RL(mon_string_none,theVolMean,
125         &         mon_foot_mean,myThid)
126          CALL MON_OUT_RL(mon_string_none,theVol,
127         &         mon_foot_vol,myThid)
128    
129        RETURN        RETURN
130        END        END
131    
132    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

Legend:
Removed from v.1.3  
changed lines
  Added in v.1.12

  ViewVC Help
Powered by ViewVC 1.1.22