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

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

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


Revision 1.14 - (show annotations) (download)
Mon Jul 26 21:16:18 2004 UTC (19 years, 9 months ago) by molod
Branch: MAIN
CVS Tags: checkpoint55c_post, checkpoint54e_post, checkpoint55d_pre, checkpoint55j_post, checkpoint56b_post, checkpoint55h_post, checkpoint55b_post, checkpoint54d_post, checkpoint56c_post, checkpoint55, checkpoint57a_post, checkpoint54f_post, checkpoint55g_post, checkpoint55f_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, checkpoint55e_post, checkpoint55a_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.13: +6 -3 lines
Code to write fewer than total number of levels to output file

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_utils.F,v 1.13 2004/07/08 16:16:09 edhill Exp $
2 C $Name: $
3
4 #include "DIAG_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP 0
8 C !ROUTINE: GETDIAG
9
10 C !INTERFACE:
11 SUBROUTINE GETDIAG (myThid,levreal,ipoint,undef,qtmp)
12
13 C !DESCRIPTION:
14 C Retrieve averaged model diagnostic
15
16 C !USES:
17 implicit none
18 #include "EEPARAMS.h"
19 #include "CPP_OPTIONS.h"
20 #include "SIZE.h"
21 CEOP
22
23 #ifdef ALLOW_FIZHI
24 #include "fizhi_SIZE.h"
25 #else
26 integer Nrphys
27 parameter (Nrphys=0)
28 #endif
29
30 #include "diagnostics_SIZE.h"
31 #include "diagnostics.h"
32
33 C INPUT:
34 C lev ..... Diagnostic LEVEL
35 C ipoint ..... DIAGNOSTIC NUMBER FROM MENU
36 C undef ..... UNDEFINED VALUE
37 C bi ..... X-direction process(or) number
38 C bj ..... Y-direction process(or) number
39 integer myThid,ipoint
40 _RL undef
41
42 C OUTPUT:
43 C qtmp ..... AVERAGED DIAGNOSTIC QUANTITY
44 _RL qtmp(1-OLx:sNx+Olx,1-Oly:sNy+Oly,Nr+Nrphys,Nsx,Nsy)
45 _RL levreal
46
47 _RL factor
48 integer i,j,ipnt,klev
49 integer bi,bj
50 integer lev
51
52 lev = levreal
53 if (ipoint.lt.1) go to 999
54
55 klev = kdiag(ipoint)
56 if (klev.ge.lev) then
57 ipnt = idiag(ipoint) + lev - 1
58 factor = 1.0
59 if (ndiag(ipoint).ne.0) factor = 1.0/ndiag(ipoint)
60
61 do bj=myByLo(myThid), myByHi(myThid)
62 do bi=myBxLo(myThid), myBxHi(myThid)
63
64 do j = 1,sNy
65 do i = 1,sNx
66 if ( qdiag(i,j,ipnt,bi,bj) .le. undef ) then
67 qtmp(i,j,lev,bi,bj) = qdiag(i,j,ipnt,bi,bj)*factor
68 else
69 qtmp(i,j,lev,bi,bj) = undef
70 endif
71 enddo
72 enddo
73
74 enddo
75 enddo
76
77 endif
78
79 999 return
80 end
81
82 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
83 CBOP 0
84 C !ROUTINE: GETDIAG2
85
86 C !INTERFACE:
87 SUBROUTINE GETDIAG2 (myThid,lev,ipoint,undef,qtmp)
88
89 C !DESCRIPTION:
90 C***********************************************************************
91 C PURPOSE
92 C Retrieve averaged model diagnostic
93 C INPUT:
94 C lev ..... Diagnostic LEVEL
95 C ipoint ..... DIAGNOSTIC NUMBER FROM MENU
96 C undef ..... UNDEFINED VALUE
97 C
98 C OUTPUT:
99 C qtmp ..... AVERAGED DIAGNOSTIC QUANTITY
100 C
101 C***********************************************************************
102
103 C !USES:
104 implicit none
105 #include "EEPARAMS.h"
106 #include "CPP_OPTIONS.h"
107 #include "SIZE.h"
108 CEOP
109
110 #ifdef ALLOW_FIZHI
111 #include "fizhi_SIZE.h"
112 #else
113 integer Nrphys
114 parameter (Nrphys=0)
115 #endif
116
117 #include "diagnostics_SIZE.h"
118 #include "diagnostics.h"
119
120 integer myThid,lev,ipoint
121 _RL undef
122 _RL qtmp(1-OLx:sNx+Olx,1-Oly:sNy+Oly,Nr+Nrphys,Nsx,Nsy)
123
124 integer i,j,ipnt,klev
125 integer bi,bj
126
127 if (ipoint.lt.1) go to 999
128
129 klev = kdiag(ipoint)
130 if (klev.ge.lev) then
131 ipnt = idiag(ipoint) + lev - 1
132
133 do bj=myByLo(myThid), myByHi(myThid)
134 do bi=myBxLo(myThid), myBxHi(myThid)
135
136 do j = 1,sNy
137 do i = 1,sNx
138 if ( qdiag(i,j,ipnt,bi,bj) .le. undef ) then
139 qtmp(i,j,lev,bi,bj) = qdiag(i,j,ipnt,bi,bj)
140 else
141 qtmp(i,j,lev,bi,bj) = undef
142 endif
143 enddo
144 enddo
145
146 enddo
147 enddo
148
149 endif
150
151 999 return
152 end
153
154 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
155
156 subroutine clrindx (myThid,listnum)
157 C***********************************************************************
158 C
159 C PURPOSE
160 C DRIVER TO CLEAR DIAGNOSTICS SPECIFIED IN DIAGNOSTIC INDEX LIST
161 C
162 C ARGUMENT DESCRIPTION
163 C listnum .... diagnostics list number
164 C
165 C***********************************************************************
166
167 implicit none
168 #include "EEPARAMS.h"
169 #include "CPP_OPTIONS.h"
170 #include "SIZE.h"
171 #include "diagnostics_SIZE.h"
172 #include "diagnostics.h"
173
174 integer myThid, listnum
175
176 integer m, n
177 character*8 parms1
178 character*1 parse1(8)
179 character*3 mate_index
180 integer mate
181
182 equivalence ( parms1 , parse1(1) )
183 equivalence ( mate_index , parse1(6) )
184
185 do n=1,nfields(listnum)
186 do m=1,ndiagt
187 if( flds(n,listnum).eq.cdiag(m) .and. idiag(m).ne.0 ) then
188 call clrdiag (myThid,m)
189
190 c Check for Counter Diagnostic
191 c ----------------------------
192 parms1 = gdiag(m)
193 if( parse1(5).eq.'C' ) then
194 read (mate_index,100) mate
195 call clrdiag (myThid,mate)
196 endif
197 endif
198 enddo
199 enddo
200
201 100 format(i3)
202 RETURN
203 END
204
205
206 subroutine clrdiag (myThid,index)
207 C***********************************************************************
208 C PURPOSE
209 C ZERO OUT MODEL DIAGNOSTIC ARRAY ELEMENTS
210 C***********************************************************************
211
212 implicit none
213 #include "EEPARAMS.h"
214 #include "CPP_OPTIONS.h"
215 #include "SIZE.h"
216 #include "diagnostics_SIZE.h"
217 #include "diagnostics.h"
218
219 integer myThid, index
220
221 integer bi,bj
222 integer i,j,k
223
224 C **********************************************************************
225 C **** SET DIAGNOSTIC AND COUNTER TO ZERO ****
226 C **********************************************************************
227
228 do bj=myByLo(myThid), myByHi(myThid)
229 do bi=myBxLo(myThid), myBxHi(myThid)
230 do k = 1,kdiag(index)
231 do j = 1,sNy
232 do i = 1,sNx
233 qdiag(i,j,idiag(index)+k-1,bi,bj) = 0.0
234 enddo
235 enddo
236 enddo
237 enddo
238 enddo
239
240 ndiag(index) = 0
241
242 return
243 end
244
245 subroutine setdiag (myThid,num,ndiagmx)
246 C***********************************************************************
247 C
248 C PURPOSE
249 C SET POINTER LOCATIONS, NAMES, LEVELS and TITLES FOR DIAGNOSTIC NUM
250 C
251 C***********************************************************************
252
253 implicit none
254 #include "CPP_OPTIONS.h"
255 #include "SIZE.h"
256 #include "diagnostics_SIZE.h"
257 #include "diagnostics.h"
258
259 integer num,myThid,ndiagmx
260 integer ipointer
261
262 DATA IPOINTER / 1 /
263
264 character*8 parms1
265 character*1 parse1(8)
266 character*3 mate_index
267 integer mate
268
269 equivalence ( parms1 , parse1(1) )
270 equivalence ( mate_index , parse1(6) )
271
272 C **********************************************************************
273 C **** SET POINTERS FOR DIAGNOSTIC NUM ****
274 C **********************************************************************
275
276 parms1 = gdiag(num)
277
278 IF( IDIAG(NUM).EQ.0 ) THEN
279 if(ndiagmx+kdiag(num).gt.numdiags) then
280 write(6,4000)num,cdiag(num)
281 else
282 IDIAG(NUM) = IPOINTER
283 IPOINTER = IPOINTER + KDIAG(NUM)
284 ndiagmx = ndiagmx + KDIAG(NUM)
285 if(myThid.eq.1) WRITE(6,2000)KDIAG(NUM),NUM,CDIAG(NUM),ndiagmx
286 endif
287 ELSE
288 if(myThid.eq.1) WRITE(6,3000) NUM, CDIAG(NUM)
289 ENDIF
290
291 c Check for Counter Diagnostic
292 c ----------------------------
293 if( parse1(5).eq.'C') then
294 read (mate_index,100) mate
295
296 IF( IDIAG(mate).EQ.0 ) THEN
297 if(ndiagmx+kdiag(num).gt.numdiags) then
298 write(6,5000)num,cdiag(num)
299 else
300 IDIAG(mate) = IPOINTER
301 IPOINTER = IPOINTER + KDIAG(mate)
302 ndiagmx = ndiagmx + KDIAG(mate)
303 if(myThid.eq.1)WRITE(6,2000)KDIAG(mate),mate,CDIAG(mate),ndiagmx
304 endif
305 ELSE
306 if(myThid.eq.1) WRITE(6,3000) mate, CDIAG(mate)
307 ENDIF
308 endif
309
310 RETURN
311
312 100 format(i3)
313 2000 FORMAT(1X,'Allocating ',I2,' Level(s) for Diagnostic # ',I3,
314 . ' (',A8,'), Total Number of Diagnostics: ',I5)
315 3000 FORMAT(1X,'Diagnostic # ',I3,' (',A8,') has already been set')
316 4000 FORMAT(1X,'Unable to allocate space for Diagnostic # ',I3,
317 . ' (',A8,')')
318 5000 FORMAT(1X,'Unable to allocate space for Counter Diagnostic # ',
319 . I3,' (',A8,')',' WARNING - Diag will not accumulate properly')
320 END

  ViewVC Help
Powered by ViewVC 1.1.22