/[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.11 - (show annotations) (download)
Thu Jan 27 16:36:24 2005 UTC (19 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57m_post, checkpoint57g_pre, checkpoint57s_post, checkpoint58b_post, checkpoint57g_post, checkpoint57y_post, checkpoint57r_post, checkpoint57d_post, checkpoint57i_post, checkpoint59, checkpoint58, checkpoint58f_post, checkpoint57n_post, checkpoint58d_post, checkpoint58a_post, checkpoint57z_post, checkpoint58y_post, checkpoint58t_post, checkpoint58m_post, checkpoint57l_post, checkpoint57t_post, checkpoint57v_post, checkpoint57f_post, checkpoint57h_pre, checkpoint58w_post, checkpoint57h_post, checkpoint57y_pre, checkpoint58o_post, checkpoint57c_post, checkpoint58p_post, checkpoint58q_post, checkpoint58e_post, mitgcm_mapl_00, checkpoint58r_post, checkpoint58n_post, checkpoint57e_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59h, checkpoint57p_post, checkpint57u_post, checkpoint57q_post, eckpoint57e_pre, checkpoint58k_post, checkpoint58v_post, checkpoint58l_post, checkpoint57h_done, checkpoint57j_post, checkpoint57f_pre, checkpoint58g_post, checkpoint58x_post, checkpoint58h_post, checkpoint58j_post, checkpoint57o_post, checkpoint57k_post, checkpoint57w_post, checkpoint58i_post, checkpoint57x_post, checkpoint58c_post, checkpoint58u_post, checkpoint58s_post
Changes since 1.10: +3 -3 lines
minor change (add "_d 0" for del2 computation)

1 C $Header: /u/gcmpack/MITgcm/pkg/monitor/mon_stats_rl.F,v 1.10 2004/04/03 21:17:10 edhill 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,theVarTile
40 _RL tmpVol
41 _RL theMeanTile, theSDTile, theDel2Tile, theVolTile
42
43 theMin=0.
44 theMax=0.
45 theMean=0.
46 theSD=0.
47 theVar=0.
48 theDel2=0.
49 theVol=0.
50 numPnts=0
51 noPnts=.TRUE.
52
53 DO bj=myByLo(myThid),myByHi(myThid)
54 DO bi=myBxLo(myThid),myBxHi(myThid)
55 theDel2Tile = 0.
56 theVolTile = 0.
57 theMeanTile = 0.
58 theVarTile = 0.
59 DO K=1,myNr
60 DO J=1,sNy
61 DO I=1,sNx
62 tmpVal=arr(I,J,K,bi,bj)
63 IF (arrMask(I,J,K,bi,bj).NE.0. .AND. noPnts) THEN
64 theMin=tmpVal
65 theMax=tmpVal
66 noPnts=.FALSE.
67 ENDIF
68 IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
69 theMin=min(theMin,tmpVal)
70 theMax=max(theMax,tmpVal)
71 theDel2Tile = theDel2Tile+0.25*ABS(
72 & (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
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*tmpVal
83 ENDIF
84 ENDDO
85 ENDDO
86 ENDDO
87 theDel2 = theDel2 + theDel2Tile
88 theVol = theVol + theVolTile
89 theMean = theMean + theMeanTile
90 theVar = theVar + theVarTile
91 ENDDO
92 ENDDO
93
94 _GLOBAL_SUM_R8(theDel2,myThid)
95 _GLOBAL_SUM_R8(theVol,myThid)
96 _GLOBAL_SUM_R8(theMean,myThid)
97 _GLOBAL_SUM_R8(theVar,myThid)
98 tmpVal=FLOAT(numPnts)
99 _GLOBAL_SUM_R8(tmpVal,myThid)
100 numPnts=NINT(tmpVal)
101
102 IF (tmpVal.GT.0.) THEN
103 rNumPnts=1. _d 0/tmpVal
104 theDel2=theDel2*rNumPnts
105 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)
118 DO bi=myBxLo(myThid),myBxHi(myThid)
119 theSDtile=0.
120 DO K=1,myNr
121 DO J=1,sNy
122 DO I=1,sNx
123 tmpVal=arr(I,J,K,bi,bj)
124 c IF (tmpVal.NE.0.) THEN
125 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
130 ENDDO
131 ENDDO
132 ENDDO
133 theSD = theSD + theSDtile
134 ENDDO
135 ENDDO
136
137 _GLOBAL_SUM_R8(theSD,myThid)
138
139 theSD=sqrt(theSD/theVol)
140 c theSD=sqrt(theVar-theMean**2)
141 ENDIF
142
143 RETURN
144 END

  ViewVC Help
Powered by ViewVC 1.1.22