Back to home page

MITgcm

 
 

    


File indexing completed on 2018-03-02 18:42:22 UTC

view on githubraw file Latest commit add29e06 on 2018-01-31 20:35:05 UTC
91672e10e3 Alis*0001 #include "MONITOR_OPTIONS.h"
dc684458c1 Alis*0002 
2741539ec0 Ed H*0003 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0004 CBOP
                0005 C     !ROUTINE: MON_STATS_RS
                0006 
                0007 C     !INTERFACE:
dc684458c1 Alis*0008       SUBROUTINE MON_STATS_RS(
2741539ec0 Ed H*0009      I     myNr, arr,
                0010      O     theMin,theMax,theMean,theSD,
                0011      I     myThid )
dc684458c1 Alis*0012 
2741539ec0 Ed H*0013 C     !DESCRIPTION:
                0014 C     Calculate bare statistics of global array ``\_RS arr''.
                0015 
                0016 C     !USES:
                0017       IMPLICIT NONE
dc684458c1 Alis*0018 #include "SIZE.h"
                0019 #include "EEPARAMS.h"
                0020 
2741539ec0 Ed H*0021 C     !INPUT PARAMETERS:
dc684458c1 Alis*0022       INTEGER myNr
                0023       _RS arr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
2741539ec0 Ed H*0024       _RL theMin, theMax, theMean, theSD
dc684458c1 Alis*0025       INTEGER myThid
2741539ec0 Ed H*0026 CEOP
dc684458c1 Alis*0027 
2741539ec0 Ed H*0028 C     !LOCAL VARIABLES:
dc684458c1 Alis*0029       INTEGER bi,bj,I,J,K
                0030       INTEGER numPnts
                0031       LOGICAL noPnts
                0032       _RL tmpVal,rNumPnts
2db77eb7b9 Jean*0033       _RL theVar
                0034       _RL tileMean(nSx,nSy)
                0035       _RL tileVar (nSx,nSy)
                0036       _RL tileSD  (nSx,nSy)
dc684458c1 Alis*0037 
2db77eb7b9 Jean*0038       theMin = 0.
                0039       theMax = 0.
                0040       theMean= 0.
                0041       theSD  = 0.
                0042       theVar = 0.
                0043       numPnts= 0
                0044       noPnts = .TRUE.
dc684458c1 Alis*0045 
                0046       DO bj=myByLo(myThid),myByHi(myThid)
                0047        DO bi=myBxLo(myThid),myBxHi(myThid)
2db77eb7b9 Jean*0048         tileMean(bi,bj) = 0.
                0049         tileVar (bi,bj) = 0.
dc684458c1 Alis*0050         DO K=1,myNr
                0051          DO J=1,sNy
                0052           DO I=1,sNx
                0053            tmpVal=arr(I,J,K,bi,bj)
2db77eb7b9 Jean*0054 c          IF (tmpVal.NE.0. .AND. noPnts) THEN
                0055            IF ( noPnts ) THEN
                0056             theMin = tmpVal
                0057             theMax = tmpVal
                0058             noPnts = .FALSE.
dc684458c1 Alis*0059            ENDIF
2db77eb7b9 Jean*0060 c          IF (tmpVal.NE.0.) THEN
                0061             theMin = MIN(theMin,tmpVal)
                0062             theMax = MAX(theMax,tmpVal)
                0063             tileMean(bi,bj)=tileMean(bi,bj)+tmpVal
                0064             tileVar (bi,bj)=tileVar (bi,bj)+tmpVal*tmpVal
dc684458c1 Alis*0065             numPnts=numPnts+1
2db77eb7b9 Jean*0066 c          ENDIF
dc684458c1 Alis*0067           ENDDO
                0068          ENDDO
                0069         ENDDO
2db77eb7b9 Jean*0070 c       theMean=theMean+tileMean(bi,bj)
                0071 c       theVar =theVar +tileVar (bi,bj)
dc684458c1 Alis*0072        ENDDO
                0073       ENDDO
                0074 
7163a40534 Jean*0075 c     _GLOBAL_SUM_RL(theMean,myThid)
                0076 c     _GLOBAL_SUM_RL(theVar,myThid)
2db77eb7b9 Jean*0077       CALL GLOBAL_SUM_TILE_RL( tileMean, theMean, myThid )
                0078       CALL GLOBAL_SUM_TILE_RL( tileVar , theVar , myThid )
dc684458c1 Alis*0079       tmpVal=FLOAT(numPnts)
7163a40534 Jean*0080       _GLOBAL_SUM_RL(tmpVal,myThid)
27c9817b26 Jean*0081       numPnts=NINT(tmpVal)
dc684458c1 Alis*0082 
                0083       IF (tmpVal.GT.0.) THEN
27c9817b26 Jean*0084        rNumPnts=1. _d 0/tmpVal
dc684458c1 Alis*0085        theMean=theMean*rNumPnts
                0086        theVar=theVar*rNumPnts
eaf4c145cc Jean*0087        IF ( noPnts ) theMin = theMean
                0088        theMin=-theMin
7163a40534 Jean*0089        _GLOBAL_MAX_RL(theMin,myThid)
eaf4c145cc Jean*0090        theMin=-theMin
                0091        IF ( noPnts ) theMax = theMean
7163a40534 Jean*0092        _GLOBAL_MAX_RL(theMax,myThid)
dc684458c1 Alis*0093 
                0094        DO bj=myByLo(myThid),myByHi(myThid)
                0095         DO bi=myBxLo(myThid),myBxHi(myThid)
2db77eb7b9 Jean*0096          tileSD(bi,bj)=0.
dc684458c1 Alis*0097          DO K=1,myNr
                0098           DO J=1,sNy
                0099            DO I=1,sNx
                0100             tmpVal=arr(I,J,K,bi,bj)
2db77eb7b9 Jean*0101 c           IF (tmpVal.NE.0.) THEN
                0102              tileSD(bi,bj) = tileSD(bi,bj)
                0103      &                     + (tmpVal-theMean)*(tmpVal-theMean)
                0104 c           ENDIF
dc684458c1 Alis*0105            ENDDO
                0106           ENDDO
                0107          ENDDO
2db77eb7b9 Jean*0108 c        theSD = theSD + tileSD(bi,bj)
dc684458c1 Alis*0109         ENDDO
                0110        ENDDO
                0111 
7163a40534 Jean*0112 c      _GLOBAL_SUM_RL(theSD,myThid)
2db77eb7b9 Jean*0113        CALL GLOBAL_SUM_TILE_RL( tileSD, theSD, myThid )
dc684458c1 Alis*0114 
2db77eb7b9 Jean*0115        theSD = SQRT(theSD*rNumPnts)
                0116 c      theSD = SQRT(theVar-theMean*theMean)
dc684458c1 Alis*0117       ENDIF
                0118 
                0119       RETURN
                0120       END