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

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

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


Revision 1.10 - (hide annotations) (download)
Sat Apr 3 21:17:10 2004 UTC (20 years, 2 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint57b_post, checkpoint56b_post, checkpoint54d_post, checkpoint54e_post, checkpoint55, checkpoint54, checkpoint57, checkpoint56, checkpoint53, checkpoint54f_post, checkpoint55i_post, checkpoint55c_post, checkpoint53d_post, checkpoint57a_post, checkpoint54b_post, checkpoint52m_post, checkpoint55g_post, checkpoint55d_post, checkpoint54a_pre, checkpoint53c_post, checkpoint55d_pre, checkpoint57c_pre, checkpoint55j_post, checkpoint54a_post, checkpoint55h_post, checkpoint55b_post, checkpoint53a_post, checkpoint55f_post, checkpoint53g_post, checkpoint56a_post, checkpoint53f_post, checkpoint52n_post, checkpoint53b_pre, checkpoint56c_post, checkpoint57a_pre, checkpoint55a_post, checkpoint53b_post, checkpoint53d_pre, checkpoint55e_post, checkpoint54c_post
Changes since 1.9: +17 -19 lines
 o removing duplicate code in mon_out.F in preparation for MNC output
 o convert all monitor files to protex-style comments

1 edhill 1.10 C $Header: /u/gcmpack/MITgcm/pkg/monitor/mon_stats_rl.F,v 1.9 2004/03/05 02:28:11 jmc Exp $
2 adcroft 1.2 C $Name: $
3 adcroft 1.1
4 adcroft 1.5 #include "MONITOR_OPTIONS.h"
5 adcroft 1.1
6 edhill 1.10 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7     CBOP
8     C !ROUTINE: MON_STATS_RL
9    
10     C !INTERFACE:
11 adcroft 1.1 SUBROUTINE MON_STATS_RL(
12 edhill 1.10 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 adcroft 1.1 IMPLICIT NONE
20     #include "SIZE.h"
21     #include "EEPARAMS.h"
22    
23 edhill 1.10 C !INPUT PARAMETERS:
24 adcroft 1.1 INTEGER myNr
25     _RL arr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
26 jmc 1.3 _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 edhill 1.10 _RL theMin, theMax, theMean, theSD, theDel2, theVol
31 adcroft 1.1 INTEGER myThid
32 edhill 1.10 CEOP
33 adcroft 1.1
34 edhill 1.10 C !LOCAL VARIABLES:
35 adcroft 1.1 INTEGER bi,bj,I,J,K
36     INTEGER numPnts
37     LOGICAL noPnts
38     _RL tmpVal,rNumPnts
39 adcroft 1.7 _RL theVar,theVarTile
40 jmc 1.4 _RL tmpVol
41 jmc 1.9 _RL theMeanTile, theSDTile, theDel2Tile, theVolTile
42 adcroft 1.1
43     theMin=0.
44     theMax=0.
45     theMean=0.
46     theSD=0.
47     theVar=0.
48 jmc 1.3 theDel2=0.
49     theVol=0.
50 adcroft 1.1 numPnts=0
51     noPnts=.TRUE.
52    
53     DO bj=myByLo(myThid),myByHi(myThid)
54     DO bi=myBxLo(myThid),myBxHi(myThid)
55 adcroft 1.8 theDel2Tile = 0.
56     theVolTile = 0.
57     theMeanTile = 0.
58     theVarTile = 0.
59 adcroft 1.1 DO K=1,myNr
60     DO J=1,sNy
61     DO I=1,sNx
62     tmpVal=arr(I,J,K,bi,bj)
63 jmc 1.3 IF (arrMask(I,J,K,bi,bj).NE.0. .AND. noPnts) THEN
64 adcroft 1.1 theMin=tmpVal
65     theMax=tmpVal
66     noPnts=.FALSE.
67     ENDIF
68 jmc 1.3 IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
69 adcroft 1.1 theMin=min(theMin,tmpVal)
70     theMax=max(theMax,tmpVal)
71 adcroft 1.7 theDel2Tile = theDel2Tile+0.25*ABS(
72 jmc 1.3 & (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 adcroft 1.1 numPnts=numPnts+1
78 jmc 1.3 tmpVol = arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
79 jmc 1.6 & *arrMask(I,J,K,bi,bj)
80 adcroft 1.7 theVolTile = theVolTile + tmpVol
81     theMeanTile = theMeanTile + tmpVol*tmpVal
82     theVarTile = theVarTile + tmpVol*tmpVal**2
83 adcroft 1.1 ENDIF
84     ENDDO
85     ENDDO
86     ENDDO
87 adcroft 1.7 theDel2 = theDel2 + theDel2Tile
88     theVol = theVol + theVolTile
89     theMean = theMean + theMeanTile
90     theVar = theVar + theVarTile
91 adcroft 1.1 ENDDO
92     ENDDO
93    
94 jmc 1.3 _GLOBAL_SUM_R8(theDel2,myThid)
95     _GLOBAL_SUM_R8(theVol,myThid)
96 adcroft 1.1 _GLOBAL_SUM_R8(theMean,myThid)
97     _GLOBAL_SUM_R8(theVar,myThid)
98     tmpVal=FLOAT(numPnts)
99     _GLOBAL_SUM_R8(tmpVal,myThid)
100 jmc 1.9 numPnts=NINT(tmpVal)
101 adcroft 1.1
102     IF (tmpVal.GT.0.) THEN
103     rNumPnts=1./tmpVal
104 jmc 1.3 theDel2=theDel2*rNumPnts
105     ENDIF
106    
107     IF (theVol.GT.0.) THEN
108     theMean=theMean/theVol
109     theVar=theVar/theVol
110 jmc 1.9 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 adcroft 1.1
117     DO bj=myByLo(myThid),myByHi(myThid)
118     DO bi=myBxLo(myThid),myBxHi(myThid)
119 adcroft 1.7 theSDtile=0.
120 adcroft 1.1 DO K=1,myNr
121     DO J=1,sNy
122     DO I=1,sNx
123     tmpVal=arr(I,J,K,bi,bj)
124 jmc 1.3 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 jmc 1.6 & *arrMask(I,J,K,bi,bj)
128 adcroft 1.7 theSDtile = theSDtile + tmpVol*(tmpVal-theMean)**2
129 adcroft 1.1 ENDIF
130     ENDDO
131     ENDDO
132     ENDDO
133 adcroft 1.7 theSD = theSD + theSDtile
134 adcroft 1.1 ENDDO
135     ENDDO
136    
137     _GLOBAL_SUM_R8(theSD,myThid)
138    
139 jmc 1.3 theSD=sqrt(theSD/theVol)
140 adcroft 1.2 c theSD=sqrt(theVar-theMean**2)
141 adcroft 1.1 ENDIF
142    
143     RETURN
144     END

  ViewVC Help
Powered by ViewVC 1.1.22