/[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.5 by adcroft, Tue May 13 18:18:05 2003 UTC revision 1.14 by jmc, Sat Jan 16 22:27:19 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,
13       O                theMin,theMax,theMean,theSD,theDel2,theVol,       O     theMin,theMax,theMean,theSD,
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     !DESCRIPTION:
17    C     Calculate bare statistics of global array ``\_RL arr''.
18    
19    C     !USES:
20          IMPLICIT NONE
21  #include "SIZE.h"  #include "SIZE.h"
22  #include "EEPARAMS.h"  #include "EEPARAMS.h"
23    
24  C     === Routine arguments ===  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  
       _RL theMax  
       _RL theMean  
       _RL theSD  
       _RL theDel2  
       _RL theVol  
28        INTEGER myThid        INTEGER myThid
29    CEOP
30    
31  C     === Local variables ====  C     !LOCAL VARIABLES:
32        INTEGER bi,bj,I,J,K        INTEGER bi,bj,I,J,K
33        INTEGER numPnts        INTEGER numPnts
34        LOGICAL noPnts        LOGICAL noPnts
35        _RL tmpVal,rNumPnts        _RL tmpVal,rNumPnts
36        _RL theVar        _RL theVar
37        _RL tmpVol        _RL tileMean(nSx,nSy)
38          _RL tileVar (nSx,nSy)
39        theMin=0.        _RL tileSD  (nSx,nSy)
40        theMax=0.  
41        theMean=0.        theMin = 0.
42        theSD=0.        theMax = 0.
43        theVar=0.        theMean= 0.
44        theDel2=0.        theSD  = 0.
45        theVol=0.        theVar = 0.
46        numPnts=0        numPnts= 0
47        noPnts=.TRUE.        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)
51            tileMean(bi,bj) = 0.
52            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  c          IF (tmpVal.NE.0. .AND. noPnts) THEN  c          IF (tmpVal.NE.0. .AND. noPnts) THEN
58             IF (arrMask(I,J,K,bi,bj).NE.0. .AND. noPnts) THEN             IF ( noPnts ) THEN
59              theMin=tmpVal              theMin = tmpVal
60              theMax=tmpVal              theMax = tmpVal
61              noPnts=.FALSE.              noPnts = .FALSE.
62             ENDIF             ENDIF
63  c          IF (tmpVal.NE.0.) THEN  c          IF (tmpVal.NE.0.) THEN
64             IF (arrMask(I,J,K,bi,bj).NE.0.) THEN              theMin = MIN(theMin,tmpVal)
65              theMin=min(theMin,tmpVal)              theMax = MAX(theMax,tmpVal)
66              theMax=max(theMax,tmpVal)              tileMean(bi,bj)=tileMean(bi,bj)+tmpVal
67              theDel2 = theDel2+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
             theVol = theVol   + tmpVol  
             theMean = theMean + tmpVol*tmpVal  
             theVar = theVar   + tmpVol*tmpVal**2  
            ENDIF  
70            ENDDO            ENDDO
71           ENDDO           ENDDO
72          ENDDO          ENDDO
73    c       theMean=theMean+tileMean(bi,bj)
74    c       theVar =theVar +tileVar (bi,bj)
75         ENDDO         ENDDO
76        ENDDO        ENDDO
77    
78        theMin=-theMin  c     _GLOBAL_SUM_RL(theMean,myThid)
79        _GLOBAL_MAX_R8(theMin,myThid)  c     _GLOBAL_SUM_RL(theVar,myThid)
80        theMin=-theMin        CALL GLOBAL_SUM_TILE_RL( tileMean, theMean, myThid )
81        _GLOBAL_MAX_R8(theMax,myThid)        CALL GLOBAL_SUM_TILE_RL( tileVar , theVar , myThid )
       _GLOBAL_SUM_R8(theDel2,myThid)  
       _GLOBAL_SUM_R8(theVol,myThid)  
       _GLOBAL_SUM_R8(theMean,myThid)  
       _GLOBAL_SUM_R8(theVar,myThid)  
82        tmpVal=FLOAT(numPnts)        tmpVal=FLOAT(numPnts)
83        _GLOBAL_SUM_R8(tmpVal,myThid)        _GLOBAL_SUM_RL(tmpVal,myThid)
84        numPnts=INT(tmpVal+0.5)        numPnts=NINT(tmpVal)
85    
86        IF (tmpVal.GT.0.) THEN        IF (tmpVal.GT.0.) THEN
87         rNumPnts=1./tmpVal         rNumPnts=1. _d 0/tmpVal
88         theDel2=theDel2*rNumPnts         theMean=theMean*rNumPnts
89        ENDIF         theVar=theVar*rNumPnts
90           IF ( noPnts ) theMin = theMean
91        IF (theVol.GT.0.) THEN         theMin=-theMin
92         theMean=theMean/theVol         _GLOBAL_MAX_RL(theMin,myThid)
93         theVar=theVar/theVol         theMin=-theMin
94           IF ( noPnts ) theMax = theMean
95           _GLOBAL_MAX_RL(theMax,myThid)
96    
97         DO bj=myByLo(myThid),myByHi(myThid)         DO bj=myByLo(myThid),myByHi(myThid)
98          DO bi=myBxLo(myThid),myBxHi(myThid)          DO bi=myBxLo(myThid),myBxHi(myThid)
99             tileSD(bi,bj)=0.
100           DO K=1,myNr           DO K=1,myNr
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  c           IF (tmpVal.NE.0.) THEN  c           IF (tmpVal.NE.0.) THEN
105              IF (arrMask(I,J,K,bi,bj).NE.0.) THEN               tileSD(bi,bj) = tileSD(bi,bj)
106               tmpVol=arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)       &                     + (tmpVal-theMean)*(tmpVal-theMean)
107               theSD = theSD + tmpVol*(tmpVal-theMean)**2  c           ENDIF
             ENDIF  
108             ENDDO             ENDDO
109            ENDDO            ENDDO
110           ENDDO           ENDDO
111    c        theSD = theSD + tileSD(bi,bj)
112          ENDDO          ENDDO
113         ENDDO         ENDDO
114    
115         _GLOBAL_SUM_R8(theSD,myThid)  c      _GLOBAL_SUM_RL(theSD,myThid)
116           CALL GLOBAL_SUM_TILE_RL( tileSD, theSD, myThid )
117    
118         theSD=sqrt(theSD/theVol)         theSD = SQRT(theSD*rNumPnts)
119  c      theSD=sqrt(theVar-theMean**2)  c      theSD = SQRT(theVar-theMean*theMean)
120        ENDIF        ENDIF
121    
122        RETURN        RETURN

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

  ViewVC Help
Powered by ViewVC 1.1.22