/[MITgcm]/MITgcm/pkg/debug/debug_fld_stats_rl.F
ViewVC logotype

Diff of /MITgcm/pkg/debug/debug_fld_stats_rl.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.1.12.1 by adcroft, Thu Oct 2 18:30:07 2003 UTC revision 1.4 by jmc, Tue Jul 26 16:23:52 2016 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "DEBUG_OPTIONS.h"  #include "DEBUG_OPTIONS.h"
5    
6    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7    CBOP
8    C     !ROUTINE: DEBUG_FLD_STATS_RL
9    
10    C     !INTERFACE:
11        SUBROUTINE DEBUG_FLD_STATS_RL(        SUBROUTINE DEBUG_FLD_STATS_RL(
12       I                myNr, arr,       I                myNr, arr, exclValue,
13       O                theMin,theMax,theMean,theSD,       O                theMin, theMax, theMean, theSD,
14       I                myThid )       I                myThid )
15  C     /==========================================================\  
16  C     | SUBROUTINE DEBUG_FLD_STATS_RL                                  |  C     *==========================================================*
17    C     | SUBROUTINE DEBUG_FLD_STATS_RL                            |
18  C     | o Calculate bare statistics of global array "_RL arr"    |  C     | o Calculate bare statistics of global array "_RL arr"    |
19  C     |==========================================================|  C     *==========================================================*
20  C     \==========================================================/  
21    C     !USES:
22        IMPLICIT NONE        IMPLICIT NONE
23    
24  C     === Global data ===  C     === Global data ===
25  #include "SIZE.h"  #include "SIZE.h"
26  #include "EEPARAMS.h"  #include "EEPARAMS.h"
27    
28  C     === Routine arguments ===  C     !INPUT/OUTPUT PARAMETERS:
29    C     myNr      :: 3rd  dimension of input field array
30    C     arr       :: input field array
31    C     exclValue :: exclusion value
32    C     theMin    :: field minimum value
33    C     theMax    :: field maximun value
34    C     theMean   :: field averaged value
35    C     theStD    :: field Standard Deviation
36    C     myThid    :: my Thread Id number
37        INTEGER myNr        INTEGER myNr
38        _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)
39          _RL exclValue
40        _RL theMin        _RL theMin
41        _RL theMax        _RL theMax
42        _RL theMean        _RL theMean
43        _RL theSD        _RL theSD
44        INTEGER myThid        INTEGER myThid
45    
46  C     === Local variables ====  C     !LOCAL VARIABLES:
47        INTEGER bi,bj,I,J,K        INTEGER bi,bj,i,j,k
       INTEGER numPnts  
48        LOGICAL noPnts        LOGICAL noPnts
49        _RL tmpVal,rNumPnts        _RL tmpVal
50          _RL nbPnts, rNbPnts
51        _RL theVar        _RL theVar
52          _RL tileMean(nSx,nSy)
53        theMin=0.        _RL tileVar (nSx,nSy)
54        theMax=0.        _RL tileSD  (nSx,nSy)
55        theMean=0.        _RL tileNbPt(nSx,nSy)
56        theSD=0.  CEOP
57        theVar=0.  
58        numPnts=0        theMin = 0.
59        noPnts=.TRUE.        theMax = 0.
60          theMean= 0.
61          theSD  = 0.
62          theVar = 0.
63          nbPnts = 0.
64          noPnts = .TRUE.
65    
66        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
67         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
68          DO K=1,myNr          tileNbPt(bi,bj) = 0.
69           DO J=1,sNy          tileMean(bi,bj) = 0.
70            DO I=1,sNx          tileVar (bi,bj) = 0.
71             tmpVal=arr(I,J,K,bi,bj)          DO k=1,myNr
72             IF (tmpVal.NE.0. .AND. noPnts) THEN           DO j=1,sNy
73              theMin=tmpVal            DO i=1,sNx
74              theMax=tmpVal             tmpVal = arr(i,j,k,bi,bj)
75              noPnts=.FALSE.             IF ( tmpVal.NE.exclValue .AND. noPnts ) THEN
76                theMin = tmpVal
77                theMax = tmpVal
78                noPnts = .FALSE.
79             ENDIF             ENDIF
80             IF (tmpVal.NE.0.) THEN             IF ( tmpVal.NE.exclValue ) THEN
81              theMin=min(theMin,tmpVal)              theMin = MIN( theMin, tmpVal )
82              theMax=max(theMax,tmpVal)              theMax = MAX( theMax, tmpVal )
83              theMean=theMean+tmpVal              tileNbPt(bi,bj) = tileNbPt(bi,bj) + 1. _d 0
84              theVar=theVar+tmpVal**2              tileMean(bi,bj) = tileMean(bi,bj) + tmpVal
85              numPnts=numPnts+1              tileVar (bi,bj) = tileVar (bi,bj) + tmpVal*tmpVal
86             ENDIF             ENDIF
87            ENDDO            ENDDO
88           ENDDO           ENDDO
# Line 66  C     === Local variables ==== Line 90  C     === Local variables ====
90         ENDDO         ENDDO
91        ENDDO        ENDDO
92    
93        theMin=-theMin        CALL GLOBAL_SUM_TILE_RL( tileNbPt, nbPnts,  myThid )
94        _GLOBAL_MAX_R8(theMin,myThid)        CALL GLOBAL_SUM_TILE_RL( tileMean, theMean, myThid )
95        theMin=-theMin  c     CALL GLOBAL_SUM_TILE_RL( tileVar , theVar,  myThid )
96        _GLOBAL_MAX_R8(theMax,myThid)  
97        _GLOBAL_SUM_R8(theMean,myThid)        IF ( nbPnts.GT.zeroRL ) THEN
98        _GLOBAL_SUM_R8(theVar,myThid)         rNbPnts = 1. _d 0/nbPnts
99        tmpVal=FLOAT(numPnts)         theMean = theMean*rNbPnts
100        _GLOBAL_SUM_R8(tmpVal,myThid)  c      theVar  = theVar *rNbPnts
101        numPnts=INT(tmpVal+0.5)  
102           IF ( noPnts ) theMin = theMean
103        IF (tmpVal.GT.0.) THEN         theMin = -theMin
104         rNumPnts=1./tmpVal         _GLOBAL_MAX_RL( theMin, myThid )
105         theMean=theMean*rNumPnts         theMin = -theMin
106         theVar=theVar*rNumPnts         IF ( noPnts ) theMax = theMean
107           _GLOBAL_MAX_RL( theMax, myThid )
108    
109         DO bj=myByLo(myThid),myByHi(myThid)         DO bj=myByLo(myThid),myByHi(myThid)
110          DO bi=myBxLo(myThid),myBxHi(myThid)          DO bi=myBxLo(myThid),myBxHi(myThid)
111           DO K=1,myNr           tileSD(bi,bj) = 0.
112            DO J=1,sNy           DO k=1,myNr
113             DO I=1,sNx            DO j=1,sNy
114              tmpVal=arr(I,J,K,bi,bj)             DO i=1,sNx
115              IF (tmpVal.NE.0.) THEN              tmpVal = arr(i,j,k,bi,bj)
116               theSD=theSD+(tmpVal-theMean)**2              IF ( tmpVal.NE.exclValue ) THEN
117                 tileSD(bi,bj) = tileSD(bi,bj)
118         &                     + (tmpVal-theMean)*(tmpVal-theMean)
119              ENDIF              ENDIF
120             ENDDO             ENDDO
121            ENDDO            ENDDO
# Line 96  C     === Local variables ==== Line 123  C     === Local variables ====
123          ENDDO          ENDDO
124         ENDDO         ENDDO
125    
126         _GLOBAL_SUM_R8(theSD,myThid)         CALL GLOBAL_SUM_TILE_RL( tileSD, theSD, myThid )
127    
128         theSD=sqrt(theSD*rNumPnts)         theSD = SQRT( theSD*rNbPnts )
129  c      theSD=sqrt(theVar-theMean**2)  c      theSD = SQRT( theVar - theMean*theMean )
130        ENDIF        ENDIF
131    
132        RETURN        RETURN

Legend:
Removed from v.1.1.12.1  
changed lines
  Added in v.1.4

  ViewVC Help
Powered by ViewVC 1.1.22