/[MITgcm]/MITgcm/pkg/diagnostics/diagstats_local.F
ViewVC logotype

Annotation of /MITgcm/pkg/diagnostics/diagstats_local.F

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


Revision 1.4 - (hide annotations) (download)
Mon Jul 11 19:02:17 2005 UTC (18 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint57o_post, checkpoint57m_post, checkpoint57s_post, checkpoint57v_post, checkpoint57r_post, checkpoint57n_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint57q_post, checkpoint57l_post
Changes since 1.3: +50 -24 lines
add option to fill a squared diagnostics directly

1 jmc 1.4 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagstats_local.F,v 1.3 2005/07/10 00:57:18 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "DIAG_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: DIAGSTATS_LOCAL
8     C !INTERFACE:
9     SUBROUTINE DIAGSTATS_LOCAL(
10     U statFld,
11 jmc 1.4 I inpFld, frcFld,
12     I scaleFact, power, useFract, sizF,
13 jmc 1.1 I sizI1,sizI2,sizJ1,sizJ2,sizK,sizTx,sizTy,
14     I iRun,jRun,kIn,biIn,bjIn,
15     I k,bi,bj, region2fill, ndId, parsFld,
16     I myThid)
17    
18     C !DESCRIPTION:
19 jmc 1.2 C Update array statFld
20 jmc 1.1 C by adding statistics over the range [1:iRun],[1:jRun]
21     C from input field array inpFld
22 jmc 1.2 C- note:
23 jmc 1.1 C a) this S/R should not see DIAGNOSTICS pkg commons blocks (in DIAGNOSTICS.h)
24     C b) for main grid variables, get area & weigting factors (to compute global mean)
25     C from the main common blocks.
26 jmc 1.2 C c) for other type of grids, call a specifics S/R which include its own
27 jmc 1.1 C grid common blocks
28    
29     C !USES:
30     IMPLICIT NONE
31    
32     #include "EEPARAMS.h"
33     #include "SIZE.h"
34     #include "DIAGNOSTICS_SIZE.h"
35     #include "PARAMS.h"
36     #include "GRID.h"
37 jmc 1.2 c #include "SURFACE.h"
38 jmc 1.1
39     C !INPUT/OUTPUT PARAMETERS:
40     C == Routine Arguments ==
41     C statFld :: cumulative statistics array (updated)
42     C inpFld :: input field array to process (compute stats & add to statFld)
43 jmc 1.3 C frcFld :: fraction used for weighted-average diagnostics
44     C scaleFact :: scaling factor
45 jmc 1.4 C power :: option to fill-in with the field square (power=2)
46 jmc 1.3 C useFract :: if True, use fraction-weight
47     C sizF :: size of frcFld array: 3rd dimension
48 jmc 1.1 C sizI1,sizI2 :: size of inpFld array: 1rst index range (min,max)
49     C sizJ1,sizJ2 :: size of inpFld array: 2nd index range (min,max)
50     C sizK :: size of inpFld array: 3rd dimension
51     C sizTx,sizTy :: size of inpFld array: tile dimensions
52     C iRun,jRun :: range of 1rst & 2nd index
53 jmc 1.3 C kIn :: level index of inpFld array to porcess
54     C biIn,bjIn :: tile indices of inpFld array to process
55 jmc 1.1 C k,bi,bj :: level and tile indices used for weighting (mask,area ...)
56     C region2fill :: indicates whether to compute statistics over this region
57     C ndId :: Diagnostics Id Number (in available diag. list)
58     C parsFld :: parser field with characteristics of the diagnostics
59     C myThid :: my Thread Id number
60     _RL statFld(0:nStats,0:nRegions)
61     INTEGER sizI1,sizI2,sizJ1,sizJ2
62 jmc 1.3 INTEGER sizF,sizK,sizTx,sizTy
63 jmc 1.1 _RL inpFld(sizI1:sizI2,sizJ1:sizJ2,sizK,sizTx,sizTy)
64 jmc 1.3 _RL frcFld(sizI1:sizI2,sizJ1:sizJ2,sizF,sizTx,sizTy)
65     _RL scaleFact
66 jmc 1.4 INTEGER power
67 jmc 1.3 LOGICAL useFract
68 jmc 1.1 INTEGER iRun, jRun, kIn, biIn, bjIn
69     INTEGER k, bi, bj, ndId
70     INTEGER region2fill(0:nRegions)
71     CHARACTER*16 parsFld
72     INTEGER myThid
73     CEOP
74    
75     C !LOCAL VARIABLES:
76     C i,j :: loop indices
77 jmc 1.3 INTEGER i, n, km, kFr
78 jmc 1.1 INTEGER im, ix, iv
79     PARAMETER ( iv = nStats - 2 , im = nStats - 1 , ix = nStats )
80     LOGICAL exclSpVal
81     LOGICAL useWeight
82     _RL statLoc(0:nStats)
83     _RL drLoc
84     _RL specialVal
85     _RL getcon
86     EXTERNAL getcon
87    
88     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
89    
90     useWeight = .FALSE.
91     exclSpVal = .FALSE.
92     specialVal = 0.
93     IF ( useFIZHI ) THEN
94     exclSpVal = .TRUE.
95 jmc 1.2 specialVal = getcon('UNDEF')
96 jmc 1.1 ENDIF
97 jmc 1.3 kFr = MIN(kIn,sizF)
98 jmc 1.2
99 jmc 1.1 DO n=0,nRegions
100     IF (region2fill(n).NE.0) THEN
101     C--- Compute statistics for this tile, level and region:
102 jmc 1.2
103 jmc 1.1 C- case of a special region (no specific regional mask)
104     IF ( n.EQ.0 ) THEN
105    
106     IF ( parsFld(10:10) .EQ. 'R' ) THEN
107    
108     drLoc = drF(k)
109     IF ( parsFld(9:9).EQ.'L') drLoc = drC(k)
110     IF ( parsFld(9:9).EQ.'U') drLoc = drC(MIN(k+1,Nr))
111     IF ( parsFld(9:9).EQ.'M') useWeight = .TRUE.
112    
113     IF ( parsFld(2:2).EQ.'U' ) THEN
114 jmc 1.2 CALL DIAGSTATS_CALC(
115 jmc 1.1 O statLoc,
116     I inpFld(sizI1,sizJ1,kIn,biIn,bjIn),
117 jmc 1.3 I frcFld(sizI1,sizJ1,kFr,biIn,bjIn),
118 jmc 1.4 I scaleFact, power, useFract,
119 jmc 1.2 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
120 jmc 1.1 I maskH(1-Olx,1-Oly,bi,bj), maskW(1-Olx,1-Oly,k,bi,bj),
121 jmc 1.2 I hFacW(1-Olx,1-Oly,k,bi,bj), rAw(1-Olx,1-Oly,bi,bj),
122 jmc 1.1 I drLoc, specialVal, exclSpVal, useWeight, myThid )
123     c I drLoc, k,bi,bj, parsFld, myThid )
124     ELSEIF ( parsFld(2:2).EQ.'V' ) THEN
125 jmc 1.2 CALL DIAGSTATS_CALC(
126 jmc 1.1 O statLoc,
127     I inpFld(sizI1,sizJ1,kIn,biIn,bjIn),
128 jmc 1.3 I frcFld(sizI1,sizJ1,kFr,biIn,bjIn),
129 jmc 1.4 I scaleFact, power, useFract,
130 jmc 1.2 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
131 jmc 1.1 I maskH(1-Olx,1-Oly,bi,bj), maskS(1-Olx,1-Oly,k,bi,bj),
132 jmc 1.2 I hFacS(1-Olx,1-Oly,k,bi,bj), rAs(1-Olx,1-Oly,bi,bj),
133 jmc 1.1 I drLoc, specialVal, exclSpVal, useWeight, myThid )
134     ELSE
135 jmc 1.2 CALL DIAGSTATS_CALC(
136 jmc 1.1 O statLoc,
137     I inpFld(sizI1,sizJ1,kIn,biIn,bjIn),
138 jmc 1.3 I frcFld(sizI1,sizJ1,kFr,biIn,bjIn),
139 jmc 1.4 I scaleFact, power, useFract,
140 jmc 1.2 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
141 jmc 1.1 I maskH(1-Olx,1-Oly,bi,bj), maskC(1-Olx,1-Oly,k,bi,bj),
142     I hFacC(1-Olx,1-Oly,k,bi,bj), rA(1-Olx,1-Oly,bi,bj),
143     I drLoc, specialVal, exclSpVal, useWeight, myThid )
144     ENDIF
145    
146 jmc 1.2 ELSEIF ( useFIZHI .AND.
147     & (parsFld(10:10).EQ.'L' .OR. parsFld(10:10).EQ.'M')
148     & ) THEN
149     CALL DIAGSTATS_LM_CALC(
150 jmc 1.1 O statLoc,
151     I inpFld(sizI1,sizJ1,kIn,biIn,bjIn),
152 jmc 1.3 I frcFld(sizI1,sizJ1,kFr,biIn,bjIn),
153 jmc 1.4 I scaleFact, power, useFract,
154 jmc 1.2 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
155 jmc 1.1 I maskH(1-Olx,1-Oly,bi,bj), maskH(1-Olx,1-Oly,bi,bj),
156 jmc 1.2 I rA(1-Olx,1-Oly,bi,bj),
157     I specialVal, exclSpVal,
158     I k,bi,bj, parsFld, myThid )
159     ELSEIF ( useLand .AND.
160     & (parsFld(10:10).EQ.'G' .OR. parsFld(10:10).EQ.'g')
161     & ) THEN
162     CALL DIAGSTATS_G_CALC(
163     O statLoc,
164     I inpFld(sizI1,sizJ1,kIn,biIn,bjIn),
165 jmc 1.3 I frcFld(sizI1,sizJ1,kFr,biIn,bjIn),
166 jmc 1.4 I scaleFact, power, useFract,
167 jmc 1.2 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
168     I maskH(1-Olx,1-Oly,bi,bj),
169     I rA(1-Olx,1-Oly,bi,bj),
170     I specialVal, exclSpVal,
171     I k,bi,bj, parsFld, myThid )
172 jmc 1.1 c ELSEIF ( parsFld(10:10) .EQ. 'I' ) THEN
173     c ELSEIF ( parsFld(10:10) .EQ. '1' ) THEN
174     ELSE
175    
176     km = 1
177     IF ( usingPCoords ) km = Nr
178     drLoc = 1. _d 0
179     IF ( parsFld(2:2).EQ.'U' ) THEN
180 jmc 1.2 CALL DIAGSTATS_CALC(
181 jmc 1.1 O statLoc,
182     I inpFld(sizI1,sizJ1,kIn,biIn,bjIn),
183 jmc 1.3 I frcFld(sizI1,sizJ1,kFr,biIn,bjIn),
184 jmc 1.4 I scaleFact, power, useFract,
185 jmc 1.2 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
186 jmc 1.1 I maskH(1-Olx,1-Oly,bi,bj), maskW(1-Olx,1-Oly,km,bi,bj),
187 jmc 1.2 I maskW(1-Olx,1-Oly,km,bi,bj),rAw(1-Olx,1-Oly,bi,bj),
188 jmc 1.1 I drLoc, specialVal, exclSpVal, useWeight, myThid )
189     ELSEIF ( parsFld(2:2).EQ.'V' ) THEN
190 jmc 1.2 CALL DIAGSTATS_CALC(
191 jmc 1.1 O statLoc,
192     I inpFld(sizI1,sizJ1,kIn,biIn,bjIn),
193 jmc 1.3 I frcFld(sizI1,sizJ1,kFr,biIn,bjIn),
194 jmc 1.4 I scaleFact, power, useFract,
195 jmc 1.2 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
196 jmc 1.1 I maskH(1-Olx,1-Oly,bi,bj), maskS(1-Olx,1-Oly,km,bi,bj),
197 jmc 1.2 I maskS(1-Olx,1-Oly,km,bi,bj),rAs(1-Olx,1-Oly,bi,bj),
198 jmc 1.1 I drLoc, specialVal, exclSpVal, useWeight, myThid )
199     ELSE
200 jmc 1.2 CALL DIAGSTATS_CALC(
201 jmc 1.1 O statLoc,
202     I inpFld(sizI1,sizJ1,kIn,biIn,bjIn),
203 jmc 1.3 I frcFld(sizI1,sizJ1,kFr,biIn,bjIn),
204 jmc 1.4 I scaleFact, power, useFract,
205 jmc 1.2 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
206 jmc 1.1 I maskH(1-Olx,1-Oly,bi,bj), maskH(1-Olx,1-Oly,bi,bj),
207     I maskH(1-Olx,1-Oly,bi,bj), rA(1-Olx,1-Oly,bi,bj),
208     I drLoc, specialVal, exclSpVal, useWeight, myThid )
209     ENDIF
210    
211     ENDIF
212    
213     C Update cumulative statistics array
214     IF ( statLoc(0).GT.0. ) THEN
215     IF ( statFld(0,n).LE.0. ) THEN
216     statFld(im,n) = statLoc(im)
217     statFld(ix,n) = statLoc(ix)
218     ELSE
219     statFld(im,n) = MIN( statFld(im,n), statLoc(im) )
220     statFld(ix,n) = MAX( statFld(ix,n), statLoc(ix) )
221     ENDIF
222     DO i=0,iv
223     statFld(i,n) = statFld(i,n) + statLoc(i)
224     ENDDO
225     ENDIF
226    
227     ENDIF
228    
229     C--- processing region "n" ends here.
230     ENDIF
231     ENDDO
232    
233 jmc 1.2 RETURN
234     END
235    
236     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
237    
238     CBOP
239     C !ROUTINE: DIAGSTATS_LM_CALC
240     C !INTERFACE:
241     SUBROUTINE DIAGSTATS_LM_CALC(
242     O statArr,
243 jmc 1.4 I inpArr, frcArr, scaleFact, power, useFract,
244 jmc 1.2 I nStats,sizI1,sizI2,sizJ1,sizJ2, iRun,jRun,
245     I regMask, arrMask, arrArea,
246     I specialVal, exclSpVal,
247     I k,bi,bj, parsFld, myThid )
248    
249     C !DESCRIPTION:
250     C Compute statistics for this tile, level, region
251     C using FIZHI level thickness
252    
253     C !USES:
254     IMPLICIT NONE
255    
256     #include "EEPARAMS.h"
257     #include "SIZE.h"
258     #ifdef ALLOW_FIZHI
259     #include "fizhi_SIZE.h"
260     #include "gridalt_mapping.h"
261     #endif
262    
263     C !INPUT/OUTPUT PARAMETERS:
264     C == Routine Arguments ==
265     C statArr :: output statistics array
266     C inpArr :: input field array to process (compute stats & add to statFld)
267 jmc 1.3 C frcArr :: fraction used for weighted-average diagnostics
268 jmc 1.4 C scaleFact :: scaling factor
269     C power :: option to fill-in with the field square (power=2)
270 jmc 1.3 C useFract :: if True, use fraction-weight
271 jmc 1.2 C nStats :: size of output statArr
272     C sizI1,sizI2 :: size of inpArr array: 1rst index range (min,max)
273     C sizJ1,sizJ2 :: size of inpArr array: 2nd index range (min,max)
274     C iRun,jRun :: range of 1rst & 2nd index to process
275     C regMask :: regional mask
276     C arrMask :: mask for this input array
277     C arrArea :: Area weighting factor
278     C specialVal :: special value in input array (to exclude if exclSpVal=T)
279     C exclSpVal :: if T, exclude "specialVal" in input array
280     C k,bi,bj :: level and tile indices used for weighting (mask,area ...)
281     C parsFld :: parser field with characteristics of the diagnostics
282     C myThid :: my Thread Id number
283     INTEGER nStats,sizI1,sizI2,sizJ1,sizJ2
284     INTEGER iRun, jRun
285     _RL statArr(0:nStats)
286     _RL inpArr (sizI1:sizI2,sizJ1:sizJ2)
287 jmc 1.3 _RL frcArr (sizI1:sizI2,sizJ1:sizJ2)
288     _RL scaleFact
289 jmc 1.4 INTEGER power
290 jmc 1.3 LOGICAL useFract
291 jmc 1.2 _RS regMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
292     _RS arrMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
293     _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
294     _RL specialVal
295     LOGICAL exclSpVal
296     INTEGER k, bi, bj
297     CHARACTER*16 parsFld
298     INTEGER myThid
299     CEOP
300    
301     #ifdef ALLOW_FIZHI
302     C !LOCAL VARIABLES:
303     LOGICAL useWeight
304     INTEGER kl
305     _RL drLoc
306    
307     c IF ( useFIZHI ) THEN
308    
309     IF ( parsFld(10:10).EQ.'L' ) THEN
310     kl = 1 + Nrphys - k
311     useWeight = .TRUE.
312     ELSE
313     kl = 1
314     useWeight = .FALSE.
315     ENDIF
316     drLoc = 1. _d 0
317    
318     C- jmc: here we have a Problem if RL & RS are not the same:
319     C since dpphys is RL but argument is RS. leave it like this for now
320     C and will change it once the Regions are fully implemented.
321    
322     CALL DIAGSTATS_CALC(
323     O statArr,
324 jmc 1.4 I inpArr, frcArr, scaleFact, power, useFract,
325 jmc 1.2 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
326     I regMask, arrMask,
327     I dpphys(1-Olx,1-Oly,kl,bi,bj), arrArea,
328     I drLoc, specialVal, exclSpVal, useWeight, myThid )
329    
330     c ENDIF
331     #endif /* ALLOW_FIZHI */
332    
333     RETURN
334     END
335    
336     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
337    
338     CBOP
339     C !ROUTINE: DIAGSTATS_G_CALC
340     C !INTERFACE:
341     SUBROUTINE DIAGSTATS_G_CALC(
342     O statArr,
343 jmc 1.4 I inpArr, frcArr, scaleFact, power, useFract,
344 jmc 1.2 I nStats,sizI1,sizI2,sizJ1,sizJ2, iRun,jRun,
345     I regMask, arrArea,
346     I specialVal, exclSpVal,
347     I k,bi,bj, parsFld, myThid )
348    
349     C !DESCRIPTION:
350     C Compute statistics for this tile, level, region
351     C using "ground" (land) type fraction
352    
353     C !USES:
354     IMPLICIT NONE
355    
356     #include "EEPARAMS.h"
357     #ifdef ALLOW_LAND
358     # include "LAND_SIZE.h"
359     # include "LAND_PARAMS.h"
360     # ifdef ALLOW_AIM
361     # include "AIM_FFIELDS.h"
362     # endif
363     #else
364     # include "SIZE.h"
365     #endif
366    
367     C !INPUT/OUTPUT PARAMETERS:
368     C == Routine Arguments ==
369     C statArr :: output statistics array
370     C inpArr :: input field array to process (compute stats & add to statFld)
371 jmc 1.3 C frcArr :: fraction used for weighted-average diagnostics
372 jmc 1.4 C scaleFact :: scaling factor
373     C power :: option to fill-in with the field square (power=2)
374 jmc 1.3 C useFract :: if True, use fraction-weight
375 jmc 1.2 C nStats :: size of output statArr
376     C sizI1,sizI2 :: size of inpArr array: 1rst index range (min,max)
377     C sizJ1,sizJ2 :: size of inpArr array: 2nd index range (min,max)
378     C iRun,jRun :: range of 1rst & 2nd index to process
379     C regMask :: regional mask
380     C arrArea :: Area weighting factor
381     C specialVal :: special value in input array (to exclude if exclSpVal=T)
382     C exclSpVal :: if T, exclude "specialVal" in input array
383     C k,bi,bj :: level and tile indices used for weighting (mask,area ...)
384     C parsFld :: parser field with characteristics of the diagnostics
385     C myThid :: my Thread Id number
386     INTEGER nStats,sizI1,sizI2,sizJ1,sizJ2
387     INTEGER iRun, jRun
388     _RL statArr(0:nStats)
389     _RL inpArr (sizI1:sizI2,sizJ1:sizJ2)
390 jmc 1.3 _RL frcArr (sizI1:sizI2,sizJ1:sizJ2)
391     _RL scaleFact
392 jmc 1.4 INTEGER power
393 jmc 1.3 LOGICAL useFract
394 jmc 1.2 _RS regMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
395     _RS arrMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
396     _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
397     _RL specialVal
398     LOGICAL exclSpVal
399     INTEGER k, bi, bj
400     CHARACTER*16 parsFld
401     INTEGER myThid
402     CEOP
403    
404     #ifdef ALLOW_LAND
405     C !LOCAL VARIABLES:
406     LOGICAL useWeight
407     INTEGER kl
408     _RL drLoc
409    
410     c IF ( useLand ) THEN
411    
412     IF ( parsFld(10:10).EQ.'G' ) THEN
413     kl = MIN(k,land_nLev)
414     drLoc = land_dzF(kl)
415     ELSE
416     drLoc = 1. _d 0
417     ENDIF
418     useWeight = .TRUE.
419    
420     CALL DIAGSTATS_CALC(
421     O statArr,
422 jmc 1.4 I inpArr, frcArr, scaleFact, power, useFract,
423 jmc 1.2 I nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
424     I regMask, aim_landFr(1-Olx,1-Oly,bi,bj),
425     I aim_landFr(1-Olx,1-Oly,bi,bj), arrArea,
426     I drLoc, specialVal, exclSpVal, useWeight, myThid )
427    
428     c ENDIF
429     #endif /* ALLOW_LAND */
430    
431     RETURN
432 jmc 1.1 END
433    
434     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
435    
436     CBOP
437     C !ROUTINE: DIAGSTATS_CALC
438     C !INTERFACE:
439 jmc 1.2 SUBROUTINE DIAGSTATS_CALC(
440     O statArr,
441 jmc 1.4 I inpArr, frcArr, scaleFact, power, useFract,
442 jmc 1.2 I nStats,sizI1,sizI2,sizJ1,sizJ2, iRun,jRun,
443 jmc 1.1 I regMask, arrMask, arrhFac, arrArea,
444     I arrDr, specialVal, exclSpVal, useWeight,
445     I myThid )
446    
447     C !DESCRIPTION:
448     C Compute statistics for this tile, level, region
449    
450     C !USES:
451     IMPLICIT NONE
452    
453     #include "EEPARAMS.h"
454     #include "SIZE.h"
455    
456     C !INPUT/OUTPUT PARAMETERS:
457     C == Routine Arguments ==
458 jmc 1.2 C statArr :: output statistics array
459 jmc 1.1 C inpArr :: input field array to process (compute stats & add to statFld)
460 jmc 1.3 C frcArr :: fraction used for weighted-average diagnostics
461 jmc 1.4 C scaleFact :: scaling factor
462     C power :: option to fill-in with the field square (power=2)
463 jmc 1.3 C useFract :: if True, use fraction-weight
464 jmc 1.2 C nStats :: size of output array: statArr
465 jmc 1.1 C sizI1,sizI2 :: size of inpArr array: 1rst index range (min,max)
466     C sizJ1,sizJ2 :: size of inpArr array: 2nd index range (min,max)
467     C iRun,jRun :: range of 1rst & 2nd index to process
468     C regMask :: regional mask
469     C arrMask :: mask for this input array
470     C arrhFac :: weight factor (horizontally varying)
471     C arrArea :: Area weighting factor
472     C arrDr :: uniform weighting factor
473     C specialVal :: special value in input array (to exclude if exclSpVal=T)
474     C exclSpVal :: if T, exclude "specialVal" in input array
475     C useWeight :: use weight factor "arrhFac"
476     Cc k,bi,bj :: level and tile indices used for weighting (mask,area ...)
477     Cc parsFld :: parser field with characteristics of the diagnostics
478     C myThid :: my Thread Id number
479 jmc 1.2 INTEGER nStats,sizI1,sizI2,sizJ1,sizJ2
480     INTEGER iRun, jRun
481 jmc 1.1 _RL statArr(0:nStats)
482     _RL inpArr (sizI1:sizI2,sizJ1:sizJ2)
483 jmc 1.3 _RL frcArr (sizI1:sizI2,sizJ1:sizJ2)
484     _RL scaleFact
485 jmc 1.4 INTEGER power
486 jmc 1.3 LOGICAL useFract
487 jmc 1.1 _RS regMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
488     _RS arrMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
489     _RS arrhFac(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
490     _RS arrArea(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
491     _RL arrDr
492     _RL specialVal
493     LOGICAL exclSpVal
494     LOGICAL useWeight
495     INTEGER myThid
496     CEOP
497    
498     C !LOCAL VARIABLES:
499     C i,j :: loop indices
500     INTEGER i, j, n
501 jmc 1.2 INTEGER im, ix
502 jmc 1.1 _RL tmpVol
503 jmc 1.3 _RL tmpFld
504 jmc 1.4 _RL tmpFac
505 jmc 1.1
506 jmc 1.2 im = nStats - 1
507     ix = nStats
508 jmc 1.1 DO n=0,nStats
509     statArr(n) = 0.
510     ENDDO
511 jmc 1.4 tmpFac = scaleFact
512     IF ( power.EQ.2) tmpFac = scaleFact*scaleFact
513 jmc 1.1
514 jmc 1.3 IF ( useFract .AND. exclSpVal ) THEN
515 jmc 1.1
516     DO j = 1,jRun
517     DO i = 1,iRun
518 jmc 1.3 IF ( arrMask(i,j).NE.0. .AND. frcArr(i,j).NE.0.
519     & .AND. inpArr(i,j).NE.specialVal ) THEN
520 jmc 1.4 IF ( power.EQ.2) THEN
521     tmpFld = tmpFac*inpArr(i,j)*inpArr(i,j)
522     ELSE
523     tmpFld = tmpFac*inpArr(i,j)
524     ENDIF
525 jmc 1.1 IF ( statArr(0).EQ.0. ) THEN
526 jmc 1.3 statArr(im) = tmpFld
527     statArr(ix) = tmpFld
528 jmc 1.1 ELSE
529 jmc 1.3 statArr(im) = MIN(tmpFld,statArr(im))
530     statArr(ix) = MAX(tmpFld,statArr(ix))
531     ENDIF
532     IF ( useWeight ) THEN
533     tmpVol = arrDr*arrhFac(i,j)*arrArea(i,j)*frcArr(i,j)
534     ELSE
535     tmpVol = arrDr*arrArea(i,j)*frcArr(i,j)
536     ENDIF
537     statArr(0) = statArr(0) + tmpVol
538     statArr(1) = statArr(1) + tmpVol*tmpFld
539     statArr(2) = statArr(2) + tmpVol*tmpFld*tmpFld
540     ENDIF
541     ENDDO
542     ENDDO
543    
544     ELSEIF ( useFract ) THEN
545    
546     DO j = 1,jRun
547     DO i = 1,iRun
548     IF ( arrMask(i,j).NE.0. .AND. frcArr(i,j).NE.0. ) THEN
549 jmc 1.4 IF ( power.EQ.2) THEN
550     tmpFld = tmpFac*inpArr(i,j)*inpArr(i,j)
551     ELSE
552     tmpFld = tmpFac*inpArr(i,j)
553     ENDIF
554 jmc 1.3 IF ( statArr(0).EQ.0. ) THEN
555     statArr(im) = tmpFld
556     statArr(ix) = tmpFld
557     ELSE
558     statArr(im) = MIN(tmpFld,statArr(im))
559     statArr(ix) = MAX(tmpFld,statArr(ix))
560     ENDIF
561     IF ( useWeight ) THEN
562     tmpVol = arrDr*arrhFac(i,j)*arrArea(i,j)*frcArr(i,j)
563     ELSE
564     tmpVol = arrDr*arrArea(i,j)*frcArr(i,j)
565     ENDIF
566     statArr(0) = statArr(0) + tmpVol
567     statArr(1) = statArr(1) + tmpVol*tmpFld
568     statArr(2) = statArr(2) + tmpVol*tmpFld*tmpFld
569     ENDIF
570     ENDDO
571     ENDDO
572    
573     ELSEIF ( exclSpVal ) THEN
574    
575     DO j = 1,jRun
576     DO i = 1,iRun
577     IF ( arrMask(i,j).NE.0.
578     & .AND. inpArr(i,j).NE.specialVal ) THEN
579 jmc 1.4 IF ( power.EQ.2) THEN
580     tmpFld = tmpFac*inpArr(i,j)*inpArr(i,j)
581     ELSE
582     tmpFld = tmpFac*inpArr(i,j)
583     ENDIF
584 jmc 1.3 IF ( statArr(0).EQ.0. ) THEN
585     statArr(im) = tmpFld
586     statArr(ix) = tmpFld
587     ELSE
588     statArr(im) = MIN(tmpFld,statArr(im))
589     statArr(ix) = MAX(tmpFld,statArr(ix))
590 jmc 1.1 ENDIF
591     IF ( useWeight ) THEN
592     tmpVol = arrDr*arrhFac(i,j)*arrArea(i,j)
593     ELSE
594     tmpVol = arrDr*arrArea(i,j)
595     ENDIF
596     statArr(0) = statArr(0) + tmpVol
597 jmc 1.3 statArr(1) = statArr(1) + tmpVol*tmpFld
598     statArr(2) = statArr(2) + tmpVol*tmpFld*tmpFld
599 jmc 1.1 ENDIF
600     ENDDO
601     ENDDO
602    
603     ELSE
604    
605     DO j = 1,jRun
606     DO i = 1,iRun
607     c IF ( regMask(i,j).NE.0. .AND. arrMask(i,j).NE.0. ) THEN
608     IF ( arrMask(i,j).NE.0. ) THEN
609 jmc 1.4 IF ( power.EQ.2) THEN
610     tmpFld = tmpFac*inpArr(i,j)*inpArr(i,j)
611     ELSE
612     tmpFld = tmpFac*inpArr(i,j)
613     ENDIF
614 jmc 1.1 IF ( statArr(0).EQ.0. ) THEN
615 jmc 1.3 statArr(im) = tmpFld
616     statArr(ix) = tmpFld
617 jmc 1.1 ELSE
618 jmc 1.3 statArr(im) = MIN(tmpFld,statArr(im))
619     statArr(ix) = MAX(tmpFld,statArr(ix))
620 jmc 1.1 ENDIF
621     IF ( useWeight ) THEN
622     tmpVol = arrDr*arrhFac(i,j)*arrArea(i,j)
623     ELSE
624     tmpVol = arrDr*arrArea(i,j)
625     ENDIF
626     statArr(0) = statArr(0) + tmpVol
627 jmc 1.3 statArr(1) = statArr(1) + tmpVol*tmpFld
628     statArr(2) = statArr(2) + tmpVol*tmpFld*tmpFld
629 jmc 1.1 ENDIF
630     ENDDO
631     ENDDO
632    
633     ENDIF
634    
635 jmc 1.2 RETURN
636 jmc 1.1 END

  ViewVC Help
Powered by ViewVC 1.1.22