/[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.4 - (show annotations) (download)
Sat Jun 15 03:14:53 2002 UTC (21 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint46n_post, checkpoint47e_post, checkpoint46l_post, checkpoint46g_pre, checkpoint47c_post, checkpoint50c_post, checkpoint46f_post, checkpoint48e_post, checkpoint50c_pre, checkpoint46b_post, checkpoint48i_post, checkpoint46l_pre, checkpoint50, checkpoint50d_post, checkpoint50b_pre, checkpoint48b_post, checkpoint48c_pre, checkpoint47d_pre, checkpoint47a_post, checkpoint48d_pre, checkpoint47i_post, checkpoint47d_post, checkpoint46d_pre, checkpoint48d_post, checkpoint48f_post, checkpoint45d_post, checkpoint46j_pre, checkpoint48h_post, checkpoint46a_post, checkpoint47g_post, checkpoint46j_post, checkpoint46k_post, checkpoint48a_post, checkpoint50a_post, checkpoint47j_post, branch-exfmods-tag, checkpoint46e_pre, checkpoint48c_post, checkpoint46b_pre, checkpoint46c_pre, checkpoint46, checkpoint47b_post, checkpoint46h_pre, checkpoint46m_post, checkpoint46a_pre, checkpoint46g_post, checkpoint47f_post, checkpoint46i_post, checkpoint46c_post, checkpoint50d_pre, checkpoint46e_post, checkpoint47, checkpoint48, checkpoint49, checkpoint46h_post, checkpoint48g_post, checkpoint47h_post, checkpoint46d_post, checkpoint50b_post
Branch point for: branch-exfmods-curt
Changes since 1.3: +4 -3 lines
* monitor output : add ocean volume output and change definition of KE
  => allow to check conservation of Energy with and without NLFS

1 C $Header: /u/gcmpack/MITgcm/pkg/monitor/mon_stats_rl.F,v 1.3 2001/11/08 16:47:34 jmc Exp $
2 C $Name: $
3
4 #include "CPP_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 theVol = theVol + tmpVol
79 theMean = theMean + tmpVol*tmpVal
80 theVar = theVar + tmpVol*tmpVal**2
81 ENDIF
82 ENDDO
83 ENDDO
84 ENDDO
85 ENDDO
86 ENDDO
87
88 theMin=-theMin
89 _GLOBAL_MAX_R8(theMin,myThid)
90 theMin=-theMin
91 _GLOBAL_MAX_R8(theMax,myThid)
92 _GLOBAL_SUM_R8(theDel2,myThid)
93 _GLOBAL_SUM_R8(theVol,myThid)
94 _GLOBAL_SUM_R8(theMean,myThid)
95 _GLOBAL_SUM_R8(theVar,myThid)
96 tmpVal=FLOAT(numPnts)
97 _GLOBAL_SUM_R8(tmpVal,myThid)
98 numPnts=INT(tmpVal+0.5)
99
100 IF (tmpVal.GT.0.) THEN
101 rNumPnts=1./tmpVal
102 theDel2=theDel2*rNumPnts
103 ENDIF
104
105 IF (theVol.GT.0.) THEN
106 theMean=theMean/theVol
107 theVar=theVar/theVol
108
109 DO bj=myByLo(myThid),myByHi(myThid)
110 DO bi=myBxLo(myThid),myBxHi(myThid)
111 DO K=1,myNr
112 DO J=1,sNy
113 DO I=1,sNx
114 tmpVal=arr(I,J,K,bi,bj)
115 c IF (tmpVal.NE.0.) THEN
116 IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
117 tmpVol=arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
118 theSD = theSD + tmpVol*(tmpVal-theMean)**2
119 ENDIF
120 ENDDO
121 ENDDO
122 ENDDO
123 ENDDO
124 ENDDO
125
126 _GLOBAL_SUM_R8(theSD,myThid)
127
128 theSD=sqrt(theSD/theVol)
129 c theSD=sqrt(theVar-theMean**2)
130 ENDIF
131
132 RETURN
133 END

  ViewVC Help
Powered by ViewVC 1.1.22