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

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

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


Revision 1.2 - (show annotations) (download)
Wed Jul 6 14:58:11 2005 UTC (18 years, 10 months ago) by edhill
Branch: MAIN
Changes since 1.1: +6 -4 lines
 o add myIter to the output and fix type for myTime

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagstats_mnc_out.F,v 1.1 2005/07/06 02:13:52 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: DIAGSTATS_MNC_OUT
9
10 C !INTERFACE:
11 SUBROUTINE DIAGSTATS_MNC_OUT(
12 I statGlob, nLev, ndId,
13 I mId, listId, myTime, myIter, myThid )
14
15 C !DESCRIPTION:
16 C Write Global statistics to a netCDF file
17
18 C !USES:
19 IMPLICIT NONE
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "EESUPPORT.h"
23 #include "PARAMS.h"
24 #include "GRID.h"
25 #include "DIAGNOSTICS_SIZE.h"
26 #include "DIAGNOSTICS.h"
27
28 #ifdef ALLOW_FIZHI
29 #include "fizhi_SIZE.h"
30 #else
31 INTEGER Nrphys
32 PARAMETER (Nrphys=0)
33 #endif
34
35 C !INPUT PARAMETERS:
36 C statGlob :: AVERAGED DIAGNOSTIC QUANTITY
37 C nLev :: 2nd Dimension (max Nb of levels) of statGlob array
38 C ndId :: diagnostic Id number (in diagnostics long list)
39 C mId :: field rank in list "listId"
40 C listId :: current output Stream list
41 C myIter :: current Iteration Number
42 C myTime :: current time of simulation (s)
43 C myThid :: my thread Id number
44 INTEGER nLev
45 _RL statGlob(0:nStats,0:nLev,0:nRegions)
46 _RL myTime
47 INTEGER ndId, mId, listId
48 INTEGER myIter, myThid
49 CEOP
50
51 C !LOCAL VARIABLES:
52 INTEGER im, ix, iv, ist
53 PARAMETER ( iv = nStats - 2 , im = nStats - 1 , ix = nStats )
54 INTEGER i, j, k
55 CHARACTER*(MAX_LEN_MBUF) tnam
56 CHARACTER*(3) stat_typ(5)
57 INTEGER ILNBLNK
58 EXTERNAL ILNBLNK
59 #ifdef ALLOW_MNC
60 INTEGER ii, ilen
61 CHARACTER*(MAX_LEN_FNAM) diag_mnc_bn
62 CHARACTER*(5) ctmp
63 INTEGER CW_DIMS, NLEN
64 PARAMETER ( CW_DIMS = 10 )
65 PARAMETER ( NLEN = 80 )
66 INTEGER dim(CW_DIMS), ib(CW_DIMS), ie(CW_DIMS)
67 CHARACTER*(NLEN) dn(CW_DIMS)
68 CHARACTER*(NLEN) d_cw_gname
69 CHARACTER*(NLEN) d_cw_gname0
70 CHARACTER*(NLEN) dn_blnk
71 _RS ztmp(Nr+Nrphys)
72 _RL stmp(Nr+Nrphys+1,nRegions+1)
73 #endif /* ALLOW_MNC */
74
75 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
76
77 #ifdef ALLOW_MNC
78
79 _BEGIN_MASTER( myThid)
80
81 stat_typ(1) = 'vol'
82 stat_typ(2) = 'ave'
83 stat_typ(3) = 'std'
84 stat_typ(4) = 'min'
85 stat_typ(5) = 'max'
86
87 #ifdef ALLOW_USE_MPI
88 IF ( diagSt_MNC .AND. mpiMyId.EQ.0 ) THEN
89 #else
90 IF ( diagSt_MNC ) THEN
91 #endif
92
93 DO i = 1,MAX_LEN_FNAM
94 diag_mnc_bn(i:i) = ' '
95 ENDDO
96 DO i = 1,NLEN
97 dn_blnk(i:i) = ' '
98 ENDDO
99 ilen = ILNBLNK(diagSt_Fname(listId))
100 WRITE(diag_mnc_bn, '(a)') diagSt_Fname(listId)(1:ilen)
101
102 IF (mId .EQ. 1) THEN
103 C Update the record dimension by writing the iteration number
104 CALL MNC_CW_SET_UDIM(diag_mnc_bn, -1, myThid)
105 CALL MNC_CW_RL_W_S('D',diag_mnc_bn,0,0,'T',myTime,myThid)
106 CALL MNC_CW_SET_UDIM(diag_mnc_bn, 0, myThid)
107 CALL MNC_CW_I_W_S('I',diag_mnc_bn,0,0,'iter',myIter,myThid)
108 ENDIF
109
110 #ifdef DIAGST_MNC_NEEDSWORK
111 C This is turned off for the time being but it should eventually
112 C be re-worked and turned on so that coordinate dimensions are
113 C supplied along with the data. Unfortunately, the current
114 C diagnostics system has **NO** way of telling us whether a
115 C quantity is defined on a typical vertical grid (eg. the dynamics
116 C grid), a gridalt--style grid, or a single-level field that has
117 C no specified vertical location.
118
119 dn(1)(1:NLEN) = dn_blnk(1:NLEN)
120 WRITE(dn(1),'(a,i6.6)') 'Zmd', kdiag(ndId)
121 dim(1) = kdiag(ndId)
122 ib(1) = 1
123 ie(1) = kdiag(ndId)
124
125 CALL MNC_CW_ADD_GNAME('diag_levels', 1,
126 & dim, dn, ib, ie, myThid)
127 CALL MNC_CW_ADD_VNAME('diag_levels', 'diag_levels',
128 & 0,0, myThid)
129 CALL MNC_CW_ADD_VATTR_TEXT('diag_levels','description',
130 & 'Idicies of vertical levels within the source arrays',
131 & myThid)
132
133 CALL MNC_CW_RL_W('D',diag_mnc_bn,0,0,
134 & 'diag_levels', levs(1,listId), myThid)
135
136 CALL MNC_CW_DEL_VNAME('diag_levels', myThid)
137 CALL MNC_CW_DEL_GNAME('diag_levels', myThid)
138
139 C Now define: Zmdxxxxxx, Zudxxxxxx, Zldxxxxxx
140 ctmp(1:5) = 'mul '
141 DO i = 1,3
142 dn(1)(1:NLEN) = dn_blnk(1:NLEN)
143 WRITE(dn(1),'(3a,i6.6)') 'Z',ctmp(i:i),'d',nlevels(listId)
144 CALL MNC_CW_ADD_GNAME(dn(1), 1, dim, dn, ib, ie, myThid)
145 CALL MNC_CW_ADD_VNAME(dn(1), dn(1), 0,0, myThid)
146
147 C The following three ztmp() loops should eventually be modified
148 C to reflect the fractional nature of levs(j,l) -- they should
149 C do something like:
150 C ztmp(j) = rC(INT(FLOOR(levs(j,l))))
151 C + ( rC(INT(FLOOR(levs(j,l))))
152 C + rC(INT(CEIL(levs(j,l)))) )
153 C / ( levs(j,l) - FLOOR(levs(j,l)) )
154 C for averaged levels.
155 IF (i .EQ. 1) THEN
156 DO j = 1,nlevels(listId)
157 ztmp(j) = rC(NINT(levs(j,listId)))
158 ENDDO
159 CALL MNC_CW_ADD_VATTR_TEXT(dn(1),'description',
160 & 'Dimensional coordinate value at the mid point',
161 & myThid)
162 ELSEIF (i .EQ. 2) THEN
163 DO j = 1,nlevels(listId)
164 ztmp(j) = rF(NINT(levs(j,listId)) + 1)
165 ENDDO
166 CALL MNC_CW_ADD_VATTR_TEXT(dn(1),'description',
167 & 'Dimensional coordinate value at the upper point',
168 & myThid)
169 ELSEIF (i .EQ. 3) THEN
170 DO j = 1,nlevels(listId)
171 ztmp(j) = rF(NINT(levs(j,listId)))
172 ENDDO
173 CALL MNC_CW_ADD_VATTR_TEXT(dn(1),'description',
174 & 'Dimensional coordinate value at the lower point',
175 & myThid)
176 ENDIF
177 CALL MNC_CW_RS_W('D',diag_mnc_bn,0,0, dn(1), ztmp, myThid)
178 CALL MNC_CW_DEL_VNAME(dn(1), myThid)
179 CALL MNC_CW_DEL_GNAME(dn(1), myThid)
180 ENDDO
181 #endif /* DIAGST_MNC_NEEDSWORK */
182
183 DO ii = 1,CW_DIMS
184 d_cw_gname(1:NLEN) = dn_blnk(1:NLEN)
185 dn(ii)(1:NLEN) = dn_blnk(1:NLEN)
186 ENDDO
187
188 C Z is special since it varies
189 WRITE(dn(1),'(a,i6.6)') 'Zd', nlevels(listId)
190 IF ( (gdiag(ndId)(10:10) .EQ. 'R')
191 & .AND. (gdiag(ndId)(9:9) .EQ. 'M') ) THEN
192 WRITE(dn(1),'(a,i6.6)') 'Zmd', nlevels(listId)
193 ENDIF
194 IF ( (gdiag(ndId)(10:10) .EQ. 'R')
195 & .AND. (gdiag(ndId)(9:9) .EQ. 'L') ) THEN
196 WRITE(dn(1),'(a,i6.6)') 'Zld', nlevels(listId)
197 ENDIF
198 IF ( (gdiag(ndId)(10:10) .EQ. 'R')
199 & .AND. (gdiag(ndId)(9:9) .EQ. 'U') ) THEN
200 WRITE(dn(1),'(a,i6.6)') 'Zud', nlevels(listId)
201 ENDIF
202 dim(1) = Nr+Nrphys+1
203 ib(1) = 1
204 ie(1) = kdiag(ndId)
205
206 C "region" dimension
207 dim(2) = nRegions + 1
208 ib(2) = 1
209 dn(2)(1:6) = 'region'
210 ie(2) = nRegions + 1
211
212 C Time dimension
213 dn(3)(1:1) = 'T'
214 dim(3) = -1
215 ib(3) = 1
216 ie(3) = 1
217
218 C Note that the "d_cw_gname" variable is a hack that hides a
219 C subtlety within MNC. Basically, each MNC-wrapped file is
220 C caching its own concept of what each "grid name" (that is, a
221 C dimension group name) means. So one cannot re-use the same
222 C "grid" name for different collections of dimensions within a
223 C given file. By appending the "ndId" values to each name, we
224 C guarantee uniqueness within each MNC-produced file.
225
226 WRITE(d_cw_gname,'(a7,i6.6)') 'dst_cw_', ndId
227 CALL MNC_CW_ADD_GNAME(d_cw_gname, 3,
228 & dim, dn, ib, ie, myThid)
229
230 WRITE(dn(1),'(a3)') 'Zd0'
231 ie(1) = 1
232 WRITE(d_cw_gname0,'(a9,i6.6)') 'dst_cw_0_', ndId
233 CALL MNC_CW_ADD_GNAME(d_cw_gname0, 3,
234 & dim, dn, ib, ie, myThid)
235
236 DO ist = 0,nStats
237
238 DO i = 1,MAX_LEN_FNAM
239 tnam(i:i) = ' '
240 ENDDO
241 ilen = ILNBLNK(cdiag(ndId))
242 WRITE(tnam,'(a,a4,a3)')
243 & cdiag(ndId)(1:ilen),'_lv_',stat_typ(ist+1)
244
245 CALL MNC_CW_ADD_VNAME(tnam, d_cw_gname,
246 & 0,0, myThid)
247 CALL MNC_CW_ADD_VATTR_TEXT(tnam,'description',
248 & tdiag(ndId),myThid)
249 CALL MNC_CW_ADD_VATTR_TEXT(tnam,'units',
250 & udiag(ndId),myThid)
251
252 C Copy the data into a temporary with the necessary shape
253 DO j = 0,nRegions
254 DO k = 1,kdiag(ndId)
255 stmp(k,j+1) = statGlob(ist,k,j)
256 ENDDO
257 ENDDO
258
259 IF ((fflags(listId)(1:1) .EQ. ' ')
260 & .OR. (fflags(listId)(1:1) .EQ. 'R')) THEN
261
262 CALL MNC_CW_RL_W('R',diag_mnc_bn,0,0,
263 & tnam, stmp, myThid)
264
265 ELSEIF (fflags(listId)(1:1) .EQ. 'D') THEN
266
267 CALL MNC_CW_RL_W('D',diag_mnc_bn,0,0,
268 & tnam, stmp, myThid)
269
270 ENDIF
271
272 CALL MNC_CW_DEL_VNAME(tnam, myThid)
273
274 IF ( kdiag(ndId) .GT. 1 ) THEN
275
276 ilen = ILNBLNK(cdiag(ndId))
277 WRITE(tnam,'(a,a4,a3)')
278 & cdiag(ndId)(1:ilen),'_vi_',stat_typ(ist+1)
279
280 CALL MNC_CW_ADD_VNAME(tnam, d_cw_gname0,
281 & 0,0, myThid)
282 CALL MNC_CW_ADD_VATTR_TEXT(tnam,'description',
283 & tdiag(ndId),myThid)
284 CALL MNC_CW_ADD_VATTR_TEXT(tnam,'units',
285 & udiag(ndId),myThid)
286
287 C Copy the data into a temporary with the necessary shape
288 DO j = 0,nRegions
289 stmp(1,j+1) = statGlob(ist,0,j)
290 ENDDO
291
292 IF ((fflags(listId)(1:1) .EQ. ' ')
293 & .OR. (fflags(listId)(1:1) .EQ. 'R')) THEN
294
295 CALL MNC_CW_RL_W('R',diag_mnc_bn,0,0,
296 & tnam, stmp, myThid)
297
298 ELSEIF (fflags(listId)(1:1) .EQ. 'D') THEN
299
300 CALL MNC_CW_RL_W('D',diag_mnc_bn,0,0,
301 & tnam, stmp, myThid)
302
303 ENDIF
304
305 CALL MNC_CW_DEL_VNAME(tnam, myThid)
306
307 ENDIF
308
309 ENDDO
310
311 CALL MNC_CW_DEL_GNAME(d_cw_gname, myThid)
312 CALL MNC_CW_DEL_GNAME(d_cw_gname0, myThid)
313
314 ENDIF
315
316 _END_MASTER( myThid )
317
318 #endif /* ALLOW_MNC */
319
320 RETURN
321 END
322 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22