/[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.7 by adcroft, Fri Feb 6 19:59:36 2004 UTC revision 1.15 by jmc, Tue Jan 26 01:09:02 2010 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_STATS_RL
9    
10    C     !INTERFACE:
11        SUBROUTINE MON_STATS_RL(        SUBROUTINE MON_STATS_RL(
12       I                myNr, arr, arrMask,arrhFac, arrArea, arrDr,       I     myNr, arr, arrMask,arrhFac, arrArea, arrDr,
13       O                theMin,theMax,theMean,theSD,theDel2,theVol,       O     theMin,theMax,theMean,theSD,theDel2,theVol,
14       I                myThid )       I     myThid )
 C     /==========================================================\  
 C     | SUBROUTINE MON_STATS_RL                                  |  
 C     | o Calculate bare statistics of global array "_RL arr"    |  
 C     |==========================================================|  
 C     \==========================================================/  
       IMPLICIT NONE  
15    
16  C     === Global data ===  C     Calculate bare statistics of global array ``\_RL arr''.
17    
18    C     !USES:
19          IMPLICIT NONE
20  #include "SIZE.h"  #include "SIZE.h"
21  #include "EEPARAMS.h"  #include "EEPARAMS.h"
22    
23  C     === Routine arguments ===  C     !INPUT PARAMETERS:
24        INTEGER myNr        INTEGER myNr
25        _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)
26        _RS arrMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)        _RS arrMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
27        _RS arrhFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)        _RS arrhFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
28        _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)        _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
29        _RS arrDr(myNr)        _RS arrDr(myNr)
30        _RL theMin        _RL theMin, theMax, theMean, theSD, theDel2, theVol
       _RL theMax  
       _RL theMean,theMeanTile  
       _RL theSD,theSDTile  
       _RL theDel2,theDel2Tile  
       _RL theVol,theVolTile  
31        INTEGER myThid        INTEGER myThid
32    CEOP
33    
34  C     === Local variables ====  C     !LOCAL VARIABLES:
35        INTEGER bi,bj,I,J,K        INTEGER bi,bj,I,J,K
36        INTEGER numPnts        INTEGER numPnts
37        LOGICAL noPnts        LOGICAL noPnts
38        _RL tmpVal,rNumPnts        _RL tmpVal,rNumPnts
39        _RL theVar,theVarTile        _RL theVar
40        _RL tmpVol        _RL tmpVol
41          _RL tileMean(nSx,nSy)
42          _RL tileVar (nSx,nSy)
43          _RL tileSD  (nSx,nSy)
44          _RL tileDel2(nSx,nSy)
45          _RL tileVol (nSx,nSy)
46    
47    C     Since 2009/12/21 MON_CALC_STATS_RL replaces MON_STATS_RL
48    C     which is now disabled
49          STOP 'ABNORMAL END: S/R MON_STATS_RL no longer maintained'
50    
51        theMin=0.        theMin=0.
52        theMax=0.        theMax=0.
# Line 53  C     === Local variables ==== Line 60  C     === Local variables ====
60    
61        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
62         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
63          theDel2 = 0.          tileDel2(bi,bj) = 0.
64          theVol = 0.          tileVol (bi,bj) = 0.
65          theMean = 0.          tileMean(bi,bj) = 0.
66          theVar = 0.          tileVar (bi,bj) = 0.
67          DO K=1,myNr          DO K=1,myNr
68           DO J=1,sNy           DO J=1,sNy
69            DO I=1,sNx            DO I=1,sNx
70             tmpVal=arr(I,J,K,bi,bj)             tmpVal=arr(I,J,K,bi,bj)
 c          IF (tmpVal.NE.0. .AND. noPnts) THEN  
71             IF (arrMask(I,J,K,bi,bj).NE.0. .AND. noPnts) THEN             IF (arrMask(I,J,K,bi,bj).NE.0. .AND. noPnts) THEN
72              theMin=tmpVal              theMin=tmpVal
73              theMax=tmpVal              theMax=tmpVal
74              noPnts=.FALSE.              noPnts=.FALSE.
75             ENDIF             ENDIF
 c          IF (tmpVal.NE.0.) THEN  
76             IF (arrMask(I,J,K,bi,bj).NE.0.) THEN             IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
77              theMin=min(theMin,tmpVal)              theMin=min(theMin,tmpVal)
78              theMax=max(theMax,tmpVal)              theMax=max(theMax,tmpVal)
79              theDel2Tile = theDel2Tile+0.25*ABS(              tileDel2(bi,bj) = tileDel2(bi,bj)
80         &      + 0.25*ABS(
81       &         (arr(I+1,J,K,bi,bj)-tmpVal)*arrMask(I+1,J,K,bi,bj)       &         (arr(I+1,J,K,bi,bj)-tmpVal)*arrMask(I+1,J,K,bi,bj)
82       &        +(arr(I-1,J,K,bi,bj)-tmpVal)*arrMask(I-1,J,K,bi,bj)       &        +(arr(I-1,J,K,bi,bj)-tmpVal)*arrMask(I-1,J,K,bi,bj)
83       &        +(arr(I,J+1,K,bi,bj)-tmpVal)*arrMask(I,J+1,K,bi,bj)       &        +(arr(I,J+1,K,bi,bj)-tmpVal)*arrMask(I,J+1,K,bi,bj)
84       &        +(arr(I,J-1,K,bi,bj)-tmpVal)*arrMask(I,J-1,K,bi,bj)       &        +(arr(I,J-1,K,bi,bj)-tmpVal)*arrMask(I,J-1,K,bi,bj)
85       &                               )       &                )
86              numPnts=numPnts+1              numPnts=numPnts+1
87              tmpVol = arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)              tmpVol = arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
88       &                                 *arrMask(I,J,K,bi,bj)       &                                 *arrMask(I,J,K,bi,bj)
89              theVolTile = theVolTile   + tmpVol              tileVol (bi,bj) = tileVol (bi,bj) + tmpVol
90              theMeanTile = theMeanTile + tmpVol*tmpVal              tileMean(bi,bj) = tileMean(bi,bj) + tmpVol*tmpVal
91              theVarTile = theVarTile   + tmpVol*tmpVal**2              tileVar (bi,bj) = tileVar (bi,bj) + tmpVol*tmpVal*tmpVal
92             ENDIF             ENDIF
93            ENDDO            ENDDO
94           ENDDO           ENDDO
95          ENDDO          ENDDO
96          theDel2 = theDel2 + theDel2Tile  c       theDel2 = theDel2 + tileDel2(bi,bj)
97          theVol = theVol + theVolTile  c       theVol  = theVol  + tileVol(bi,bj)
98          theMean = theMean + theMeanTile  c       theMean = theMean + tileMean(bi,bj)
99          theVar = theVar + theVarTile  c       theVar  = theVar  + tileVar (bi,bj)
100         ENDDO         ENDDO
101        ENDDO        ENDDO
102    
103        theMin=-theMin  c     _GLOBAL_SUM_RL(theDel2,myThid)
104        _GLOBAL_MAX_R8(theMin,myThid)  c     _GLOBAL_SUM_RL(theVol,myThid)
105        theMin=-theMin  c     _GLOBAL_SUM_RL(theMean,myThid)
106        _GLOBAL_MAX_R8(theMax,myThid)  c     _GLOBAL_SUM_RL(theVar,myThid)
107        _GLOBAL_SUM_R8(theDel2,myThid)        CALL GLOBAL_SUM_TILE_RL( tileDel2, theDel2, myThid )
108        _GLOBAL_SUM_R8(theVol,myThid)        CALL GLOBAL_SUM_TILE_RL( tileVol , theVol , myThid )
109        _GLOBAL_SUM_R8(theMean,myThid)        CALL GLOBAL_SUM_TILE_RL( tileMean, theMean, myThid )
110        _GLOBAL_SUM_R8(theVar,myThid)        CALL GLOBAL_SUM_TILE_RL( tileVar , theVar , myThid )
111        tmpVal=FLOAT(numPnts)        tmpVal=FLOAT(numPnts)
112        _GLOBAL_SUM_R8(tmpVal,myThid)        _GLOBAL_SUM_RL(tmpVal,myThid)
113        numPnts=INT(tmpVal+0.5)        numPnts=NINT(tmpVal)
114    
115        IF (tmpVal.GT.0.) THEN        IF (tmpVal.GT.0.) THEN
116         rNumPnts=1./tmpVal         rNumPnts=1. _d 0/tmpVal
117         theDel2=theDel2*rNumPnts         theDel2=theDel2*rNumPnts
118        ENDIF        ENDIF
119    
120        IF (theVol.GT.0.) THEN        IF (theVol.GT.0.) THEN
121         theMean=theMean/theVol         theMean=theMean/theVol
122         theVar=theVar/theVol         theVar=theVar/theVol
123           IF ( noPnts ) theMin = theMean
124           theMin=-theMin
125           _GLOBAL_MAX_RL(theMin,myThid)
126           theMin=-theMin
127           IF ( noPnts ) theMax = theMean
128           _GLOBAL_MAX_RL(theMax,myThid)
129    
130         DO bj=myByLo(myThid),myByHi(myThid)         DO bj=myByLo(myThid),myByHi(myThid)
131          DO bi=myBxLo(myThid),myBxHi(myThid)          DO bi=myBxLo(myThid),myBxHi(myThid)
132           theSDtile=0.           tileSD(bi,bj)=0.
133           DO K=1,myNr           DO K=1,myNr
134            DO J=1,sNy            DO J=1,sNy
135             DO I=1,sNx             DO I=1,sNx
136              tmpVal=arr(I,J,K,bi,bj)              tmpVal=arr(I,J,K,bi,bj)
 c           IF (tmpVal.NE.0.) THEN  
137              IF (arrMask(I,J,K,bi,bj).NE.0.) THEN              IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
138               tmpVol=arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)               tmpVol=arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
139       &                                *arrMask(I,J,K,bi,bj)       &                                *arrMask(I,J,K,bi,bj)
140               theSDtile = theSDtile + tmpVol*(tmpVal-theMean)**2               tileSD(bi,bj) = tileSD(bi,bj)
141         &                     + tmpVol*(tmpVal-theMean)*(tmpVal-theMean)
142              ENDIF              ENDIF
143             ENDDO             ENDDO
144            ENDDO            ENDDO
145           ENDDO           ENDDO
146           theSD = theSD + theSDtile  c        theSD = theSD + tileSD(bi,bj)
147          ENDDO          ENDDO
148         ENDDO         ENDDO
149    
150         _GLOBAL_SUM_R8(theSD,myThid)  c      _GLOBAL_SUM_RL(theSD,myThid)
151           CALL GLOBAL_SUM_TILE_RL( tileSD, theSD, myThid )
152    
153         theSD=sqrt(theSD/theVol)         theSD = SQRT(theSD/theVol)
154  c      theSD=sqrt(theVar-theMean**2)  c      theSD = SQRT(theVar-theMean*theMean)
155        ENDIF        ENDIF
156    
157        RETURN        RETURN

Legend:
Removed from v.1.7  
changed lines
  Added in v.1.15

  ViewVC Help
Powered by ViewVC 1.1.22