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

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

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


Revision 1.4 - (hide annotations) (download)
Mon Jan 3 02:29:34 2005 UTC (19 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57d_post, checkpoint57c_pre, checkpoint57c_post
Changes since 1.3: +5 -5 lines
fill-in up to sNx+1 or sNy+1 if field at U,V or Z location (for mnc output)

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

  ViewVC Help
Powered by ViewVC 1.1.22