/[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.8 - (hide annotations) (download)
Sun Jul 23 00:35:53 2017 UTC (6 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, HEAD
Changes since 1.7: +179 -25 lines
Immplement thickness-factor averaged: new S/R DIAGNOSTICS_HF_CUMUL, called
from S/R DIAGNOSTICS_FILL_FIELD (and within file diagnostics_fill_field.F)

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

  ViewVC Help
Powered by ViewVC 1.1.22