/[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.3 - (hide annotations) (download)
Thu Nov 8 16:47:34 2001 UTC (22 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint44e_post, checkpoint44f_post, checkpoint43a-release1mods, chkpt44d_post, checkpoint44e_pre, release1-branch_tutorials, chkpt44a_post, checkpoint44h_pre, chkpt44c_pre, checkpoint45a_post, checkpoint44g_post, checkpoint45b_post, release1-branch-end, release1_final_v1, checkpoint44b_post, checkpoint45c_post, checkpoint44h_post, chkpt44a_pre, checkpoint44b_pre, checkpoint44, checkpoint45, chkpt44c_post, checkpoint44f_pre, release1-branch_branchpoint
Branch point for: release1_final, release1-branch
Changes since 1.2: +38 -12 lines
update MONITOR:
* compute volume mean and (volume) standard deviation (replace the
  previous one)
* add diagnostic of 2dx,2dy grid noise for each field.
* volume mean and volume integral of KE

1 jmc 1.3 C $Header: /u/gcmpack/models/MITgcmUV/pkg/monitor/mon_stats_rl.F,v 1.2 2001/06/04 20:04:24 adcroft Exp $
2 adcroft 1.2 C $Name: $
3 adcroft 1.1
4     #include "CPP_OPTIONS.h"
5    
6     SUBROUTINE MON_STATS_RL(
7 jmc 1.3 I myNr, arr, arrMask,arrhFac, arrArea, arrDr,
8     O theMin,theMax,theMean,theSD,theDel2,
9 adcroft 1.1 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 jmc 1.3 _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 adcroft 1.1 _RL theMin
29     _RL theMax
30     _RL theMean
31     _RL theSD
32 jmc 1.3 _RL theDel2
33 adcroft 1.1 INTEGER myThid
34    
35     C === Local variables ====
36     INTEGER bi,bj,I,J,K
37     INTEGER numPnts
38     LOGICAL noPnts
39     _RL tmpVal,rNumPnts
40     _RL theVar
41 jmc 1.3 _RL theVol, tmpVol
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     DO K=1,myNr
56     DO J=1,sNy
57     DO I=1,sNx
58     tmpVal=arr(I,J,K,bi,bj)
59 jmc 1.3 c IF (tmpVal.NE.0. .AND. noPnts) THEN
60     IF (arrMask(I,J,K,bi,bj).NE.0. .AND. noPnts) THEN
61 adcroft 1.1 theMin=tmpVal
62     theMax=tmpVal
63     noPnts=.FALSE.
64     ENDIF
65 jmc 1.3 c IF (tmpVal.NE.0.) THEN
66     IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
67 adcroft 1.1 theMin=min(theMin,tmpVal)
68     theMax=max(theMax,tmpVal)
69 jmc 1.3 theDel2 = theDel2+0.25*ABS(
70     & (arr(I+1,J,K,bi,bj)-tmpVal)*arrMask(I+1,J,K,bi,bj)
71     & +(arr(I-1,J,K,bi,bj)-tmpVal)*arrMask(I-1,J,K,bi,bj)
72     & +(arr(I,J+1,K,bi,bj)-tmpVal)*arrMask(I,J+1,K,bi,bj)
73     & +(arr(I,J-1,K,bi,bj)-tmpVal)*arrMask(I,J-1,K,bi,bj)
74     & )
75 adcroft 1.1 numPnts=numPnts+1
76 jmc 1.3 tmpVol = arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
77     theVol = theVol + tmpVol
78     theMean = theMean + tmpVol*tmpVal
79     theVar = theVar + tmpVol*tmpVal**2
80 adcroft 1.1 ENDIF
81     ENDDO
82     ENDDO
83     ENDDO
84     ENDDO
85     ENDDO
86    
87     theMin=-theMin
88     _GLOBAL_MAX_R8(theMin,myThid)
89     theMin=-theMin
90     _GLOBAL_MAX_R8(theMax,myThid)
91 jmc 1.3 _GLOBAL_SUM_R8(theDel2,myThid)
92     _GLOBAL_SUM_R8(theVol,myThid)
93 adcroft 1.1 _GLOBAL_SUM_R8(theMean,myThid)
94     _GLOBAL_SUM_R8(theVar,myThid)
95     tmpVal=FLOAT(numPnts)
96     _GLOBAL_SUM_R8(tmpVal,myThid)
97     numPnts=INT(tmpVal+0.5)
98    
99     IF (tmpVal.GT.0.) THEN
100     rNumPnts=1./tmpVal
101 jmc 1.3 theDel2=theDel2*rNumPnts
102     ENDIF
103    
104     IF (theVol.GT.0.) THEN
105     theMean=theMean/theVol
106     theVar=theVar/theVol
107 adcroft 1.1
108     DO bj=myByLo(myThid),myByHi(myThid)
109     DO bi=myBxLo(myThid),myBxHi(myThid)
110     DO K=1,myNr
111     DO J=1,sNy
112     DO I=1,sNx
113     tmpVal=arr(I,J,K,bi,bj)
114 jmc 1.3 c IF (tmpVal.NE.0.) THEN
115     IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
116     tmpVol=arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
117     theSD = theSD + tmpVol*(tmpVal-theMean)**2
118 adcroft 1.1 ENDIF
119     ENDDO
120     ENDDO
121     ENDDO
122     ENDDO
123     ENDDO
124    
125     _GLOBAL_SUM_R8(theSD,myThid)
126    
127 jmc 1.3 theSD=sqrt(theSD/theVol)
128 adcroft 1.2 c theSD=sqrt(theVar-theMean**2)
129 adcroft 1.1 ENDIF
130    
131     RETURN
132     END

  ViewVC Help
Powered by ViewVC 1.1.22