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

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

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


Revision 1.1 - (hide annotations) (download)
Mon Nov 10 22:58:53 2003 UTC (20 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52e_pre, hrcube4, checkpoint52j_post, checkpoint52e_post, hrcube_1, branch-netcdf, checkpoint52d_pre, checkpoint52k_post, checkpoint52b_pre, checkpoint52a_pre, checkpoint52d_post, checkpoint52a_post, checkpoint52b_post, checkpoint52f_post, checkpoint52c_post, checkpoint52i_post, checkpoint52j_pre, checkpoint52i_pre, checkpoint52h_pre, checkpoint52f_pre, hrcube_2, hrcube_3
Branch point for: netcdf-sm0
new S/R: do basic statistic separately on each latitude band

1 jmc 1.1 C $Header: $
2     C $Name: $
3    
4     #include "MONITOR_OPTIONS.h"
5    
6     SUBROUTINE MON_STATS_LATBND_RL(
7     I myNr, nSepBnd, ySepBnd,
8     I arr, arrMask, arrhFac, arrArea, arrY, arrDr,
9     O theMin,theMax,theMean,theVar,theVol,
10     I myThid )
11     C *==========================================================*
12     C | SUBROUTINE MON_STATS_LATBND_RL
13     C | o Calculate bare statistics of global array "_RL arr"
14     C | on each Latitude band (given by ySepBnd)
15     C *==========================================================*
16     C *==========================================================*
17     IMPLICIT NONE
18    
19     C === Global data ===
20     #include "SIZE.h"
21     #include "EEPARAMS.h"
22    
23     C === Routine arguments ===
24     C nSepBnd :: Number of latitude bands
25     C ySepBnd :: latitude band egdes (from 1 to nSepBnd-1)
26     INTEGER myNr
27     INTEGER nSepBnd
28     _RS ySepBnd(nSepBnd)
29     _RL arr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
30     _RS arrMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
31     _RS arrhFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
32     _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
33     _RS arrY(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
34     _RS arrDr(myNr)
35     _RL theMin(nSepBnd)
36     _RL theMax(nSepBnd)
37     _RL theMean(nSepBnd)
38     _RL theVar(nSepBnd)
39     _RL theVol(nSepBnd)
40     INTEGER myThid
41    
42     C === Functions ====
43     INTEGER NLATBND
44     EXTERNAL NLATBND
45    
46     C === Local variables ====
47     INTEGER bi,bj,i,j,k,n
48     INTEGER numPnts
49     LOGICAL noPnts(Ny)
50     _RL tmpVal,rNumPnts
51     _RL tmpVol
52    
53     DO n=1,nSepBnd
54     noPnts(n)=.TRUE.
55     theMin(n)=0.
56     theMax(n)=0.
57     theMean(n)=0.
58     theVar(n)=0.
59     theVol(n)=0.
60     ENDDO
61    
62     DO bj=myByLo(myThid),myByHi(myThid)
63     DO bi=myBxLo(myThid),myBxHi(myThid)
64     DO k=1,myNr
65     DO j=1,sNy
66     DO i=1,sNx
67     n = NLATBND(nSepBnd, ySepBnd, arrY(i,j,bi,bj) )
68     tmpVal=arr(i,j,k,bi,bj)
69     IF (arrMask(i,j,k,bi,bj).NE.0. .AND. noPnts(n)) THEN
70     theMin(n)=tmpVal
71     theMax(n)=tmpVal
72     noPnts(n)=.FALSE.
73     ENDIF
74     IF (arrMask(i,j,k,bi,bj).NE.0.) THEN
75     theMin(n)=min(theMin(n),tmpVal)
76     theMax(n)=max(theMax(n),tmpVal)
77     tmpVol = arrArea(i,j,bi,bj)*arrhFac(i,j,k,bi,bj)*arrDr(k)
78     & *arrMask(i,j,k,bi,bj)
79     theVol(n) = theVol(n) + tmpVol
80     theMean(n)=theMean(n) + tmpVol*tmpVal
81     theVar(n) = theVar(n) + tmpVol*tmpVal*tmpVal
82     ENDIF
83     ENDDO
84     ENDDO
85     ENDDO
86     ENDDO
87     ENDDO
88    
89     DO n=1,nSepBnd
90     theMin(n)=-theMin(n)
91     _GLOBAL_MAX_R8(theMin(n), myThid)
92     theMin(n)=-theMin(n)
93     _GLOBAL_MAX_R8(theMax(n), myThid)
94     _GLOBAL_SUM_R8(theVol(n), myThid)
95     _GLOBAL_SUM_R8(theMean(n),myThid)
96     _GLOBAL_SUM_R8(theVar(n), myThid)
97     ENDDO
98    
99     DO n=1,nSepBnd
100     IF (theVol(n).GT.0.) THEN
101     theMean(n)= theMean(n)/theVol(n)
102     theVar(n) = theVar(n) /theVol(n)
103     ENDIF
104     ENDDO
105    
106     RETURN
107     END
108    
109     CBOP
110     C !ROUTINE: NLATBND
111    
112     C !INTERFACE:
113     INTEGER FUNCTION NLATBND( nBnd, yBnd, yLoc )
114     IMPLICIT NONE
115    
116     C !DESCRIPTION:
117     C *==========================================================*
118     C | FUNCTION NLATBND
119     C | o Find the latidude band of yLoc in nSep strip
120     C *==========================================================*
121     C
122     C !INPUT PARAMETERS:
123     C nBnd :: Nb of latitude band
124     C yBnd :: latitude of band boundaries
125     C yLoc :: current latitude
126     INTEGER nBnd
127     _RS yBnd(nBnd)
128     _RS yLoc
129    
130     C !LOCAL VARIABLES:
131     INTEGER n
132    
133     NLATBND = nBnd
134     DO n=1,nBnd-1
135     IF (yLoc .LE. yBnd(n)) NLATBND = n
136     ENDDO
137    
138     RETURN
139     END

  ViewVC Help
Powered by ViewVC 1.1.22