/[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.4 - (hide annotations) (download)
Mon Jul 11 18:59:07 2005 UTC (18 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, mitgcm_mapl_00, checkpoint58u_post, checkpoint58w_post, checkpoint57m_post, checkpoint57s_post, checkpoint58r_post, checkpoint57y_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint57y_pre, checkpoint58q_post, checkpoint57v_post, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint57r_post, checkpoint59, checkpoint58, checkpoint58f_post, checkpoint57x_post, checkpoint57n_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint58b_post, checkpoint58m_post, checkpoint57l_post
Changes since 1.3: +56 -25 lines
add option to fill a squared diagnostics directly.

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

  ViewVC Help
Powered by ViewVC 1.1.22