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

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

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


Revision 1.5 - (show annotations) (download)
Tue Feb 5 15:31:19 2008 UTC (16 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59o, checkpoint59n, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q
Changes since 1.4: +11 -5 lines
minor modifications for many diagnostics:
- modify "available_diagnostics.log" and diagnostics summary (write mate number)
- use wider (integer) format (generally, use I6) to write diagnostics number
- rename numdiags --> numDiags (to differentiate from mdiag)

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

  ViewVC Help
Powered by ViewVC 1.1.22