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

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

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


Revision 1.5 - (show annotations) (download)
Fri Feb 25 16:43:39 2005 UTC (19 years, 3 months ago) by molod
Branch: MAIN
CVS Tags: checkpoint57g_post, checkpoint57e_post, checkpoint57g_pre, checkpoint57f_pre, eckpoint57e_pre, checkpoint57f_post, checkpoint57h_pre, checkpoint57h_post
Changes since 1.4: +28 -29 lines
Add code for negative bibjflg possibility - indicates not to increment diagnostic counter

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

  ViewVC Help
Powered by ViewVC 1.1.22