/[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.2 - (show annotations) (download)
Sun Dec 19 20:27:42 2004 UTC (19 years, 5 months ago) by jmc
Branch: MAIN
Changes since 1.1: +225 -242 lines
re-write to avoid making a local copy of input array ; add a safety check.

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

  ViewVC Help
Powered by ViewVC 1.1.22