/[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.12 - (show annotations) (download)
Thu Jul 8 00:30:45 2004 UTC (19 years, 10 months ago) by edhill
Branch: MAIN
Changes since 1.11: +78 -60 lines
 o fix the logic: ".ge." should be ".le."
 o indent the fixed areas
 o protex-ify the two altered subroutines

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

  ViewVC Help
Powered by ViewVC 1.1.22