/[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.10 by edhill, Sat Apr 3 21:17:10 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    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,       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     /==========================================================\  
16  C     | SUBROUTINE MON_STATS_RL                                  |  C     Calculate bare statistics of global array ``\_RL arr''.
 C     | o Calculate bare statistics of global array "_RL arr"    |  
 C     |==========================================================|  
 C     \==========================================================/  
       IMPLICIT NONE  
17    
18  C     === Global data ===  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        _RL theMin        _RS arrMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
27        _RL theMax        _RS arrhFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
28        _RL theMean        _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
29        _RL theSD        _RS arrDr(myNr)
30          _RL theMin, theMax, theMean, theSD, theDel2, theVol
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        _RL theVar,theVarTile
40          _RL tmpVol
41          _RL theMeanTile, theSDTile, theDel2Tile, theVolTile
42    
43        theMin=0.        theMin=0.
44        theMax=0.        theMax=0.
45        theMean=0.        theMean=0.
46        theSD=0.        theSD=0.
47        theVar=0.        theVar=0.
48          theDel2=0.
49          theVol=0.
50        numPnts=0        numPnts=0
51        noPnts=.TRUE.        noPnts=.TRUE.
52    
53        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
54         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
55            theDel2Tile = 0.
56            theVolTile = 0.
57            theMeanTile = 0.
58            theVarTile = 0.
59          DO K=1,myNr          DO K=1,myNr
60           DO J=1,sNy           DO J=1,sNy
61            DO I=1,sNx            DO I=1,sNx
62             tmpVal=arr(I,J,K,bi,bj)             tmpVal=arr(I,J,K,bi,bj)
63             IF (tmpVal.NE.0. .AND. noPnts) THEN             IF (arrMask(I,J,K,bi,bj).NE.0. .AND. noPnts) THEN
64              theMin=tmpVal              theMin=tmpVal
65              theMax=tmpVal              theMax=tmpVal
66              noPnts=.FALSE.              noPnts=.FALSE.
67             ENDIF             ENDIF
68             IF (tmpVal.NE.0.) THEN             IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
69              theMin=min(theMin,tmpVal)              theMin=min(theMin,tmpVal)
70              theMax=max(theMax,tmpVal)              theMax=max(theMax,tmpVal)
71              theMean=theMean+tmpVal              theDel2Tile = theDel2Tile+0.25*ABS(
72              theVar=theVar+tmpVal**2       &         (arr(I+1,J,K,bi,bj)-tmpVal)*arrMask(I+1,J,K,bi,bj)
73         &        +(arr(I-1,J,K,bi,bj)-tmpVal)*arrMask(I-1,J,K,bi,bj)
74         &        +(arr(I,J+1,K,bi,bj)-tmpVal)*arrMask(I,J+1,K,bi,bj)
75         &        +(arr(I,J-1,K,bi,bj)-tmpVal)*arrMask(I,J-1,K,bi,bj)
76         &                               )
77              numPnts=numPnts+1              numPnts=numPnts+1
78                tmpVol = arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
79         &                                 *arrMask(I,J,K,bi,bj)
80                theVolTile = theVolTile   + tmpVol
81                theMeanTile = theMeanTile + tmpVol*tmpVal
82                theVarTile = theVarTile   + tmpVol*tmpVal**2
83             ENDIF             ENDIF
84            ENDDO            ENDDO
85           ENDDO           ENDDO
86          ENDDO          ENDDO
87            theDel2 = theDel2 + theDel2Tile
88            theVol = theVol + theVolTile
89            theMean = theMean + theMeanTile
90            theVar = theVar + theVarTile
91         ENDDO         ENDDO
92        ENDDO        ENDDO
93    
94        theMin=-theMin        _GLOBAL_SUM_R8(theDel2,myThid)
95        _GLOBAL_MAX_R8(theMin,myThid)        _GLOBAL_SUM_R8(theVol,myThid)
       theMin=-theMin  
       _GLOBAL_MAX_R8(theMax,myThid)  
96        _GLOBAL_SUM_R8(theMean,myThid)        _GLOBAL_SUM_R8(theMean,myThid)
97        _GLOBAL_SUM_R8(theVar,myThid)        _GLOBAL_SUM_R8(theVar,myThid)
98        tmpVal=FLOAT(numPnts)        tmpVal=FLOAT(numPnts)
99        _GLOBAL_SUM_R8(tmpVal,myThid)        _GLOBAL_SUM_R8(tmpVal,myThid)
100        numPnts=INT(tmpVal+0.5)        numPnts=NINT(tmpVal)
101    
102        IF (tmpVal.GT.0.) THEN        IF (tmpVal.GT.0.) THEN
103         rNumPnts=1./tmpVal         rNumPnts=1./tmpVal
104         theMean=theMean*rNumPnts         theDel2=theDel2*rNumPnts
105         theVar=theVar*rNumPnts        ENDIF
106    
107          IF (theVol.GT.0.) THEN
108           theMean=theMean/theVol
109           theVar=theVar/theVol
110           IF ( noPnts ) theMin = theMean
111           theMin=-theMin
112           _GLOBAL_MAX_R8(theMin,myThid)
113           theMin=-theMin
114           IF ( noPnts ) theMax = theMean
115           _GLOBAL_MAX_R8(theMax,myThid)
116    
117         DO bj=myByLo(myThid),myByHi(myThid)         DO bj=myByLo(myThid),myByHi(myThid)
118          DO bi=myBxLo(myThid),myBxHi(myThid)          DO bi=myBxLo(myThid),myBxHi(myThid)
119             theSDtile=0.
120           DO K=1,myNr           DO K=1,myNr
121            DO J=1,sNy            DO J=1,sNy
122             DO I=1,sNx             DO I=1,sNx
123              tmpVal=arr(I,J,K,bi,bj)              tmpVal=arr(I,J,K,bi,bj)
124              IF (tmpVal.NE.0.) THEN  c           IF (tmpVal.NE.0.) THEN
125               theSD=theSD+(tmpVal-theMean)**2              IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
126                 tmpVol=arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
127         &                                *arrMask(I,J,K,bi,bj)
128                 theSDtile = theSDtile + tmpVol*(tmpVal-theMean)**2
129              ENDIF              ENDIF
130             ENDDO             ENDDO
131            ENDDO            ENDDO
132           ENDDO           ENDDO
133             theSD = theSD + theSDtile
134          ENDDO          ENDDO
135         ENDDO         ENDDO
136    
137         _GLOBAL_SUM_R8(theSD,myThid)         _GLOBAL_SUM_R8(theSD,myThid)
138    
139  c      theSD=sqrt(theSD*rNumPnts)         theSD=sqrt(theSD/theVol)
140         theSD=sqrt(theVar-theMean**2)  c      theSD=sqrt(theVar-theMean**2)
141        ENDIF        ENDIF
142    
143        RETURN        RETURN

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

  ViewVC Help
Powered by ViewVC 1.1.22