/[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.6 - (show annotations) (download)
Mon Nov 10 23:03:29 2003 UTC (20 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52d_pre, checkpoint52f_post, checkpoint52i_pre, hrcube_1, hrcube_2, checkpoint52e_pre, checkpoint52e_post, checkpoint52b_pre, checkpoint52b_post, checkpoint52c_post, checkpoint52f_pre, checkpoint52d_post, checkpoint52a_pre, checkpoint52i_post, checkpoint52h_pre, branch-netcdf, checkpoint52a_post
Branch point for: netcdf-sm0
Changes since 1.5: +3 -1 lines
multiply by the mask: no effect for usual fields; usefull for fractional
 fields (e.g., sea-ice, land)

1 C $Header: /u/gcmpack/MITgcm/pkg/monitor/mon_stats_rl.F,v 1.5 2003/05/13 18:18:05 adcroft Exp $
2 C $Name: $
3
4 #include "MONITOR_OPTIONS.h"
5
6 SUBROUTINE MON_STATS_RL(
7 I myNr, arr, arrMask,arrhFac, arrArea, arrDr,
8 O theMin,theMax,theMean,theSD,theDel2,theVol,
9 I myThid )
10 C /==========================================================\
11 C | SUBROUTINE MON_STATS_RL |
12 C | o Calculate bare statistics of global array "_RL arr" |
13 C |==========================================================|
14 C \==========================================================/
15 IMPLICIT NONE
16
17 C === Global data ===
18 #include "SIZE.h"
19 #include "EEPARAMS.h"
20
21 C === Routine arguments ===
22 INTEGER myNr
23 _RL arr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
24 _RS arrMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
25 _RS arrhFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
26 _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
27 _RS arrDr(myNr)
28 _RL theMin
29 _RL theMax
30 _RL theMean
31 _RL theSD
32 _RL theDel2
33 _RL theVol
34 INTEGER myThid
35
36 C === Local variables ====
37 INTEGER bi,bj,I,J,K
38 INTEGER numPnts
39 LOGICAL noPnts
40 _RL tmpVal,rNumPnts
41 _RL theVar
42 _RL tmpVol
43
44 theMin=0.
45 theMax=0.
46 theMean=0.
47 theSD=0.
48 theVar=0.
49 theDel2=0.
50 theVol=0.
51 numPnts=0
52 noPnts=.TRUE.
53
54 DO bj=myByLo(myThid),myByHi(myThid)
55 DO bi=myBxLo(myThid),myBxHi(myThid)
56 DO K=1,myNr
57 DO J=1,sNy
58 DO I=1,sNx
59 tmpVal=arr(I,J,K,bi,bj)
60 c IF (tmpVal.NE.0. .AND. noPnts) THEN
61 IF (arrMask(I,J,K,bi,bj).NE.0. .AND. noPnts) THEN
62 theMin=tmpVal
63 theMax=tmpVal
64 noPnts=.FALSE.
65 ENDIF
66 c IF (tmpVal.NE.0.) THEN
67 IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
68 theMin=min(theMin,tmpVal)
69 theMax=max(theMax,tmpVal)
70 theDel2 = theDel2+0.25*ABS(
71 & (arr(I+1,J,K,bi,bj)-tmpVal)*arrMask(I+1,J,K,bi,bj)
72 & +(arr(I-1,J,K,bi,bj)-tmpVal)*arrMask(I-1,J,K,bi,bj)
73 & +(arr(I,J+1,K,bi,bj)-tmpVal)*arrMask(I,J+1,K,bi,bj)
74 & +(arr(I,J-1,K,bi,bj)-tmpVal)*arrMask(I,J-1,K,bi,bj)
75 & )
76 numPnts=numPnts+1
77 tmpVol = arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
78 & *arrMask(I,J,K,bi,bj)
79 theVol = theVol + tmpVol
80 theMean = theMean + tmpVol*tmpVal
81 theVar = theVar + tmpVol*tmpVal**2
82 ENDIF
83 ENDDO
84 ENDDO
85 ENDDO
86 ENDDO
87 ENDDO
88
89 theMin=-theMin
90 _GLOBAL_MAX_R8(theMin,myThid)
91 theMin=-theMin
92 _GLOBAL_MAX_R8(theMax,myThid)
93 _GLOBAL_SUM_R8(theDel2,myThid)
94 _GLOBAL_SUM_R8(theVol,myThid)
95 _GLOBAL_SUM_R8(theMean,myThid)
96 _GLOBAL_SUM_R8(theVar,myThid)
97 tmpVal=FLOAT(numPnts)
98 _GLOBAL_SUM_R8(tmpVal,myThid)
99 numPnts=INT(tmpVal+0.5)
100
101 IF (tmpVal.GT.0.) THEN
102 rNumPnts=1./tmpVal
103 theDel2=theDel2*rNumPnts
104 ENDIF
105
106 IF (theVol.GT.0.) THEN
107 theMean=theMean/theVol
108 theVar=theVar/theVol
109
110 DO bj=myByLo(myThid),myByHi(myThid)
111 DO bi=myBxLo(myThid),myBxHi(myThid)
112 DO K=1,myNr
113 DO J=1,sNy
114 DO I=1,sNx
115 tmpVal=arr(I,J,K,bi,bj)
116 c IF (tmpVal.NE.0.) THEN
117 IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
118 tmpVol=arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
119 & *arrMask(I,J,K,bi,bj)
120 theSD = theSD + tmpVol*(tmpVal-theMean)**2
121 ENDIF
122 ENDDO
123 ENDDO
124 ENDDO
125 ENDDO
126 ENDDO
127
128 _GLOBAL_SUM_R8(theSD,myThid)
129
130 theSD=sqrt(theSD/theVol)
131 c theSD=sqrt(theVar-theMean**2)
132 ENDIF
133
134 RETURN
135 END

  ViewVC Help
Powered by ViewVC 1.1.22