/[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.2 - (show annotations) (download)
Sun Jun 26 16:51:49 2005 UTC (18 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57k_post, checkpoint57j_post
Changes since 1.1: +34 -25 lines
change pointers so that 1 diag. can be used several times (with # freq.)

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

  ViewVC Help
Powered by ViewVC 1.1.22