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

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

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


Revision 1.2 - (show annotations) (download)
Wed Mar 3 14:15:38 2004 UTC (20 years, 3 months ago) by jmc
Branch: MAIN
Changes since 1.1: +22 -11 lines
add 2 arguments to make it more flexible

1 C $Header: /u/gcmpack/MITgcm/pkg/monitor/mon_stats_latbnd_rl.F,v 1.1 2003/11/10 22:58:53 jmc Exp $
2 C $Name: $
3
4 #include "MONITOR_OPTIONS.h"
5
6 SUBROUTINE MON_STATS_LATBND_RL(
7 I myNr, mskNr, kLoc, 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, mskNr, kLoc
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,mskNr,nSx,nSy)
31 _RS arrhFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,mskNr,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 km, k1, k2
49 INTEGER numPnts
50 LOGICAL noPnts(Ny)
51 _RL tmpVal,rNumPnts
52 _RL tmpVol
53
54 C- set k index range [k1,k2]
55 IF ( kLoc.EQ.0 ) THEN
56 k1 = 1
57 k2 = myNr
58 ELSE
59 k1 = kLoc
60 k2 = kLoc
61 ENDIF
62
63 DO n=1,nSepBnd
64 noPnts(n)=.TRUE.
65 theMin(n)=0.
66 theMax(n)=0.
67 theMean(n)=0.
68 theVar(n)=0.
69 theVol(n)=0.
70 ENDDO
71
72 DO bj=myByLo(myThid),myByHi(myThid)
73 DO bi=myBxLo(myThid),myBxHi(myThid)
74 DO k=k1,k2
75 km = MIN(k,mskNr)
76 DO j=1,sNy
77 DO i=1,sNx
78 n = NLATBND(nSepBnd, ySepBnd, arrY(i,j,bi,bj) )
79 tmpVal=arr(i,j,k,bi,bj)
80 IF (arrMask(i,j,km,bi,bj).NE.0. .AND. noPnts(n)) THEN
81 theMin(n)=tmpVal
82 theMax(n)=tmpVal
83 noPnts(n)=.FALSE.
84 ENDIF
85 IF (arrMask(i,j,km,bi,bj).NE.0.) THEN
86 theMin(n)=min(theMin(n),tmpVal)
87 theMax(n)=max(theMax(n),tmpVal)
88 tmpVol = arrArea(i,j,bi,bj)*arrhFac(i,j,km,bi,bj)*arrDr(k)
89 & *arrMask(i,j,km,bi,bj)
90 theVol(n) = theVol(n) + tmpVol
91 theMean(n)= theMean(n)+ tmpVol*tmpVal
92 theVar(n) = theVar(n) + tmpVol*tmpVal*tmpVal
93 ENDIF
94 ENDDO
95 ENDDO
96 ENDDO
97 ENDDO
98 ENDDO
99
100 DO n=1,nSepBnd
101 theMin(n)=-theMin(n)
102 _GLOBAL_MAX_R8(theMin(n), myThid)
103 theMin(n)=-theMin(n)
104 _GLOBAL_MAX_R8(theMax(n), myThid)
105 _GLOBAL_SUM_R8(theVol(n), myThid)
106 _GLOBAL_SUM_R8(theMean(n),myThid)
107 _GLOBAL_SUM_R8(theVar(n), myThid)
108 ENDDO
109
110 DO n=1,nSepBnd
111 IF (theVol(n).GT.0.) THEN
112 theMean(n)= theMean(n)/theVol(n)
113 theVar(n) = theVar(n) /theVol(n)
114 ENDIF
115 ENDDO
116
117 RETURN
118 END
119
120 CBOP
121 C !ROUTINE: NLATBND
122
123 C !INTERFACE:
124 INTEGER FUNCTION NLATBND( nBnd, yBnd, yLoc )
125 IMPLICIT NONE
126
127 C !DESCRIPTION:
128 C *==========================================================*
129 C | FUNCTION NLATBND
130 C | o Find the latidude band of yLoc in nSep strip
131 C *==========================================================*
132 C
133 C !INPUT PARAMETERS:
134 C nBnd :: Nb of latitude band
135 C yBnd :: latitude of band boundaries
136 C yLoc :: current latitude
137 INTEGER nBnd
138 _RS yBnd(nBnd)
139 _RS yLoc
140
141 C !LOCAL VARIABLES:
142 INTEGER n
143
144 NLATBND = nBnd
145 DO n=1,nBnd-1
146 IF (yLoc .LE. yBnd(n)) NLATBND = n
147 ENDDO
148
149 RETURN
150 END

  ViewVC Help
Powered by ViewVC 1.1.22