Back to home page

MITgcm

 
 

    


File indexing completed on 2018-03-02 18:38:53 UTC

view on githubraw file Latest commit add29e06 on 2018-01-31 20:35:05 UTC
6d54cf9ca1 Ed H*0001 #include "DEBUG_OPTIONS.h"
561d4b6953 Jean*0002 
2c673da9a7 Jean*0003 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0004 CBOP
                0005 C     !ROUTINE: DEBUG_FLD_STATS_RL
                0006 
                0007 C     !INTERFACE:
561d4b6953 Jean*0008       SUBROUTINE DEBUG_FLD_STATS_RL(
2c673da9a7 Jean*0009      I                myNr, arr, exclValue,
                0010      O                theMin, theMax, theMean, theSD,
561d4b6953 Jean*0011      I                myThid )
2c673da9a7 Jean*0012 
                0013 C     *==========================================================*
                0014 C     | SUBROUTINE DEBUG_FLD_STATS_RL                            |
561d4b6953 Jean*0015 C     | o Calculate bare statistics of global array "_RL arr"    |
2c673da9a7 Jean*0016 C     *==========================================================*
                0017 
                0018 C     !USES:
561d4b6953 Jean*0019       IMPLICIT NONE
                0020 
                0021 C     === Global data ===
                0022 #include "SIZE.h"
                0023 #include "EEPARAMS.h"
                0024 
2c673da9a7 Jean*0025 C     !INPUT/OUTPUT PARAMETERS:
                0026 C     myNr      :: 3rd  dimension of input field array
                0027 C     arr       :: input field array
                0028 C     exclValue :: exclusion value
                0029 C     theMin    :: field minimum value
                0030 C     theMax    :: field maximun value
                0031 C     theMean   :: field averaged value
                0032 C     theStD    :: field Standard Deviation
                0033 C     myThid    :: my Thread Id number
561d4b6953 Jean*0034       INTEGER myNr
                0035       _RL arr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
2c673da9a7 Jean*0036       _RL exclValue
561d4b6953 Jean*0037       _RL theMin
                0038       _RL theMax
                0039       _RL theMean
                0040       _RL theSD
                0041       INTEGER myThid
                0042 
2c673da9a7 Jean*0043 C     !LOCAL VARIABLES:
                0044       INTEGER bi,bj,i,j,k
561d4b6953 Jean*0045       LOGICAL noPnts
2c673da9a7 Jean*0046       _RL tmpVal
                0047       _RL nbPnts, rNbPnts
561d4b6953 Jean*0048       _RL theVar
2c673da9a7 Jean*0049       _RL tileMean(nSx,nSy)
                0050       _RL tileVar (nSx,nSy)
                0051       _RL tileSD  (nSx,nSy)
                0052       _RL tileNbPt(nSx,nSy)
                0053 CEOP
561d4b6953 Jean*0054 
2c673da9a7 Jean*0055       theMin = 0.
                0056       theMax = 0.
                0057       theMean= 0.
                0058       theSD  = 0.
                0059       theVar = 0.
                0060       nbPnts = 0.
                0061       noPnts = .TRUE.
561d4b6953 Jean*0062 
                0063       DO bj=myByLo(myThid),myByHi(myThid)
                0064        DO bi=myBxLo(myThid),myBxHi(myThid)
2c673da9a7 Jean*0065         tileNbPt(bi,bj) = 0.
                0066         tileMean(bi,bj) = 0.
                0067         tileVar (bi,bj) = 0.
                0068         DO k=1,myNr
                0069          DO j=1,sNy
                0070           DO i=1,sNx
                0071            tmpVal = arr(i,j,k,bi,bj)
                0072            IF ( tmpVal.NE.exclValue .AND. noPnts ) THEN
                0073             theMin = tmpVal
                0074             theMax = tmpVal
                0075             noPnts = .FALSE.
561d4b6953 Jean*0076            ENDIF
2c673da9a7 Jean*0077            IF ( tmpVal.NE.exclValue ) THEN
                0078             theMin = MIN( theMin, tmpVal )
                0079             theMax = MAX( theMax, tmpVal )
                0080             tileNbPt(bi,bj) = tileNbPt(bi,bj) + 1. _d 0
                0081             tileMean(bi,bj) = tileMean(bi,bj) + tmpVal
                0082             tileVar (bi,bj) = tileVar (bi,bj) + tmpVal*tmpVal
561d4b6953 Jean*0083            ENDIF
                0084           ENDDO
                0085          ENDDO
                0086         ENDDO
                0087        ENDDO
                0088       ENDDO
                0089 
2c673da9a7 Jean*0090       CALL GLOBAL_SUM_TILE_RL( tileNbPt, nbPnts,  myThid )
                0091       CALL GLOBAL_SUM_TILE_RL( tileMean, theMean, myThid )
                0092 c     CALL GLOBAL_SUM_TILE_RL( tileVar , theVar,  myThid )
                0093 
                0094       IF ( nbPnts.GT.zeroRL ) THEN
                0095        rNbPnts = 1. _d 0/nbPnts
                0096        theMean = theMean*rNbPnts
                0097 c      theVar  = theVar *rNbPnts
                0098 
                0099        IF ( noPnts ) theMin = theMean
                0100        theMin = -theMin
                0101        _GLOBAL_MAX_RL( theMin, myThid )
                0102        theMin = -theMin
                0103        IF ( noPnts ) theMax = theMean
                0104        _GLOBAL_MAX_RL( theMax, myThid )
561d4b6953 Jean*0105 
                0106        DO bj=myByLo(myThid),myByHi(myThid)
                0107         DO bi=myBxLo(myThid),myBxHi(myThid)
2c673da9a7 Jean*0108          tileSD(bi,bj) = 0.
                0109          DO k=1,myNr
                0110           DO j=1,sNy
                0111            DO i=1,sNx
                0112             tmpVal = arr(i,j,k,bi,bj)
                0113             IF ( tmpVal.NE.exclValue ) THEN
                0114              tileSD(bi,bj) = tileSD(bi,bj)
                0115      &                     + (tmpVal-theMean)*(tmpVal-theMean)
561d4b6953 Jean*0116             ENDIF
                0117            ENDDO
                0118           ENDDO
                0119          ENDDO
                0120         ENDDO
                0121        ENDDO
                0122 
2c673da9a7 Jean*0123        CALL GLOBAL_SUM_TILE_RL( tileSD, theSD, myThid )
561d4b6953 Jean*0124 
2c673da9a7 Jean*0125        theSD = SQRT( theSD*rNbPnts )
                0126 c      theSD = SQRT( theVar - theMean*theMean )
561d4b6953 Jean*0127       ENDIF
                0128 
                0129       RETURN
                0130       END