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

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

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


Revision 1.7 - (hide annotations) (download)
Sat Apr 3 17:34:39 2010 UTC (14 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint65, checkpoint63, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.6: +5 -5 lines
always stops when arrType < 0

1 jmc 1.7 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_fill_field.F,v 1.6 2009/09/03 20:39:18 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "DIAG_OPTIONS.h"
5    
6 jmc 1.5 C-- File diagnostics_fill_field.F:
7     C-- Contents:
8     C-- o DIAGNOSTICS_FILL_FIELD
9 jmc 1.6 C-- o DIAGNOSTICS_CUMULATE
10 jmc 1.5
11     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
12 jmc 1.1 CBOP
13     C !ROUTINE: DIAGNOSTICS_FILL_FIELD
14     C !INTERFACE:
15 jmc 1.3 SUBROUTINE DIAGNOSTICS_FILL_FIELD(
16 jmc 1.6 I inpFldRL, fracFldRL, inpFldRS, fracFldRS,
17     I scaleFact, power, arrType, nLevFrac,
18 jmc 1.4 I ndiagnum, ipointer, kLev, nLevs,
19     I bibjFlg, biArg, bjArg, myThid )
20 jmc 1.1
21     C !DESCRIPTION:
22     C***********************************************************************
23 jmc 1.3 C Increment the diagnostics array with a 2D/3D field
24 jmc 1.4 C using a scaling factor & square option (power=2),
25 jmc 1.3 C and with the option to use a fraction-weight (assumed
26     C to be the counter-mate of the current diagnostics)
27 jmc 1.1 C***********************************************************************
28     C !USES:
29     IMPLICIT NONE
30    
31     C == Global variables ===
32     #include "EEPARAMS.h"
33     #include "SIZE.h"
34     #include "DIAGNOSTICS_SIZE.h"
35     #include "DIAGNOSTICS.h"
36    
37     C !INPUT PARAMETERS:
38     C***********************************************************************
39     C Arguments Description
40     C ----------------------
41 jmc 1.6 C inpFldRL :: Field to increment diagnostics array (arrType=0,1)
42     C fracFldRL :: fraction used for weighted average diagnostics (arrType=0,2)
43     C inpFldRS :: Field to increment diagnostics array (arrType=2,3)
44     C fracFldRS :: fraction used for weighted average diagnostics (arrType=1,3)
45 jmc 1.4 C scaleFact :: scaling factor
46     C power :: option to fill-in with the field square (power=2)
47 jmc 1.6 C arrType :: select which array & fraction (RL/RS) to process:
48     C 0: both RL ; 1: inpRL & fracRS ; 2: inpRS,fracRL ; 3: both RS
49     C nLevFrac :: number of levels of the fraction field, =0: do not use fraction
50 jmc 1.4 C ndiagnum :: Diagnostics Number (in available diag list) of diag to process
51     C ipointer :: Pointer to the slot in qdiag to fill
52     C kLev :: Integer flag for vertical levels:
53 jmc 1.1 C > 0 (any integer): WHICH single level to increment in qdiag.
54     C 0,-1 to increment "nLevs" levels in qdiag,
55 jmc 1.2 C 0 : fill-in in the same order as the input array
56 jmc 1.1 C -1: fill-in in reverse order.
57 jmc 1.4 C nLevs :: indicates Number of levels of the input field array
58 jmc 1.1 C (whether to fill-in all the levels (kLev<1) or just one (kLev>0))
59 jmc 1.4 C bibjFlg :: Integer flag to indicate instructions for bi bj loop
60 jmc 1.1 C 0 indicates that the bi-bj loop must be done here
61     C 1 indicates that the bi-bj loop is done OUTSIDE
62     C 2 indicates that the bi-bj loop is done OUTSIDE
63     C AND that we have been sent a local array (with overlap regions)
64     C 3 indicates that the bi-bj loop is done OUTSIDE
65     C AND that we have been sent a local array
66     C AND that the array has no overlap region (interior only)
67 jmc 1.2 C NOTE - bibjFlg can be NEGATIVE to indicate not to increment counter
68 jmc 1.4 C biArg :: X-direction tile number - used for bibjFlg=1-3
69     C bjArg :: Y-direction tile number - used for bibjFlg=1-3
70     C myThid :: my thread Id number
71 jmc 1.1 C***********************************************************************
72     C NOTE: User beware! If a local (1 tile only) array
73 jmc 1.2 C is sent here, bibjFlg MUST NOT be set to 0
74 jmc 1.1 C or there will be out of bounds problems!
75     C***********************************************************************
76 jmc 1.6 _RL inpFldRL(*)
77     _RL fracFldRL(*)
78     _RS inpFldRS(*)
79     _RS fracFldRS(*)
80 jmc 1.3 _RL scaleFact
81 jmc 1.4 INTEGER power
82 jmc 1.6 INTEGER arrType
83     INTEGER nLevFrac
84 jmc 1.1 INTEGER ndiagnum, ipointer
85 jmc 1.2 INTEGER kLev, nLevs, bibjFlg, biArg, bjArg
86 jmc 1.1 INTEGER myThid
87     CEOP
88    
89     C !LOCAL VARIABLES:
90     C ===============
91 jmc 1.4 C useFract :: flag to increment (or not) with fraction-weigted inpFld
92 jmc 1.3 LOGICAL useFract
93     INTEGER sizF
94 jmc 1.1 INTEGER sizI1,sizI2,sizJ1,sizJ2
95     INTEGER sizTx,sizTy
96     INTEGER iRun, jRun, k, bi, bj
97     INTEGER kFirst, kLast
98     INTEGER kd, kd0, ksgn, kStore
99     CHARACTER*8 parms1
100     CHARACTER*(MAX_LEN_MBUF) msgBuf
101    
102     C If-sequence to see if we are a valid and an active diagnostic
103     c IF ( ndiagnum.NE.0 .AND. ipointer.NE.0 ) THEN
104    
105 jmc 1.2 IF ( bibjFlg.GE.0 .AND. ABS(kLev).LE.1 ) THEN
106     C Increment the counter for the diagnostic
107     IF ( bibjFlg.EQ.0 ) THEN
108     DO bj=myByLo(myThid), myByHi(myThid)
109     DO bi=myBxLo(myThid), myBxHi(myThid)
110     ndiag(ipointer,bi,bj) = ndiag(ipointer,bi,bj) + 1
111     ENDDO
112     ENDDO
113     ELSE
114     bi = MIN(biArg,nSx)
115     bj = MIN(bjArg,nSy)
116     ndiag(ipointer,bi,bj) = ndiag(ipointer,bi,bj) + 1
117     ENDIF
118     ENDIF
119 jmc 1.1
120     C- select range for 1rst & 2nd indices to accumulate
121 jmc 1.2 C depending on variable location on C-grid,
122 jmc 1.1 parms1 = gdiag(ndiagnum)(1:8)
123     IF ( parms1(2:2).EQ.'M' ) THEN
124     iRun = sNx
125     jRun = sNy
126     ELSEIF ( parms1(2:2).EQ.'U' ) THEN
127     iRun = sNx+1
128     jRun = sNy
129     ELSEIF ( parms1(2:2).EQ.'V' ) THEN
130     iRun = sNx
131     jRun = sNy+1
132     ELSEIF ( parms1(2:2).EQ.'Z' ) THEN
133     iRun = sNx+1
134     jRun = sNy+1
135     ELSE
136     iRun = sNx
137     jRun = sNy
138     ENDIF
139    
140     C- Dimension of the input array:
141 jmc 1.2 IF (abs(bibjFlg).EQ.3) THEN
142 jmc 1.1 sizI1 = 1
143     sizI2 = sNx
144     sizJ1 = 1
145     sizJ2 = sNy
146     iRun = sNx
147     jRun = sNy
148     ELSE
149     sizI1 = 1-OLx
150     sizI2 = sNx+OLx
151     sizJ1 = 1-OLy
152     sizJ2 = sNy+OLy
153     ENDIF
154 jmc 1.2 IF (abs(bibjFlg).GE.2) THEN
155 jmc 1.1 sizTx = 1
156     sizTy = 1
157     ELSE
158     sizTx = nSx
159     sizTy = nSy
160     ENDIF
161     C- Which part of inpFld to add : k = 3rd index,
162     C and do the loop >> do k=kFirst,kLast <<
163     IF (kLev.LE.0) THEN
164     kFirst = 1
165     kLast = nLevs
166     ELSEIF ( nLevs.EQ.1 ) THEN
167     kFirst = 1
168     kLast = 1
169     ELSEIF ( kLev.LE.nLevs ) THEN
170     kFirst = kLev
171     kLast = kLev
172     ELSE
173     STOP 'ABNORMAL END in DIAGNOSTICS_FILL_FIELD: kLev > nLevs >0'
174     ENDIF
175 jmc 1.2 C- Which part of qdiag to update: kd = 3rd index,
176 jmc 1.1 C and do the loop >> do k=kFirst,kLast ; kd = kd0 + k*ksgn <<
177     IF ( kLev.EQ.-1 ) THEN
178     ksgn = -1
179     kd0 = ipointer + nLevs
180     ELSEIF ( kLev.EQ.0 ) THEN
181     ksgn = 1
182     kd0 = ipointer - 1
183     ELSE
184     ksgn = 0
185     kd0 = ipointer + kLev - 1
186     ENDIF
187 jmc 1.3 C- Set fraction-weight option :
188 jmc 1.6 useFract = nLevFrac.GT.0
189 jmc 1.3 IF ( useFract ) THEN
190 jmc 1.6 sizF = nLevFrac
191 jmc 1.3 ELSE
192     sizF = 1
193     ENDIF
194 jmc 1.1
195     C- Check for consistency with Nb of levels reserved in storage array
196     kStore = kd0 + MAX(ksgn*kFirst,ksgn*kLast) - ipointer + 1
197     IF ( kStore.GT.kdiag(ndiagnum) ) THEN
198     _BEGIN_MASTER(myThid)
199 jmc 1.5 WRITE(msgBuf,'(2A,I4,A)') 'DIAGNOSTICS_FILL_FIELD: ',
200 jmc 1.1 & 'exceed Nb of levels(=',kdiag(ndiagnum),' ) reserved '
201     CALL PRINT_ERROR( msgBuf , myThid )
202 jmc 1.5 WRITE(msgBuf,'(2A,I6,2A)') 'DIAGNOSTICS_FILL_FIELD: ',
203 jmc 1.1 & 'for Diagnostics #', ndiagnum, ' : ', cdiag(ndiagnum)
204     CALL PRINT_ERROR( msgBuf , myThid )
205     WRITE(msgBuf,'(2A,2I4,I3)') 'calling DIAGNOSTICS_FILL_FIELD ',
206     I 'with kLev,nLevs,bibjFlg=', kLev,nLevs,bibjFlg
207     CALL PRINT_ERROR( msgBuf , myThid )
208     WRITE(msgBuf,'(2A,I6,A)') 'DIAGNOSTICS_FILL_FIELD: ',
209     I '==> trying to store up to ', kStore, ' levels'
210     CALL PRINT_ERROR( msgBuf , myThid )
211     STOP 'ABNORMAL END: S/R DIAGNOSTICS_FILL_FIELD'
212     _END_MASTER(myThid)
213     ENDIF
214    
215 jmc 1.2 IF ( bibjFlg.EQ.0 ) THEN
216    
217 jmc 1.1 DO bj=myByLo(myThid), myByHi(myThid)
218     DO bi=myBxLo(myThid), myBxHi(myThid)
219     DO k = kFirst,kLast
220     kd = kd0 + ksgn*k
221 jmc 1.6 CALL DIAGNOSTICS_CUMULATE(
222 jmc 1.1 U qdiag(1-OLx,1-OLy,kd,bi,bj),
223 jmc 1.6 I inpFldRL, fracFldRL, inpFldRS, fracFldRS,
224     I scaleFact, power, arrType, useFract, sizF,
225 jmc 1.1 I sizI1,sizI2,sizJ1,sizJ2,nLevs,sizTx,sizTy,
226     I iRun,jRun,k,bi,bj,
227     I myThid)
228     ENDDO
229     ENDDO
230     ENDDO
231     ELSE
232     bi = MIN(biArg,sizTx)
233     bj = MIN(bjArg,sizTy)
234     DO k = kFirst,kLast
235     kd = kd0 + ksgn*k
236 jmc 1.6 CALL DIAGNOSTICS_CUMULATE(
237 jmc 1.1 U qdiag(1-OLx,1-OLy,kd,biArg,bjArg),
238 jmc 1.6 I inpFldRL, fracFldRL, inpFldRS, fracFldRS,
239     I scaleFact, power, arrType, useFract, sizF,
240 jmc 1.1 I sizI1,sizI2,sizJ1,sizJ2,nLevs,sizTx,sizTy,
241     I iRun,jRun,k,bi,bj,
242     I myThid)
243     ENDDO
244     ENDIF
245    
246     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
247     c ELSE
248     c IF (myThid.EQ.1) WRITE(6,1000) cdiag(ndiagnum)
249    
250     c ENDIF
251    
252 jmc 1.5 c1000 format(' ',' Warning: Trying to write to diagnostic ',a8,
253     c & ' But it is not a valid (or active) name ')
254 jmc 1.2 RETURN
255 jmc 1.1 END
256    
257     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
258    
259     CBOP
260 jmc 1.6 C !ROUTINE: DIAGNOSTICS_CUMULATE
261 jmc 1.1 C !INTERFACE:
262 jmc 1.6 SUBROUTINE DIAGNOSTICS_CUMULATE(
263 jmc 1.1 U cumFld,
264 jmc 1.6 I inpFldRL, frcFldRL, inpFldRS, frcFldRS,
265     I scaleFact, power, arrType, useFract, sizF,
266 jmc 1.1 I sizI1,sizI2,sizJ1,sizJ2,sizK,sizTx,sizTy,
267     I iRun,jRun,k,bi,bj,
268 jmc 1.6 I myThid )
269 jmc 1.1
270     C !DESCRIPTION:
271 jmc 1.2 C Update array cumFld
272 jmc 1.1 C by adding content of input field array inpFld
273     C over the range [1:iRun],[1:jRun]
274    
275     C !USES:
276     IMPLICIT NONE
277    
278     #include "EEPARAMS.h"
279     #include "SIZE.h"
280    
281     C !INPUT/OUTPUT PARAMETERS:
282     C == Routine Arguments ==
283     C cumFld :: cumulative array (updated)
284 jmc 1.6 C inpFldRL :: input field array to add to cumFld (arrType=0,1)
285     C frcFldRL :: fraction used for weighted-average diagnostics (arrType=0,2)
286     C inpFldRS :: input field array to add to cumFld (arrType=2,3)
287     C frcFldRS :: fraction used for weighted-average diagnostics (arrType=1,3)
288 jmc 1.3 C scaleFact :: scaling factor
289 jmc 1.4 C power :: option to fill-in with the field square (power=2)
290 jmc 1.6 C arrType :: select which array & fraction (RL/RS) to process:
291     C 0: both RL ; 1: inpRL & fracRS ; 2: inpRS,fracRL ; 3: both RS
292 jmc 1.3 C useFract :: if True, use fraction-weight
293     C sizF :: size of frcFld array: 3rd dimension
294 jmc 1.1 C sizI1,sizI2 :: size of inpFld array: 1rst index range (min,max)
295     C sizJ1,sizJ2 :: size of inpFld array: 2nd index range (min,max)
296     C sizK :: size of inpFld array: 3rd dimension
297     C sizTx,sizTy :: size of inpFld array: tile dimensions
298     C iRun,jRun :: range of 1rst & 2nd index
299 jmc 1.6 C k,bi,bj :: level and tile indices of inFld array to add to cumFld array
300 jmc 1.1 C myThid :: my Thread Id number
301     _RL cumFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
302     INTEGER sizI1,sizI2,sizJ1,sizJ2
303 jmc 1.3 INTEGER sizF,sizK,sizTx,sizTy
304 jmc 1.6 _RL inpFldRL(sizI1:sizI2,sizJ1:sizJ2,sizK,sizTx,sizTy)
305     _RL frcFldRL(sizI1:sizI2,sizJ1:sizJ2,sizF,sizTx,sizTy)
306     _RS inpFldRS(sizI1:sizI2,sizJ1:sizJ2,sizK,sizTx,sizTy)
307     _RS frcFldRS(sizI1:sizI2,sizJ1:sizJ2,sizF,sizTx,sizTy)
308 jmc 1.3 _RL scaleFact
309 jmc 1.4 INTEGER power
310 jmc 1.6 INTEGER arrType
311 jmc 1.3 LOGICAL useFract
312 jmc 1.1 INTEGER iRun, jRun, k, bi, bj
313     INTEGER myThid
314     CEOP
315    
316     C !LOCAL VARIABLES:
317     C i,j :: loop indices
318 jmc 1.3 INTEGER i, j, l
319 jmc 1.4 _RL tmpFact
320 jmc 1.1
321 jmc 1.3 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
322    
323 jmc 1.4 tmpFact = scaleFact
324     IF ( power.EQ.2 ) tmpFact = scaleFact*scaleFact
325    
326     IF ( useFract .AND. power.EQ.2 ) THEN
327     l = MIN(k,sizF)
328 jmc 1.6
329     IF ( arrType.EQ.0 ) THEN
330     DO j = 1,jRun
331     DO i = 1,iRun
332     cumFld(i,j) = cumFld(i,j)
333     & + tmpFact*inpFldRL(i,j,k,bi,bj)
334     & *inpFldRL(i,j,k,bi,bj)
335     & *frcFldRL(i,j,l,bi,bj)
336     ENDDO
337     ENDDO
338     ELSEIF ( arrType.EQ.1 ) THEN
339     DO j = 1,jRun
340     DO i = 1,iRun
341 jmc 1.4 cumFld(i,j) = cumFld(i,j)
342 jmc 1.6 & + tmpFact*inpFldRL(i,j,k,bi,bj)
343     & *inpFldRL(i,j,k,bi,bj)
344     & *frcFldRS(i,j,l,bi,bj)
345     ENDDO
346 jmc 1.4 ENDDO
347 jmc 1.6 ELSEIF ( arrType.EQ.2 ) THEN
348     DO j = 1,jRun
349     DO i = 1,iRun
350     cumFld(i,j) = cumFld(i,j)
351     & + tmpFact*inpFldRS(i,j,k,bi,bj)
352     & *inpFldRS(i,j,k,bi,bj)
353     & *frcFldRL(i,j,l,bi,bj)
354     ENDDO
355     ENDDO
356     ELSEIF ( arrType.EQ.3 ) THEN
357     DO j = 1,jRun
358     DO i = 1,iRun
359     cumFld(i,j) = cumFld(i,j)
360     & + tmpFact*inpFldRS(i,j,k,bi,bj)
361     & *inpFldRS(i,j,k,bi,bj)
362     & *frcFldRS(i,j,l,bi,bj)
363     ENDDO
364     ENDDO
365     ELSE
366     STOP 'DIAGNOSTICS_CUMULATE: invalid arrType'
367     ENDIF
368    
369 jmc 1.4 ELSEIF ( useFract ) THEN
370 jmc 1.3 l = MIN(k,sizF)
371 jmc 1.6
372     IF ( arrType.EQ.0 ) THEN
373     DO j = 1,jRun
374     DO i = 1,iRun
375     cumFld(i,j) = cumFld(i,j)
376     & + tmpFact*inpFldRL(i,j,k,bi,bj)
377     & *frcFldRL(i,j,l,bi,bj)
378     ENDDO
379     ENDDO
380     ELSEIF ( arrType.EQ.1 ) THEN
381     DO j = 1,jRun
382     DO i = 1,iRun
383 jmc 1.4 cumFld(i,j) = cumFld(i,j)
384 jmc 1.6 & + tmpFact*inpFldRL(i,j,k,bi,bj)
385     & *frcFldRS(i,j,l,bi,bj)
386     ENDDO
387 jmc 1.4 ENDDO
388 jmc 1.6 ELSEIF ( arrType.EQ.2 ) THEN
389     DO j = 1,jRun
390     DO i = 1,iRun
391     cumFld(i,j) = cumFld(i,j)
392     & + tmpFact*inpFldRS(i,j,k,bi,bj)
393     & *frcFldRL(i,j,l,bi,bj)
394     ENDDO
395     ENDDO
396     ELSEIF ( arrType.EQ.3 ) THEN
397     DO j = 1,jRun
398     DO i = 1,iRun
399     cumFld(i,j) = cumFld(i,j)
400     & + tmpFact*inpFldRS(i,j,k,bi,bj)
401     & *frcFldRS(i,j,l,bi,bj)
402     ENDDO
403     ENDDO
404     ELSE
405     STOP 'DIAGNOSTICS_CUMULATE: invalid arrType'
406     ENDIF
407    
408 jmc 1.4 ELSEIF ( power.EQ.2 ) THEN
409 jmc 1.6
410 jmc 1.7 IF ( arrType.EQ.0 .OR. arrType.EQ.1 ) THEN
411 jmc 1.6 DO j = 1,jRun
412     DO i = 1,iRun
413     cumFld(i,j) = cumFld(i,j)
414     & + tmpFact*inpFldRL(i,j,k,bi,bj)
415     & *inpFldRL(i,j,k,bi,bj)
416     ENDDO
417     ENDDO
418 jmc 1.7 ELSEIF ( arrType.EQ.2 .OR. arrType.EQ.3 ) THEN
419 jmc 1.6 DO j = 1,jRun
420     DO i = 1,iRun
421 jmc 1.4 cumFld(i,j) = cumFld(i,j)
422 jmc 1.6 & + tmpFact*inpFldRS(i,j,k,bi,bj)
423     & *inpFldRS(i,j,k,bi,bj)
424     ENDDO
425 jmc 1.3 ENDDO
426 jmc 1.6 ELSE
427     STOP 'DIAGNOSTICS_CUMULATE: invalid arrType'
428     ENDIF
429    
430 jmc 1.3 ELSE
431 jmc 1.6
432 jmc 1.7 IF ( arrType.EQ.0 .OR. arrType.EQ.1 ) THEN
433 jmc 1.6 DO j = 1,jRun
434     DO i = 1,iRun
435 jmc 1.2 C- jmc: try with fixed ranges, that are known at compiling stage
436 jmc 1.1 C (might produce a better cash optimisation ?)
437 jmc 1.6 c DO j = 1,sNy
438     c DO i = 1,sNx
439     cumFld(i,j) = cumFld(i,j)
440     & + tmpFact*inpFldRL(i,j,k,bi,bj)
441     ENDDO
442     ENDDO
443 jmc 1.7 ELSEIF ( arrType.EQ.2 .OR. arrType.EQ.3 ) THEN
444 jmc 1.6 DO j = 1,jRun
445     DO i = 1,iRun
446 jmc 1.4 cumFld(i,j) = cumFld(i,j)
447 jmc 1.6 & + tmpFact*inpFldRS(i,j,k,bi,bj)
448     ENDDO
449 jmc 1.3 ENDDO
450 jmc 1.6 ELSE
451     STOP 'DIAGNOSTICS_CUMULATE: invalid arrType'
452     ENDIF
453    
454 jmc 1.3 ENDIF
455 jmc 1.1
456 jmc 1.2 RETURN
457 jmc 1.1 END

  ViewVC Help
Powered by ViewVC 1.1.22