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

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

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

revision 1.1 by jmc, Fri May 20 07:28:52 2005 UTC revision 1.2 by jmc, Mon May 23 02:18:40 2005 UTC
# Line 15  C     !INTERFACE: Line 15  C     !INTERFACE:
15       I                  myThid)       I                  myThid)
16    
17  C     !DESCRIPTION:  C     !DESCRIPTION:
18  C     Update array statFld  C     Update array statFld
19  C     by adding statistics over the range [1:iRun],[1:jRun]  C     by adding statistics over the range [1:iRun],[1:jRun]
20  C     from input field array inpFld  C     from input field array inpFld
21  C- note:  C- note:
22  C   a) this S/R should not see DIAGNOSTICS pkg commons blocks (in DIAGNOSTICS.h)  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)  C   b) for main grid variables, get area & weigting factors (to compute global mean)
24  C      from the main common blocks.  C      from the main common blocks.
25  C   c) for other type of grids, call a specifics S/R which include its own  C   c) for other type of grids, call a specifics S/R which include its own
26  C      grid common blocks  C      grid common blocks
27    
28  C     !USES:  C     !USES:
# Line 33  C     !USES: Line 33  C     !USES:
33  #include "DIAGNOSTICS_SIZE.h"  #include "DIAGNOSTICS_SIZE.h"
34  #include "PARAMS.h"  #include "PARAMS.h"
35  #include "GRID.h"  #include "GRID.h"
36  #include "SURFACE.h"  c #include "SURFACE.h"
 #ifdef ALLOW_FIZHI  
 #include "fizhi_SIZE.h"  
 #include "gridalt_mapping.h"  
 #endif  
37    
38  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
39  C     == Routine Arguments ==  C     == Routine Arguments ==
# Line 86  C---+----1----+----2----+----3----+----4 Line 82  C---+----1----+----2----+----3----+----4
82        specialVal = 0.        specialVal = 0.
83        IF ( useFIZHI ) THEN        IF ( useFIZHI ) THEN
84          exclSpVal = .TRUE.          exclSpVal = .TRUE.
85          specialVal = getcon('UNDEF')          specialVal = getcon('UNDEF')
86        ENDIF        ENDIF
87            
88        DO n=0,nRegions        DO n=0,nRegions
89         IF (region2fill(n).NE.0) THEN         IF (region2fill(n).NE.0) THEN
90  C---   Compute statistics for this tile, level and region:  C---   Compute statistics for this tile, level and region:
91          
92  C-     case of a special region (no specific regional mask)  C-     case of a special region (no specific regional mask)
93          IF ( n.EQ.0 ) THEN          IF ( n.EQ.0 ) THEN
94    
# Line 104  C-     case of a special region (no spec Line 100  C-     case of a special region (no spec
100            IF ( parsFld(9:9).EQ.'M') useWeight = .TRUE.            IF ( parsFld(9:9).EQ.'M') useWeight = .TRUE.
101    
102            IF     ( parsFld(2:2).EQ.'U' ) THEN            IF     ( parsFld(2:2).EQ.'U' ) THEN
103             CALL  DIAGSTATS_R_CALC(             CALL  DIAGSTATS_CALC(
104       O            statLoc,       O            statLoc,
105       I            inpFld(sizI1,sizJ1,kIn,biIn,bjIn),       I            inpFld(sizI1,sizJ1,kIn,biIn,bjIn),
106       I            sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,       I            nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
107       I            maskH(1-Olx,1-Oly,bi,bj), maskW(1-Olx,1-Oly,k,bi,bj),       I            maskH(1-Olx,1-Oly,bi,bj), maskW(1-Olx,1-Oly,k,bi,bj),
108       I            hFacW(1-Olx,1-Oly,k,bi,bj), rAw(1-Olx,1-Oly,bi,bj),       I            hFacW(1-Olx,1-Oly,k,bi,bj), rAw(1-Olx,1-Oly,bi,bj),
109       I            drLoc, specialVal, exclSpVal, useWeight, myThid )       I            drLoc, specialVal, exclSpVal, useWeight, myThid )
110  c    I            drLoc, k,bi,bj, parsFld, myThid )  c    I            drLoc, k,bi,bj, parsFld, myThid )
111            ELSEIF ( parsFld(2:2).EQ.'V' ) THEN            ELSEIF ( parsFld(2:2).EQ.'V' ) THEN
112             CALL  DIAGSTATS_R_CALC(             CALL  DIAGSTATS_CALC(
113       O            statLoc,       O            statLoc,
114       I            inpFld(sizI1,sizJ1,kIn,biIn,bjIn),       I            inpFld(sizI1,sizJ1,kIn,biIn,bjIn),
115       I            sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,       I            nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
116       I            maskH(1-Olx,1-Oly,bi,bj), maskS(1-Olx,1-Oly,k,bi,bj),       I            maskH(1-Olx,1-Oly,bi,bj), maskS(1-Olx,1-Oly,k,bi,bj),
117       I            hFacS(1-Olx,1-Oly,k,bi,bj), rAs(1-Olx,1-Oly,bi,bj),       I            hFacS(1-Olx,1-Oly,k,bi,bj), rAs(1-Olx,1-Oly,bi,bj),
118       I            drLoc, specialVal, exclSpVal, useWeight, myThid )       I            drLoc, specialVal, exclSpVal, useWeight, myThid )
119            ELSE            ELSE
120             CALL  DIAGSTATS_R_CALC(             CALL  DIAGSTATS_CALC(
121       O            statLoc,       O            statLoc,
122       I            inpFld(sizI1,sizJ1,kIn,biIn,bjIn),       I            inpFld(sizI1,sizJ1,kIn,biIn,bjIn),
123       I            sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,       I            nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
124       I            maskH(1-Olx,1-Oly,bi,bj), maskC(1-Olx,1-Oly,k,bi,bj),       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),       I            hFacC(1-Olx,1-Oly,k,bi,bj), rA(1-Olx,1-Oly,bi,bj),
126       I            drLoc, specialVal, exclSpVal, useWeight, myThid )       I            drLoc, specialVal, exclSpVal, useWeight, myThid )
127            ENDIF            ENDIF
128    
129  #ifdef ALLOW_FIZHI           ELSEIF ( useFIZHI .AND.
130  c        ELSEIF ( parsFld(10:10) .EQ. 'L' ) THEN       &           (parsFld(10:10).EQ.'L' .OR. parsFld(10:10).EQ.'M')
131           ELSEIF ( parsFld(10:10) .EQ. 'M' ) THEN       &          ) THEN
132             drLoc = 1. _d 0             CALL  DIAGSTATS_LM_CALC(
            km = 1 + Nrphys - k  
            CALL  DIAGSTATS_R_CALC(  
133       O            statLoc,       O            statLoc,
134       I            inpFld(sizI1,sizJ1,kIn,biIn,bjIn),       I            inpFld(sizI1,sizJ1,kIn,biIn,bjIn),
135       I            sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,       I            nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
136       I            maskH(1-Olx,1-Oly,bi,bj), maskH(1-Olx,1-Oly,bi,bj),       I            maskH(1-Olx,1-Oly,bi,bj), maskH(1-Olx,1-Oly,bi,bj),
137       I            dpphys(1-Olx,1-Oly,km,bi,bj), rA(1-Olx,1-Oly,bi,bj),       I            rA(1-Olx,1-Oly,bi,bj),
138       I            drLoc, specialVal, exclSpVal, useWeight, myThid )       I            specialVal, exclSpVal,
139  #endif       I            k,bi,bj, parsFld, myThid )
140  #ifdef ALLOW_LAND           ELSEIF ( useLand .AND.
141  c        ELSEIF ( parsFld(10:10) .EQ. 'G' ) THEN       &           (parsFld(10:10).EQ.'G' .OR. parsFld(10:10).EQ.'g')
142  #endif       &          ) 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  c        ELSEIF ( parsFld(10:10) .EQ. 'I' ) THEN  c        ELSEIF ( parsFld(10:10) .EQ. 'I' ) THEN
152  c        ELSEIF ( parsFld(10:10) .EQ. '1' ) THEN  c        ELSEIF ( parsFld(10:10) .EQ. '1' ) THEN
153           ELSE           ELSE
# Line 154  c        ELSEIF ( parsFld(10:10) .EQ. '1 Line 156  c        ELSEIF ( parsFld(10:10) .EQ. '1
156            IF ( usingPCoords ) km = Nr            IF ( usingPCoords ) km = Nr
157            drLoc = 1. _d 0            drLoc = 1. _d 0
158            IF     ( parsFld(2:2).EQ.'U' ) THEN            IF     ( parsFld(2:2).EQ.'U' ) THEN
159             CALL  DIAGSTATS_R_CALC(             CALL  DIAGSTATS_CALC(
160       O            statLoc,       O            statLoc,
161       I            inpFld(sizI1,sizJ1,kIn,biIn,bjIn),       I            inpFld(sizI1,sizJ1,kIn,biIn,bjIn),
162       I            sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,       I            nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
163       I            maskH(1-Olx,1-Oly,bi,bj), maskW(1-Olx,1-Oly,km,bi,bj),       I            maskH(1-Olx,1-Oly,bi,bj), maskW(1-Olx,1-Oly,km,bi,bj),
164       I            maskW(1-Olx,1-Oly,km,bi,bj),rAw(1-Olx,1-Oly,bi,bj),       I            maskW(1-Olx,1-Oly,km,bi,bj),rAw(1-Olx,1-Oly,bi,bj),
165       I            drLoc, specialVal, exclSpVal, useWeight, myThid )       I            drLoc, specialVal, exclSpVal, useWeight, myThid )
166            ELSEIF ( parsFld(2:2).EQ.'V' ) THEN            ELSEIF ( parsFld(2:2).EQ.'V' ) THEN
167             CALL  DIAGSTATS_R_CALC(             CALL  DIAGSTATS_CALC(
168       O            statLoc,       O            statLoc,
169       I            inpFld(sizI1,sizJ1,kIn,biIn,bjIn),       I            inpFld(sizI1,sizJ1,kIn,biIn,bjIn),
170       I            sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,       I            nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
171       I            maskH(1-Olx,1-Oly,bi,bj), maskS(1-Olx,1-Oly,km,bi,bj),       I            maskH(1-Olx,1-Oly,bi,bj), maskS(1-Olx,1-Oly,km,bi,bj),
172       I            maskS(1-Olx,1-Oly,km,bi,bj),rAs(1-Olx,1-Oly,bi,bj),       I            maskS(1-Olx,1-Oly,km,bi,bj),rAs(1-Olx,1-Oly,bi,bj),
173       I            drLoc, specialVal, exclSpVal, useWeight, myThid )       I            drLoc, specialVal, exclSpVal, useWeight, myThid )
174            ELSE            ELSE
175             CALL  DIAGSTATS_R_CALC(             CALL  DIAGSTATS_CALC(
176       O            statLoc,       O            statLoc,
177       I            inpFld(sizI1,sizJ1,kIn,biIn,bjIn),       I            inpFld(sizI1,sizJ1,kIn,biIn,bjIn),
178       I            sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,       I            nStats,sizI1,sizI2,sizJ1,sizJ2,iRun,jRun,
179       I            maskH(1-Olx,1-Oly,bi,bj), maskH(1-Olx,1-Oly,bi,bj),       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),       I            maskH(1-Olx,1-Oly,bi,bj), rA(1-Olx,1-Oly,bi,bj),
181       I            drLoc, specialVal, exclSpVal, useWeight, myThid )       I            drLoc, specialVal, exclSpVal, useWeight, myThid )
# Line 201  C---   processing region "n" ends here. Line 203  C---   processing region "n" ends here.
203         ENDIF         ENDIF
204        ENDDO        ENDDO
205    
206        RETURN        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        END        END
390    
391  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
# Line 209  C---+----1----+----2----+----3----+----4 Line 393  C---+----1----+----2----+----3----+----4
393  CBOP  CBOP
394  C     !ROUTINE: DIAGSTATS_CALC  C     !ROUTINE: DIAGSTATS_CALC
395  C     !INTERFACE:  C     !INTERFACE:
396        SUBROUTINE DIAGSTATS_R_CALC(        SUBROUTINE DIAGSTATS_CALC(
397       U                  statArr,       O                  statArr,
398       I                  inpArr,       I                  inpArr,
399       I                  sizI1,sizI2,sizJ1,sizJ2, iRun,jRun,       I                  nStats,sizI1,sizI2,sizJ1,sizJ2, iRun,jRun,
400       I                  regMask, arrMask, arrhFac, arrArea,       I                  regMask, arrMask, arrhFac, arrArea,
401       I                  arrDr, specialVal, exclSpVal, useWeight,       I                  arrDr, specialVal, exclSpVal, useWeight,
402       I                  myThid )       I                  myThid )
# Line 226  C     !USES: Line 410  C     !USES:
410    
411  #include "EEPARAMS.h"  #include "EEPARAMS.h"
412  #include "SIZE.h"  #include "SIZE.h"
 #include "DIAGNOSTICS_SIZE.h"  
 c #include "PARAMS.h"  
 c #include "GRID.h"  
 c #include "SURFACE.h"  
413    
414  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
415  C     == Routine Arguments ==  C     == Routine Arguments ==
416  C     statArr     :: cumulative statistics array (updated)  C     statArr     :: output statistics array
417  C     inpArr      :: input field array to process (compute stats & add to statFld)  C     inpArr      :: input field array to process (compute stats & add to statFld)
418    C     nStats      :: size of output array: statArr
419  C     sizI1,sizI2 :: size of inpArr array: 1rst index range (min,max)  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)  C     sizJ1,sizJ2 :: size of inpArr array: 2nd  index range (min,max)
421  C     iRun,jRun   :: range of 1rst & 2nd index to process  C     iRun,jRun   :: range of 1rst & 2nd index to process
# Line 249  C     useWeight   :: use weight factor " Line 430  C     useWeight   :: use weight factor "
430  Cc    k,bi,bj     :: level and tile indices used for weighting (mask,area ...)  Cc    k,bi,bj     :: level and tile indices used for weighting (mask,area ...)
431  Cc    parsFld     :: parser field with characteristics of the diagnostics  Cc    parsFld     :: parser field with characteristics of the diagnostics
432  C     myThid      :: my Thread Id number  C     myThid      :: my Thread Id number
433        _RL statArr(0:nStats)        INTEGER nStats,sizI1,sizI2,sizJ1,sizJ2
       INTEGER sizI1,sizI2,sizJ1,sizJ2  
434        INTEGER iRun, jRun        INTEGER iRun, jRun
435          _RL statArr(0:nStats)
436        _RL inpArr (sizI1:sizI2,sizJ1:sizJ2)        _RL inpArr (sizI1:sizI2,sizJ1:sizJ2)
437        _RS regMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS regMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
438        _RS arrMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS arrMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 269  CEOP Line 450  CEOP
450  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
451  C     i,j    :: loop indices  C     i,j    :: loop indices
452        INTEGER i, j, n        INTEGER i, j, n
453        INTEGER im, ix, iv        INTEGER im, ix
       PARAMETER ( iv = nStats - 2 , im = nStats - 1 , ix = nStats )  
454        _RL tmpVol        _RL tmpVol
455    
456          im = nStats - 1
457          ix = nStats
458        DO n=0,nStats        DO n=0,nStats
459          statArr(n) = 0.          statArr(n) = 0.
460        ENDDO        ENDDO
# Line 328  c         IF ( regMask(i,j).NE.0. .AND. Line 510  c         IF ( regMask(i,j).NE.0. .AND.
510    
511        ENDIF        ENDIF
512    
513        RETURN        RETURN
514        END        END

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.2

  ViewVC Help
Powered by ViewVC 1.1.22