/[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.13 by jmc, Tue Apr 28 18:16:53 2009 UTC revision 1.14 by jmc, Sat Jan 16 22:27:19 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, arrMask,arrhFac, arrArea, arrDr,       I     myNr, arr,
13       O     theMin,theMax,theMean,theSD,theDel2,theVol,       O     theMin,theMax,theMean,theSD,
14       I     myThid )       I     myThid )
15    
16    C     !DESCRIPTION:
17  C     Calculate bare statistics of global array ``\_RL arr''.  C     Calculate bare statistics of global array ``\_RL arr''.
18    
19  C     !USES:  C     !USES:
# Line 23  C     !USES: Line 24  C     !USES:
24  C     !INPUT PARAMETERS:  C     !INPUT PARAMETERS:
25        INTEGER myNr        INTEGER myNr
26        _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)
27        _RS arrMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)        _RL theMin, theMax, theMean, theSD
       _RS arrhFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)  
       _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)  
       _RS arrDr(myNr)  
       _RL theMin, theMax, theMean, theSD, theDel2, theVol  
28        INTEGER myThid        INTEGER myThid
29  CEOP  CEOP
30    
# Line 37  C     !LOCAL VARIABLES: Line 34  C     !LOCAL VARIABLES:
34        LOGICAL noPnts        LOGICAL noPnts
35        _RL tmpVal,rNumPnts        _RL tmpVal,rNumPnts
36        _RL theVar        _RL theVar
       _RL tmpVol  
37        _RL tileMean(nSx,nSy)        _RL tileMean(nSx,nSy)
38        _RL tileVar (nSx,nSy)        _RL tileVar (nSx,nSy)
39        _RL tileSD  (nSx,nSy)        _RL tileSD  (nSx,nSy)
       _RL tileDel2(nSx,nSy)  
       _RL tileVol (nSx,nSy)  
40    
41        theMin=0.        theMin = 0.
42        theMax=0.        theMax = 0.
43        theMean=0.        theMean= 0.
44        theSD=0.        theSD  = 0.
45        theVar=0.        theVar = 0.
46        theDel2=0.        numPnts= 0
47        theVol=0.        noPnts = .TRUE.
       numPnts=0  
       noPnts=.TRUE.  
48    
49        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
50         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
         tileDel2(bi,bj) = 0.  
         tileVol (bi,bj) = 0.  
51          tileMean(bi,bj) = 0.          tileMean(bi,bj) = 0.
52          tileVar (bi,bj) = 0.          tileVar (bi,bj) = 0.
53          DO K=1,myNr          DO K=1,myNr
54           DO J=1,sNy           DO J=1,sNy
55            DO I=1,sNx            DO I=1,sNx
56             tmpVal=arr(I,J,K,bi,bj)             tmpVal=arr(I,J,K,bi,bj)
57             IF (arrMask(I,J,K,bi,bj).NE.0. .AND. noPnts) THEN  c          IF (tmpVal.NE.0. .AND. noPnts) THEN
58              theMin=tmpVal             IF ( noPnts ) THEN
59              theMax=tmpVal              theMin = tmpVal
60              noPnts=.FALSE.              theMax = tmpVal
61                noPnts = .FALSE.
62             ENDIF             ENDIF
63             IF (arrMask(I,J,K,bi,bj).NE.0.) THEN  c          IF (tmpVal.NE.0.) THEN
64              theMin=min(theMin,tmpVal)              theMin = MIN(theMin,tmpVal)
65              theMax=max(theMax,tmpVal)              theMax = MAX(theMax,tmpVal)
66              tileDel2(bi,bj) = tileDel2(bi,bj)              tileMean(bi,bj)=tileMean(bi,bj)+tmpVal
67       &      + 0.25*ABS(              tileVar (bi,bj)=tileVar (bi,bj)+tmpVal*tmpVal
      &         (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)  
      &        +(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)  
      &                )  
68              numPnts=numPnts+1              numPnts=numPnts+1
69              tmpVol = arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)  c          ENDIF
      &                                 *arrMask(I,J,K,bi,bj)  
             tileVol (bi,bj) = tileVol (bi,bj) + tmpVol  
             tileMean(bi,bj) = tileMean(bi,bj) + tmpVol*tmpVal  
             tileVar (bi,bj) = tileVar (bi,bj) + tmpVol*tmpVal*tmpVal  
            ENDIF  
70            ENDDO            ENDDO
71           ENDDO           ENDDO
72          ENDDO          ENDDO
73  c       theDel2 = theDel2 + tileDel2(bi,bj)  c       theMean=theMean+tileMean(bi,bj)
74  c       theVol  = theVol  + tileVol(bi,bj)  c       theVar =theVar +tileVar (bi,bj)
 c       theMean = theMean + tileMean(bi,bj)  
 c       theVar  = theVar  + tileVar (bi,bj)  
75         ENDDO         ENDDO
76        ENDDO        ENDDO
77    
 c     _GLOBAL_SUM_RL(theDel2,myThid)  
 c     _GLOBAL_SUM_RL(theVol,myThid)  
78  c     _GLOBAL_SUM_RL(theMean,myThid)  c     _GLOBAL_SUM_RL(theMean,myThid)
79  c     _GLOBAL_SUM_RL(theVar,myThid)  c     _GLOBAL_SUM_RL(theVar,myThid)
       CALL GLOBAL_SUM_TILE_RL( tileDel2, theDel2, myThid )  
       CALL GLOBAL_SUM_TILE_RL( tileVol , theVol , myThid )  
80        CALL GLOBAL_SUM_TILE_RL( tileMean, theMean, myThid )        CALL GLOBAL_SUM_TILE_RL( tileMean, theMean, myThid )
81        CALL GLOBAL_SUM_TILE_RL( tileVar , theVar , myThid )        CALL GLOBAL_SUM_TILE_RL( tileVar , theVar , myThid )
82        tmpVal=FLOAT(numPnts)        tmpVal=FLOAT(numPnts)
# Line 110  c     _GLOBAL_SUM_RL(theVar,myThid) Line 85  c     _GLOBAL_SUM_RL(theVar,myThid)
85    
86        IF (tmpVal.GT.0.) THEN        IF (tmpVal.GT.0.) THEN
87         rNumPnts=1. _d 0/tmpVal         rNumPnts=1. _d 0/tmpVal
88         theDel2=theDel2*rNumPnts         theMean=theMean*rNumPnts
89        ENDIF         theVar=theVar*rNumPnts
   
       IF (theVol.GT.0.) THEN  
        theMean=theMean/theVol  
        theVar=theVar/theVol  
90         IF ( noPnts ) theMin = theMean         IF ( noPnts ) theMin = theMean
91         theMin=-theMin         theMin=-theMin
92         _GLOBAL_MAX_RL(theMin,myThid)         _GLOBAL_MAX_RL(theMin,myThid)
# Line 130  c     _GLOBAL_SUM_RL(theVar,myThid) Line 101  c     _GLOBAL_SUM_RL(theVar,myThid)
101            DO J=1,sNy            DO J=1,sNy
102             DO I=1,sNx             DO I=1,sNx
103              tmpVal=arr(I,J,K,bi,bj)              tmpVal=arr(I,J,K,bi,bj)
104              IF (arrMask(I,J,K,bi,bj).NE.0.) THEN  c           IF (tmpVal.NE.0.) THEN
              tmpVol=arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)  
      &                                *arrMask(I,J,K,bi,bj)  
105               tileSD(bi,bj) = tileSD(bi,bj)               tileSD(bi,bj) = tileSD(bi,bj)
106       &                     + tmpVol*(tmpVal-theMean)*(tmpVal-theMean)       &                     + (tmpVal-theMean)*(tmpVal-theMean)
107              ENDIF  c           ENDIF
108             ENDDO             ENDDO
109            ENDDO            ENDDO
110           ENDDO           ENDDO
# Line 146  c        theSD = theSD + tileSD(bi,bj) Line 115  c        theSD = theSD + tileSD(bi,bj)
115  c      _GLOBAL_SUM_RL(theSD,myThid)  c      _GLOBAL_SUM_RL(theSD,myThid)
116         CALL GLOBAL_SUM_TILE_RL( tileSD, theSD, myThid )         CALL GLOBAL_SUM_TILE_RL( tileSD, theSD, myThid )
117    
118         theSD = SQRT(theSD/theVol)         theSD = SQRT(theSD*rNumPnts)
119  c      theSD = SQRT(theVar-theMean*theMean)  c      theSD = SQRT(theVar-theMean*theMean)
120        ENDIF        ENDIF
121    

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

  ViewVC Help
Powered by ViewVC 1.1.22