/[MITgcm]/MITgcm/pkg/monitor/mon_stats_rl.F
ViewVC logotype

Contents of /MITgcm/pkg/monitor/mon_stats_rl.F

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


Revision 1.13 - (show annotations) (download)
Tue Apr 28 18:16:53 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62a, checkpoint62, checkpoint61n, checkpoint61q, checkpoint61o, checkpoint61m, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.12: +9 -9 lines
change macros (EXCH & GLOBAL_SUM/MAX) sufix _R4/_R8 to _RS/_RL
 when applied to _RS/_RL variable

1 C $Header: /u/gcmpack/MITgcm/pkg/monitor/mon_stats_rl.F,v 1.12 2007/10/15 00:18:40 jmc Exp $
2 C $Name: $
3
4 #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(
12 I myNr, arr, arrMask,arrhFac, arrArea, arrDr,
13 O theMin,theMax,theMean,theSD,theDel2,theVol,
14 I myThid )
15
16 C Calculate bare statistics of global array ``\_RL arr''.
17
18 C !USES:
19 IMPLICIT NONE
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22
23 C !INPUT PARAMETERS:
24 INTEGER myNr
25 _RL arr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
26 _RS arrMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
27 _RS arrhFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
28 _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
29 _RS arrDr(myNr)
30 _RL theMin, theMax, theMean, theSD, theDel2, theVol
31 INTEGER myThid
32 CEOP
33
34 C !LOCAL VARIABLES:
35 INTEGER bi,bj,I,J,K
36 INTEGER numPnts
37 LOGICAL noPnts
38 _RL tmpVal,rNumPnts
39 _RL theVar
40 _RL tmpVol
41 _RL tileMean(nSx,nSy)
42 _RL tileVar (nSx,nSy)
43 _RL tileSD (nSx,nSy)
44 _RL tileDel2(nSx,nSy)
45 _RL tileVol (nSx,nSy)
46
47 theMin=0.
48 theMax=0.
49 theMean=0.
50 theSD=0.
51 theVar=0.
52 theDel2=0.
53 theVol=0.
54 numPnts=0
55 noPnts=.TRUE.
56
57 DO bj=myByLo(myThid),myByHi(myThid)
58 DO bi=myBxLo(myThid),myBxHi(myThid)
59 tileDel2(bi,bj) = 0.
60 tileVol (bi,bj) = 0.
61 tileMean(bi,bj) = 0.
62 tileVar (bi,bj) = 0.
63 DO K=1,myNr
64 DO J=1,sNy
65 DO I=1,sNx
66 tmpVal=arr(I,J,K,bi,bj)
67 IF (arrMask(I,J,K,bi,bj).NE.0. .AND. noPnts) THEN
68 theMin=tmpVal
69 theMax=tmpVal
70 noPnts=.FALSE.
71 ENDIF
72 IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
73 theMin=min(theMin,tmpVal)
74 theMax=max(theMax,tmpVal)
75 tileDel2(bi,bj) = tileDel2(bi,bj)
76 & + 0.25*ABS(
77 & (arr(I+1,J,K,bi,bj)-tmpVal)*arrMask(I+1,J,K,bi,bj)
78 & +(arr(I-1,J,K,bi,bj)-tmpVal)*arrMask(I-1,J,K,bi,bj)
79 & +(arr(I,J+1,K,bi,bj)-tmpVal)*arrMask(I,J+1,K,bi,bj)
80 & +(arr(I,J-1,K,bi,bj)-tmpVal)*arrMask(I,J-1,K,bi,bj)
81 & )
82 numPnts=numPnts+1
83 tmpVol = arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
84 & *arrMask(I,J,K,bi,bj)
85 tileVol (bi,bj) = tileVol (bi,bj) + tmpVol
86 tileMean(bi,bj) = tileMean(bi,bj) + tmpVol*tmpVal
87 tileVar (bi,bj) = tileVar (bi,bj) + tmpVol*tmpVal*tmpVal
88 ENDIF
89 ENDDO
90 ENDDO
91 ENDDO
92 c theDel2 = theDel2 + tileDel2(bi,bj)
93 c theVol = theVol + tileVol(bi,bj)
94 c theMean = theMean + tileMean(bi,bj)
95 c theVar = theVar + tileVar (bi,bj)
96 ENDDO
97 ENDDO
98
99 c _GLOBAL_SUM_RL(theDel2,myThid)
100 c _GLOBAL_SUM_RL(theVol,myThid)
101 c _GLOBAL_SUM_RL(theMean,myThid)
102 c _GLOBAL_SUM_RL(theVar,myThid)
103 CALL GLOBAL_SUM_TILE_RL( tileDel2, theDel2, myThid )
104 CALL GLOBAL_SUM_TILE_RL( tileVol , theVol , myThid )
105 CALL GLOBAL_SUM_TILE_RL( tileMean, theMean, myThid )
106 CALL GLOBAL_SUM_TILE_RL( tileVar , theVar , myThid )
107 tmpVal=FLOAT(numPnts)
108 _GLOBAL_SUM_RL(tmpVal,myThid)
109 numPnts=NINT(tmpVal)
110
111 IF (tmpVal.GT.0.) THEN
112 rNumPnts=1. _d 0/tmpVal
113 theDel2=theDel2*rNumPnts
114 ENDIF
115
116 IF (theVol.GT.0.) THEN
117 theMean=theMean/theVol
118 theVar=theVar/theVol
119 IF ( noPnts ) theMin = theMean
120 theMin=-theMin
121 _GLOBAL_MAX_RL(theMin,myThid)
122 theMin=-theMin
123 IF ( noPnts ) theMax = theMean
124 _GLOBAL_MAX_RL(theMax,myThid)
125
126 DO bj=myByLo(myThid),myByHi(myThid)
127 DO bi=myBxLo(myThid),myBxHi(myThid)
128 tileSD(bi,bj)=0.
129 DO K=1,myNr
130 DO J=1,sNy
131 DO I=1,sNx
132 tmpVal=arr(I,J,K,bi,bj)
133 IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
134 tmpVol=arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
135 & *arrMask(I,J,K,bi,bj)
136 tileSD(bi,bj) = tileSD(bi,bj)
137 & + tmpVol*(tmpVal-theMean)*(tmpVal-theMean)
138 ENDIF
139 ENDDO
140 ENDDO
141 ENDDO
142 c theSD = theSD + tileSD(bi,bj)
143 ENDDO
144 ENDDO
145
146 c _GLOBAL_SUM_RL(theSD,myThid)
147 CALL GLOBAL_SUM_TILE_RL( tileSD, theSD, myThid )
148
149 theSD = SQRT(theSD/theVol)
150 c theSD = SQRT(theVar-theMean*theMean)
151 ENDIF
152
153 RETURN
154 END

  ViewVC Help
Powered by ViewVC 1.1.22