/[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.8 - (hide annotations) (download)
Thu Feb 19 21:02:39 2004 UTC (20 years, 4 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint52k_post
Changes since 1.7: +5 -5 lines
Fixed GLARING error that I put in deliberately to see if anyone cares or
checks what's going on.
 - this is the cause of NaN's reported by Dimitris and is indeed because
   of the "portability" changes I made.
 - odd that it worked under ifc but then Intel are brilliant ...
 - ... me too

1 adcroft 1.8 C $Header: /u/gcmpack/MITgcm/pkg/monitor/mon_stats_rl.F,v 1.7 2004/02/06 19:59:36 adcroft Exp $
2 adcroft 1.2 C $Name: $
3 adcroft 1.1
4 adcroft 1.5 #include "MONITOR_OPTIONS.h"
5 adcroft 1.1
6     SUBROUTINE MON_STATS_RL(
7 jmc 1.3 I myNr, arr, arrMask,arrhFac, arrArea, arrDr,
8 jmc 1.4 O theMin,theMax,theMean,theSD,theDel2,theVol,
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 adcroft 1.7 _RL theMean,theMeanTile
31     _RL theSD,theSDTile
32     _RL theDel2,theDel2Tile
33     _RL theVol,theVolTile
34 adcroft 1.1 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 adcroft 1.7 _RL theVar,theVarTile
42 jmc 1.4 _RL tmpVol
43 adcroft 1.1
44     theMin=0.
45     theMax=0.
46     theMean=0.
47     theSD=0.
48     theVar=0.
49 jmc 1.3 theDel2=0.
50     theVol=0.
51 adcroft 1.1 numPnts=0
52     noPnts=.TRUE.
53    
54     DO bj=myByLo(myThid),myByHi(myThid)
55     DO bi=myBxLo(myThid),myBxHi(myThid)
56 adcroft 1.8 theDel2Tile = 0.
57     theVolTile = 0.
58     theMeanTile = 0.
59     theVarTile = 0.
60 adcroft 1.1 DO K=1,myNr
61     DO J=1,sNy
62     DO I=1,sNx
63     tmpVal=arr(I,J,K,bi,bj)
64 jmc 1.3 c IF (tmpVal.NE.0. .AND. noPnts) THEN
65     IF (arrMask(I,J,K,bi,bj).NE.0. .AND. noPnts) THEN
66 adcroft 1.1 theMin=tmpVal
67     theMax=tmpVal
68     noPnts=.FALSE.
69     ENDIF
70 jmc 1.3 c IF (tmpVal.NE.0.) THEN
71     IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
72 adcroft 1.1 theMin=min(theMin,tmpVal)
73     theMax=max(theMax,tmpVal)
74 adcroft 1.7 theDel2Tile = theDel2Tile+0.25*ABS(
75 jmc 1.3 & (arr(I+1,J,K,bi,bj)-tmpVal)*arrMask(I+1,J,K,bi,bj)
76     & +(arr(I-1,J,K,bi,bj)-tmpVal)*arrMask(I-1,J,K,bi,bj)
77     & +(arr(I,J+1,K,bi,bj)-tmpVal)*arrMask(I,J+1,K,bi,bj)
78     & +(arr(I,J-1,K,bi,bj)-tmpVal)*arrMask(I,J-1,K,bi,bj)
79     & )
80 adcroft 1.1 numPnts=numPnts+1
81 jmc 1.3 tmpVol = arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
82 jmc 1.6 & *arrMask(I,J,K,bi,bj)
83 adcroft 1.7 theVolTile = theVolTile + tmpVol
84     theMeanTile = theMeanTile + tmpVol*tmpVal
85     theVarTile = theVarTile + tmpVol*tmpVal**2
86 adcroft 1.1 ENDIF
87     ENDDO
88     ENDDO
89     ENDDO
90 adcroft 1.7 theDel2 = theDel2 + theDel2Tile
91     theVol = theVol + theVolTile
92     theMean = theMean + theMeanTile
93     theVar = theVar + theVarTile
94 adcroft 1.1 ENDDO
95     ENDDO
96    
97     theMin=-theMin
98     _GLOBAL_MAX_R8(theMin,myThid)
99     theMin=-theMin
100     _GLOBAL_MAX_R8(theMax,myThid)
101 jmc 1.3 _GLOBAL_SUM_R8(theDel2,myThid)
102     _GLOBAL_SUM_R8(theVol,myThid)
103 adcroft 1.1 _GLOBAL_SUM_R8(theMean,myThid)
104     _GLOBAL_SUM_R8(theVar,myThid)
105     tmpVal=FLOAT(numPnts)
106     _GLOBAL_SUM_R8(tmpVal,myThid)
107     numPnts=INT(tmpVal+0.5)
108    
109     IF (tmpVal.GT.0.) THEN
110     rNumPnts=1./tmpVal
111 jmc 1.3 theDel2=theDel2*rNumPnts
112     ENDIF
113    
114     IF (theVol.GT.0.) THEN
115     theMean=theMean/theVol
116     theVar=theVar/theVol
117 adcroft 1.1
118     DO bj=myByLo(myThid),myByHi(myThid)
119     DO bi=myBxLo(myThid),myBxHi(myThid)
120 adcroft 1.7 theSDtile=0.
121 adcroft 1.1 DO K=1,myNr
122     DO J=1,sNy
123     DO I=1,sNx
124     tmpVal=arr(I,J,K,bi,bj)
125 jmc 1.3 c IF (tmpVal.NE.0.) THEN
126     IF (arrMask(I,J,K,bi,bj).NE.0.) THEN
127     tmpVol=arrArea(I,J,bi,bj)*arrhFac(I,J,K,bi,bj)*arrDr(K)
128 jmc 1.6 & *arrMask(I,J,K,bi,bj)
129 adcroft 1.7 theSDtile = theSDtile + tmpVol*(tmpVal-theMean)**2
130 adcroft 1.1 ENDIF
131     ENDDO
132     ENDDO
133     ENDDO
134 adcroft 1.7 theSD = theSD + theSDtile
135 adcroft 1.1 ENDDO
136     ENDDO
137    
138     _GLOBAL_SUM_R8(theSD,myThid)
139    
140 jmc 1.3 theSD=sqrt(theSD/theVol)
141 adcroft 1.2 c theSD=sqrt(theVar-theMean**2)
142 adcroft 1.1 ENDIF
143    
144     RETURN
145     END

  ViewVC Help
Powered by ViewVC 1.1.22