/[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.7 - (show annotations) (download)
Mon Oct 15 00:18:40 2007 UTC (16 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59k, checkpoint59j, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61l, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i
Changes since 1.6: +33 -10 lines
use GLOBAL_SUM_TILE instead of _GLOBAL_SUM

1 C $Header: /u/gcmpack/MITgcm/pkg/monitor/mon_stats_latbnd_rl.F,v 1.6 2005/11/04 01:33:05 jmc Exp $
2 C $Name: $
3
4 #include "MONITOR_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP
8 C !ROUTINE: MON_STATS_LATBND_RL
9
10 C !INTERFACE:
11 SUBROUTINE MON_STATS_LATBND_RL(
12 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 IMPLICIT NONE
23 #include "SIZE.h"
24 #include "EEPARAMS.h"
25 INTEGER NLATBND
26 EXTERNAL NLATBND
27
28 C !INPUT PARAMETERS:
29 C nSepBnd :: Number of latitude bands
30 C ySepBnd :: Southern latitude egde (from 2 to nSepBnd, 1 is not used)
31 INTEGER myNr, mskNr, kLoc
32 INTEGER nSepBnd
33 _RS ySepBnd(nSepBnd)
34 _RL arr(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNr,nSx,nSy)
35 _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 _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 CEOP
47
48 C !LOCAL VARIABLES:
49 C msgBuf :: Informational/error meesage buffer
50 CHARACTER*(MAX_LEN_MBUF) msgBuf
51 INTEGER bi,bj,i,j,k,n
52 INTEGER km, k1, k2
53 LOGICAL noPnts(Ny)
54 _RL tmpVal
55 _RL tmpVol
56 INTEGER nSepDim
57 PARAMETER ( nSepDim = 200 )
58 _RL tileVol (nSx,nSy,nSepDim)
59 _RL tileMean(nSx,nSy,nSepDim)
60 _RL tileVar (nSx,nSy,nSepDim)
61
62 C- Check local Dim
63 IF ( nSepBnd .GT. nSepDim ) THEN
64 WRITE(msgBuf,'(A,I6,A)')
65 & 'MON_STATS_LATBND_RL: local array Dim (nSepDim=',nSepDim,
66 & ' ) too small'
67 CALL PRINT_ERROR( msgBuf , myThid)
68 WRITE(msgBuf,'(A,I6)')
69 & 'MON_STATS_LATBND_RL: Need nSepDim to be at least =', nSepBnd
70 CALL PRINT_ERROR( msgBuf , myThid)
71 STOP 'ABNORMAL END: S/R MON_STATS_LATBND_RL'
72 ENDIF
73
74 IF ( kLoc.EQ.0 ) THEN
75 k1 = 1
76 k2 = myNr
77 ELSE
78 k1 = kLoc
79 k2 = kLoc
80 ENDIF
81
82 DO n=1,nSepBnd
83 noPnts(n)=.TRUE.
84 theMin(n)=0.
85 theMax(n)=0.
86 theMean(n)=0.
87 theVar(n)=0.
88 theVol(n)=0.
89 ENDDO
90
91 DO bj=myByLo(myThid),myByHi(myThid)
92 DO bi=myBxLo(myThid),myBxHi(myThid)
93 DO n=1,nSepBnd
94 tileVol (bi,bj,n) = 0.
95 tileMean(bi,bj,n) = 0.
96 tileVar (bi,bj,n) = 0.
97 ENDDO
98 DO k=k1,k2
99 km = MIN(k,mskNr)
100 DO j=1,sNy
101 DO i=1,sNx
102 n = NLATBND(nSepBnd, ySepBnd, arrY(i,j,bi,bj) )
103 tmpVal=arr(i,j,k,bi,bj)
104 IF (arrMask(i,j,km,bi,bj).NE.0. .AND. noPnts(n)) THEN
105 theMin(n)=tmpVal
106 theMax(n)=tmpVal
107 noPnts(n)=.FALSE.
108 ENDIF
109 IF (arrMask(i,j,km,bi,bj).NE.0.) THEN
110 theMin(n)=MIN(theMin(n),tmpVal)
111 theMax(n)=MAX(theMax(n),tmpVal)
112 tmpVol = arrArea(i,j,bi,bj)*arrhFac(i,j,km,bi,bj)*arrDr(k)
113 & *arrMask(i,j,km,bi,bj)
114 tileVol (bi,bj,n) = tileVol (bi,bj,n) + tmpVol
115 tileMean(bi,bj,n) = tileMean(bi,bj,n) + tmpVol*tmpVal
116 tileVar (bi,bj,n) = tileVar (bi,bj,n) + tmpVol*tmpVal*tmpVal
117 ENDIF
118 ENDDO
119 ENDDO
120 ENDDO
121 ENDDO
122 ENDDO
123
124 DO n=1,nSepBnd
125 CALL GLOBAL_SUM_TILE_RL( tileVol(1,1,n) , theVol(n) , myThid )
126 CALL GLOBAL_SUM_TILE_RL( tileMean(1,1,n), theMean(n), myThid )
127 CALL GLOBAL_SUM_TILE_RL( tileVar(1,1,n) , theVar(n) , myThid )
128 ENDDO
129
130 DO n=1,nSepBnd
131 IF (theVol(n).GT.0.) THEN
132 theMean(n)= theMean(n)/theVol(n)
133 theVar(n) = theVar(n) /theVol(n)
134 theVar(n) = theVar(n) -theMean(n)*theMean(n)
135 IF ( noPnts(n) ) theMin(n) = theMean(n)
136 theMin(n) = -theMin(n)
137 _GLOBAL_MAX_R8(theMin(n), myThid)
138 theMin(n)=-theMin(n)
139 IF ( noPnts(n) ) theMax(n) = theMin(n)
140 _GLOBAL_MAX_R8(theMax(n), myThid)
141 ENDIF
142 ENDDO
143
144 RETURN
145 END
146
147 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
148 CBOP
149 C !ROUTINE: NLATBND
150
151 C !INTERFACE:
152 INTEGER FUNCTION NLATBND( nBnd, yBnd, yLoc )
153 IMPLICIT NONE
154
155 C !DESCRIPTION:
156 C Find the latidude band of yLoc in nSep strip
157
158 C !INPUT PARAMETERS:
159 C nBnd :: Number of latitude bands
160 C yBnd :: latitude of southern boundary (for each lat. band)
161 C yLoc :: current latitude
162 INTEGER nBnd
163 _RS yBnd(nBnd)
164 _RS yLoc
165 CEOP
166
167 C !LOCAL VARIABLES:
168 INTEGER n
169
170 NLATBND = 1
171 DO n=2,nBnd
172 IF (yLoc .GT. yBnd(n)) NLATBND = n
173 ENDDO
174
175 RETURN
176 END
177
178 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22