/[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.3 - (show annotations) (download)
Sun Jul 10 00:59:01 2005 UTC (18 years, 11 months ago) by jmc
Branch: MAIN
Changes since 1.2: +55 -15 lines
o modif to fill a diagnostics using a scaling factor and a fraction-weight
      field ; does not affect diagnostics_fill.F arguments.

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

  ViewVC Help
Powered by ViewVC 1.1.22