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

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

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

revision 1.1 by adcroft, Wed May 30 19:33:18 2001 UTC revision 1.8 by adcroft, Thu Feb 19 21:02:39 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        SUBROUTINE MON_STATS_RL(        SUBROUTINE MON_STATS_RL(
7       I                myNr, arr,       I                myNr, arr, arrMask,arrhFac, arrArea, arrDr,
8       O                theMin,theMax,theMean,theSD,       O                theMin,theMax,theMean,theSD,theDel2,theVol,
9       I                myThid )       I                myThid )
10  C     /==========================================================\  C     /==========================================================\
11  C     | SUBROUTINE MON_STATS_RL                                  |  C     | SUBROUTINE MON_STATS_RL                                  |
# Line 21  C     === Global data === Line 21  C     === Global data ===
21  C     === Routine arguments ===  C     === Routine arguments ===
22        INTEGER myNr        INTEGER myNr
23        _RL arr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)        _RL arr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
24          _RS arrMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
25          _RS arrhFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
26          _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
27          _RS arrDr(myNr)
28        _RL theMin        _RL theMin
29        _RL theMax        _RL theMax
30        _RL theMean        _RL theMean,theMeanTile
31        _RL theSD        _RL theSD,theSDTile
32          _RL theDel2,theDel2Tile
33          _RL theVol,theVolTile
34        INTEGER myThid        INTEGER myThid
35    
36  C     === Local variables ====  C     === Local variables ====
# Line 32  C     === Local variables ==== Line 38  C     === Local variables ====
38        INTEGER numPnts        INTEGER numPnts
39        LOGICAL noPnts        LOGICAL noPnts
40        _RL tmpVal,rNumPnts        _RL tmpVal,rNumPnts
41        _RL theVar        _RL theVar,theVarTile
42          _RL tmpVol
43    
44        theMin=0.        theMin=0.
45        theMax=0.        theMax=0.
46        theMean=0.        theMean=0.
47        theSD=0.        theSD=0.
48        theVar=0.        theVar=0.
49          theDel2=0.
50          theVol=0.
51        numPnts=0        numPnts=0
52        noPnts=.TRUE.        noPnts=.TRUE.
53    
54        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
55         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
56            theDel2Tile = 0.
57            theVolTile = 0.
58            theMeanTile = 0.
59            theVarTile = 0.
60          DO K=1,myNr          DO K=1,myNr
61           DO J=1,sNy           DO J=1,sNy
62            DO I=1,sNx            DO I=1,sNx
63             tmpVal=arr(I,J,K,bi,bj)             tmpVal=arr(I,J,K,bi,bj)
64             IF (tmpVal.NE.0. .AND. noPnts) THEN  c          IF (tmpVal.NE.0. .AND. noPnts) THEN
65               IF (arrMask(I,J,K,bi,bj).NE.0. .AND. noPnts) THEN
66              theMin=tmpVal              theMin=tmpVal
67              theMax=tmpVal              theMax=tmpVal
68              noPnts=.FALSE.              noPnts=.FALSE.
69             ENDIF             ENDIF
70             IF (tmpVal.NE.0.) THEN  c          IF (tmpVal.NE.0.) THEN
71               IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
72              theMin=min(theMin,tmpVal)              theMin=min(theMin,tmpVal)
73              theMax=max(theMax,tmpVal)              theMax=max(theMax,tmpVal)
74              theMean=theMean+tmpVal              theDel2Tile = theDel2Tile+0.25*ABS(
75              theVar=theVar+tmpVal**2       &         (arr(I+1,J,K,bi,bj)-tmpVal)*arrMask(I+1,J,K,bi,bj)
76         &        +(arr(I-1,J,K,bi,bj)-tmpVal)*arrMask(I-1,J,K,bi,bj)
77         &        +(arr(I,J+1,K,bi,bj)-tmpVal)*arrMask(I,J+1,K,bi,bj)
78         &        +(arr(I,J-1,K,bi,bj)-tmpVal)*arrMask(I,J-1,K,bi,bj)
79         &                               )
80              numPnts=numPnts+1              numPnts=numPnts+1
81                tmpVol = arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
82         &                                 *arrMask(I,J,K,bi,bj)
83                theVolTile = theVolTile   + tmpVol
84                theMeanTile = theMeanTile + tmpVol*tmpVal
85                theVarTile = theVarTile   + tmpVol*tmpVal**2
86             ENDIF             ENDIF
87            ENDDO            ENDDO
88           ENDDO           ENDDO
89          ENDDO          ENDDO
90            theDel2 = theDel2 + theDel2Tile
91            theVol = theVol + theVolTile
92            theMean = theMean + theMeanTile
93            theVar = theVar + theVarTile
94         ENDDO         ENDDO
95        ENDDO        ENDDO
96    
# Line 70  C     === Local variables ==== Line 98  C     === Local variables ====
98        _GLOBAL_MAX_R8(theMin,myThid)        _GLOBAL_MAX_R8(theMin,myThid)
99        theMin=-theMin        theMin=-theMin
100        _GLOBAL_MAX_R8(theMax,myThid)        _GLOBAL_MAX_R8(theMax,myThid)
101          _GLOBAL_SUM_R8(theDel2,myThid)
102          _GLOBAL_SUM_R8(theVol,myThid)
103        _GLOBAL_SUM_R8(theMean,myThid)        _GLOBAL_SUM_R8(theMean,myThid)
104        _GLOBAL_SUM_R8(theVar,myThid)        _GLOBAL_SUM_R8(theVar,myThid)
105        tmpVal=FLOAT(numPnts)        tmpVal=FLOAT(numPnts)
# Line 78  C     === Local variables ==== Line 108  C     === Local variables ====
108    
109        IF (tmpVal.GT.0.) THEN        IF (tmpVal.GT.0.) THEN
110         rNumPnts=1./tmpVal         rNumPnts=1./tmpVal
111         theMean=theMean*rNumPnts         theDel2=theDel2*rNumPnts
112         theVar=theVar*rNumPnts        ENDIF
113    
114          IF (theVol.GT.0.) THEN
115           theMean=theMean/theVol
116           theVar=theVar/theVol
117    
118         DO bj=myByLo(myThid),myByHi(myThid)         DO bj=myByLo(myThid),myByHi(myThid)
119          DO bi=myBxLo(myThid),myBxHi(myThid)          DO bi=myBxLo(myThid),myBxHi(myThid)
120             theSDtile=0.
121           DO K=1,myNr           DO K=1,myNr
122            DO J=1,sNy            DO J=1,sNy
123             DO I=1,sNx             DO I=1,sNx
124              tmpVal=arr(I,J,K,bi,bj)              tmpVal=arr(I,J,K,bi,bj)
125              IF (tmpVal.NE.0.) THEN  c           IF (tmpVal.NE.0.) THEN
126               theSD=theSD+(tmpVal-theMean)**2              IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
127                 tmpVol=arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
128         &                                *arrMask(I,J,K,bi,bj)
129                 theSDtile = theSDtile + tmpVol*(tmpVal-theMean)**2
130              ENDIF              ENDIF
131             ENDDO             ENDDO
132            ENDDO            ENDDO
133           ENDDO           ENDDO
134             theSD = theSD + theSDtile
135          ENDDO          ENDDO
136         ENDDO         ENDDO
137    
138         _GLOBAL_SUM_R8(theSD,myThid)         _GLOBAL_SUM_R8(theSD,myThid)
139    
140  c      theSD=sqrt(theSD*rNumPnts)         theSD=sqrt(theSD/theVol)
141         theSD=sqrt(theVar-theMean**2)  c      theSD=sqrt(theVar-theMean**2)
142        ENDIF        ENDIF
143    
144        RETURN        RETURN

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.8

  ViewVC Help
Powered by ViewVC 1.1.22