/[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.2 - (hide annotations) (download)
Mon May 23 02:18:40 2005 UTC (18 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57k_post, checkpoint57i_post, checkpoint57j_post
Changes since 1.1: +237 -55 lines
rewrite small pieces:
- implement land fraction weight.
- fix for fizhi variables on Physics grid.
- do not mix (or at least, mix less) different common blocks (from different pkgs)

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

  ViewVC Help
Powered by ViewVC 1.1.22