/[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.3 - (hide annotations) (download)
Sun Jul 10 00:57:18 2005 UTC (18 years, 10 months ago) by jmc
Branch: MAIN
Changes since 1.2: +122 -26 lines
modif to fill a diagnostics using a scaling factor and a fraction-weight
      field ; does not affect diagnostics_fill.F arguments.

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

  ViewVC Help
Powered by ViewVC 1.1.22