/[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.6 - (hide annotations) (download)
Fri Nov 4 01:33:05 2005 UTC (18 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58e_post, mitgcm_mapl_00, checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint57y_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint57y_pre, checkpoint58q_post, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59h, checkpoint59, checkpoint58, checkpoint58f_post, checkpoint57x_post, checkpoint58d_post, checkpoint58c_post, checkpoint58a_post, checkpoint58i_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint58b_post, checkpoint58m_post
Changes since 1.5: +2 -3 lines
remove unused variables (reduces number of compiler warning)

1 jmc 1.6 C $Header: /u/gcmpack/MITgcm/pkg/monitor/mon_stats_latbnd_rl.F,v 1.5 2004/04/03 04:57:12 edhill Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "MONITOR_OPTIONS.h"
5    
6 edhill 1.5 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7     CBOP
8     C !ROUTINE: MON_STATS_LATBND_RL
9    
10     C !INTERFACE:
11 jmc 1.1 SUBROUTINE MON_STATS_LATBND_RL(
12 edhill 1.5 I myNr, mskNr, kLoc, nSepBnd, ySepBnd,
13     I arr, arrMask, arrhFac, arrArea, arrY, arrDr,
14     O theMin,theMax,theMean,theVar,theVol,
15     I myThid )
16    
17     C !DESCRIPTION:
18     C Calculate bare statistics of global array "\_RL arr" on each
19     C Latitude band (given by \texttt{ySepBnd}).
20    
21     C !USES:
22 jmc 1.1 IMPLICIT NONE
23     #include "SIZE.h"
24     #include "EEPARAMS.h"
25 edhill 1.5 INTEGER NLATBND
26     EXTERNAL NLATBND
27 jmc 1.1
28 edhill 1.5 C !INPUT PARAMETERS:
29 jmc 1.1 C nSepBnd :: Number of latitude bands
30 jmc 1.3 C ySepBnd :: Southern latitude egde (from 2 to nSepBnd, 1 is not used)
31 jmc 1.2 INTEGER myNr, mskNr, kLoc
32 jmc 1.1 INTEGER nSepBnd
33     _RS ySepBnd(nSepBnd)
34     _RL arr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
35 jmc 1.2 _RS arrMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy,mskNr,nSx,nSy)
36     _RS arrhFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,mskNr,nSx,nSy)
37 jmc 1.1 _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
38     _RS arrY(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
39     _RS arrDr(myNr)
40     _RL theMin(nSepBnd)
41     _RL theMax(nSepBnd)
42     _RL theMean(nSepBnd)
43     _RL theVar(nSepBnd)
44     _RL theVol(nSepBnd)
45     INTEGER myThid
46 edhill 1.5 CEOP
47 jmc 1.1
48 edhill 1.5 C !LOCAL VARIABLES:
49 jmc 1.1 INTEGER bi,bj,i,j,k,n
50 jmc 1.2 INTEGER km, k1, k2
51 jmc 1.1 LOGICAL noPnts(Ny)
52 jmc 1.6 _RL tmpVal
53 jmc 1.1 _RL tmpVol
54    
55 jmc 1.2 C- set k index range [k1,k2]
56     IF ( kLoc.EQ.0 ) THEN
57     k1 = 1
58     k2 = myNr
59     ELSE
60     k1 = kLoc
61     k2 = kLoc
62     ENDIF
63    
64 jmc 1.1 DO n=1,nSepBnd
65     noPnts(n)=.TRUE.
66     theMin(n)=0.
67     theMax(n)=0.
68     theMean(n)=0.
69     theVar(n)=0.
70     theVol(n)=0.
71     ENDDO
72    
73     DO bj=myByLo(myThid),myByHi(myThid)
74     DO bi=myBxLo(myThid),myBxHi(myThid)
75 jmc 1.2 DO k=k1,k2
76     km = MIN(k,mskNr)
77 jmc 1.1 DO j=1,sNy
78     DO i=1,sNx
79     n = NLATBND(nSepBnd, ySepBnd, arrY(i,j,bi,bj) )
80     tmpVal=arr(i,j,k,bi,bj)
81 jmc 1.2 IF (arrMask(i,j,km,bi,bj).NE.0. .AND. noPnts(n)) THEN
82 jmc 1.1 theMin(n)=tmpVal
83     theMax(n)=tmpVal
84     noPnts(n)=.FALSE.
85     ENDIF
86 jmc 1.2 IF (arrMask(i,j,km,bi,bj).NE.0.) THEN
87 jmc 1.3 theMin(n)=MIN(theMin(n),tmpVal)
88     theMax(n)=MAX(theMax(n),tmpVal)
89 jmc 1.2 tmpVol = arrArea(i,j,bi,bj)*arrhFac(i,j,km,bi,bj)*arrDr(k)
90     & *arrMask(i,j,km,bi,bj)
91 jmc 1.1 theVol(n) = theVol(n) + tmpVol
92 jmc 1.2 theMean(n)= theMean(n)+ tmpVol*tmpVal
93 jmc 1.1 theVar(n) = theVar(n) + tmpVol*tmpVal*tmpVal
94     ENDIF
95     ENDDO
96     ENDDO
97     ENDDO
98     ENDDO
99     ENDDO
100    
101     DO n=1,nSepBnd
102     _GLOBAL_SUM_R8(theVol(n), myThid)
103     _GLOBAL_SUM_R8(theMean(n),myThid)
104     _GLOBAL_SUM_R8(theVar(n), myThid)
105     ENDDO
106    
107     DO n=1,nSepBnd
108     IF (theVol(n).GT.0.) THEN
109     theMean(n)= theMean(n)/theVol(n)
110     theVar(n) = theVar(n) /theVol(n)
111 jmc 1.4 theVar(n) = theVar(n) -theMean(n)*theMean(n)
112     IF ( noPnts(n) ) theMin(n) = theMean(n)
113     theMin(n) = -theMin(n)
114     _GLOBAL_MAX_R8(theMin(n), myThid)
115     theMin(n)=-theMin(n)
116     IF ( noPnts(n) ) theMax(n) = theMin(n)
117     _GLOBAL_MAX_R8(theMax(n), myThid)
118 jmc 1.1 ENDIF
119     ENDDO
120    
121     RETURN
122     END
123    
124 edhill 1.5 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
125 jmc 1.1 CBOP
126     C !ROUTINE: NLATBND
127    
128     C !INTERFACE:
129     INTEGER FUNCTION NLATBND( nBnd, yBnd, yLoc )
130     IMPLICIT NONE
131    
132     C !DESCRIPTION:
133 edhill 1.5 C Find the latidude band of yLoc in nSep strip
134    
135 jmc 1.1 C !INPUT PARAMETERS:
136 jmc 1.3 C nBnd :: Number of latitude bands
137     C yBnd :: latitude of southern boundary (for each lat. band)
138 jmc 1.1 C yLoc :: current latitude
139     INTEGER nBnd
140     _RS yBnd(nBnd)
141     _RS yLoc
142 edhill 1.5 CEOP
143 jmc 1.1
144     C !LOCAL VARIABLES:
145     INTEGER n
146    
147 jmc 1.3 NLATBND = 1
148     DO n=2,nBnd
149     IF (yLoc .GT. yBnd(n)) NLATBND = n
150 jmc 1.1 ENDDO
151    
152     RETURN
153     END
154 edhill 1.5
155     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22