/[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.14 by jmc, Sat Jan 16 22:27:19 2010 UTC revision 1.15 by jmc, Tue Jan 26 01:09:02 2010 UTC
# Line 9  C     !ROUTINE: MON_STATS_RL Line 9  C     !ROUTINE: MON_STATS_RL
9    
10  C     !INTERFACE:  C     !INTERFACE:
11        SUBROUTINE MON_STATS_RL(        SUBROUTINE MON_STATS_RL(
12       I     myNr, arr,       I     myNr, arr, arrMask,arrhFac, arrArea, arrDr,
13       O     theMin,theMax,theMean,theSD,       O     theMin,theMax,theMean,theSD,theDel2,theVol,
14       I     myThid )       I     myThid )
15    
 C     !DESCRIPTION:  
16  C     Calculate bare statistics of global array ``\_RL arr''.  C     Calculate bare statistics of global array ``\_RL arr''.
17    
18  C     !USES:  C     !USES:
# Line 24  C     !USES: Line 23  C     !USES:
23  C     !INPUT PARAMETERS:  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        _RL theMin, theMax, theMean, theSD        _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)
28          _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
29          _RS arrDr(myNr)
30          _RL theMin, theMax, theMean, theSD, theDel2, theVol
31        INTEGER myThid        INTEGER myThid
32  CEOP  CEOP
33    
# Line 34  C     !LOCAL VARIABLES: Line 37  C     !LOCAL VARIABLES:
37        LOGICAL noPnts        LOGICAL noPnts
38        _RL tmpVal,rNumPnts        _RL tmpVal,rNumPnts
39        _RL theVar        _RL theVar
40          _RL tmpVol
41        _RL tileMean(nSx,nSy)        _RL tileMean(nSx,nSy)
42        _RL tileVar (nSx,nSy)        _RL tileVar (nSx,nSy)
43        _RL tileSD  (nSx,nSy)        _RL tileSD  (nSx,nSy)
44          _RL tileDel2(nSx,nSy)
45          _RL tileVol (nSx,nSy)
46    
47        theMin = 0.  C     Since 2009/12/21 MON_CALC_STATS_RL replaces MON_STATS_RL
48        theMax = 0.  C     which is now disabled
49        theMean= 0.        STOP 'ABNORMAL END: S/R MON_STATS_RL no longer maintained'
50        theSD  = 0.  
51        theVar = 0.        theMin=0.
52        numPnts= 0        theMax=0.
53        noPnts = .TRUE.        theMean=0.
54          theSD=0.
55          theVar=0.
56          theDel2=0.
57          theVol=0.
58          numPnts=0
59          noPnts=.TRUE.
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            tileDel2(bi,bj) = 0.
64            tileVol (bi,bj) = 0.
65          tileMean(bi,bj) = 0.          tileMean(bi,bj) = 0.
66          tileVar (bi,bj) = 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)
71  c          IF (tmpVal.NE.0. .AND. noPnts) THEN             IF (arrMask(I,J,K,bi,bj).NE.0. .AND. noPnts) THEN
72             IF ( noPnts ) THEN              theMin=tmpVal
73              theMin = tmpVal              theMax=tmpVal
74              theMax = tmpVal              noPnts=.FALSE.
             noPnts = .FALSE.  
75             ENDIF             ENDIF
76  c          IF (tmpVal.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              tileMean(bi,bj)=tileMean(bi,bj)+tmpVal              tileDel2(bi,bj) = tileDel2(bi,bj)
80              tileVar (bi,bj)=tileVar (bi,bj)+tmpVal*tmpVal       &      + 0.25*ABS(
81         &         (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)
83         &        +(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)
85         &                )
86              numPnts=numPnts+1              numPnts=numPnts+1
87  c          ENDIF              tmpVol = arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
88         &                                 *arrMask(I,J,K,bi,bj)
89                tileVol (bi,bj) = tileVol (bi,bj) + tmpVol
90                tileMean(bi,bj) = tileMean(bi,bj) + tmpVol*tmpVal
91                tileVar (bi,bj) = tileVar (bi,bj) + tmpVol*tmpVal*tmpVal
92               ENDIF
93            ENDDO            ENDDO
94           ENDDO           ENDDO
95          ENDDO          ENDDO
96  c       theMean=theMean+tileMean(bi,bj)  c       theDel2 = theDel2 + tileDel2(bi,bj)
97  c       theVar =theVar +tileVar (bi,bj)  c       theVol  = theVol  + tileVol(bi,bj)
98    c       theMean = theMean + tileMean(bi,bj)
99    c       theVar  = theVar  + tileVar (bi,bj)
100         ENDDO         ENDDO
101        ENDDO        ENDDO
102    
103    c     _GLOBAL_SUM_RL(theDel2,myThid)
104    c     _GLOBAL_SUM_RL(theVol,myThid)
105  c     _GLOBAL_SUM_RL(theMean,myThid)  c     _GLOBAL_SUM_RL(theMean,myThid)
106  c     _GLOBAL_SUM_RL(theVar,myThid)  c     _GLOBAL_SUM_RL(theVar,myThid)
107          CALL GLOBAL_SUM_TILE_RL( tileDel2, theDel2, myThid )
108          CALL GLOBAL_SUM_TILE_RL( tileVol , theVol , myThid )
109        CALL GLOBAL_SUM_TILE_RL( tileMean, theMean, myThid )        CALL GLOBAL_SUM_TILE_RL( tileMean, theMean, myThid )
110        CALL GLOBAL_SUM_TILE_RL( tileVar , theVar , myThid )        CALL GLOBAL_SUM_TILE_RL( tileVar , theVar , myThid )
111        tmpVal=FLOAT(numPnts)        tmpVal=FLOAT(numPnts)
# Line 85  c     _GLOBAL_SUM_RL(theVar,myThid) Line 114  c     _GLOBAL_SUM_RL(theVar,myThid)
114    
115        IF (tmpVal.GT.0.) THEN        IF (tmpVal.GT.0.) THEN
116         rNumPnts=1. _d 0/tmpVal         rNumPnts=1. _d 0/tmpVal
117         theMean=theMean*rNumPnts         theDel2=theDel2*rNumPnts
118         theVar=theVar*rNumPnts        ENDIF
119    
120          IF (theVol.GT.0.) THEN
121           theMean=theMean/theVol
122           theVar=theVar/theVol
123         IF ( noPnts ) theMin = theMean         IF ( noPnts ) theMin = theMean
124         theMin=-theMin         theMin=-theMin
125         _GLOBAL_MAX_RL(theMin,myThid)         _GLOBAL_MAX_RL(theMin,myThid)
# Line 101  c     _GLOBAL_SUM_RL(theVar,myThid) Line 134  c     _GLOBAL_SUM_RL(theVar,myThid)
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)
137  c           IF (tmpVal.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)
139         &                                *arrMask(I,J,K,bi,bj)
140               tileSD(bi,bj) = tileSD(bi,bj)               tileSD(bi,bj) = tileSD(bi,bj)
141       &                     + (tmpVal-theMean)*(tmpVal-theMean)       &                     + tmpVol*(tmpVal-theMean)*(tmpVal-theMean)
142  c           ENDIF              ENDIF
143             ENDDO             ENDDO
144            ENDDO            ENDDO
145           ENDDO           ENDDO
# Line 115  c        theSD = theSD + tileSD(bi,bj) Line 150  c        theSD = theSD + tileSD(bi,bj)
150  c      _GLOBAL_SUM_RL(theSD,myThid)  c      _GLOBAL_SUM_RL(theSD,myThid)
151         CALL GLOBAL_SUM_TILE_RL( tileSD, theSD, myThid )         CALL GLOBAL_SUM_TILE_RL( tileSD, theSD, myThid )
152    
153         theSD = SQRT(theSD*rNumPnts)         theSD = SQRT(theSD/theVol)
154  c      theSD = SQRT(theVar-theMean*theMean)  c      theSD = SQRT(theVar-theMean*theMean)
155        ENDIF        ENDIF
156    

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

  ViewVC Help
Powered by ViewVC 1.1.22