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

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

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


Revision 1.29 - (hide annotations) (download)
Mon Jun 5 18:17:23 2006 UTC (17 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, mitgcm_mapl_00, checkpoint58r_post, checkpoint58n_post, checkpoint58h_post, checkpoint58q_post, checkpoint58j_post, checkpoint58i_post, checkpoint58g_post, checkpoint58o_post, checkpoint58k_post, checkpoint58s_post, checkpoint58p_post, checkpoint58m_post
Changes since 1.28: +71 -44 lines
Implement periodic averaging diagnostics (e.g., mean seasonal cycle,
 mean diurnal cycle)

1 jmc 1.29 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_out.F,v 1.28 2006/02/07 15:52:02 edhill Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "DIAG_OPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7     CBOP 0
8     C !ROUTINE: DIAGNOSTICS_OUT
9    
10     C !INTERFACE:
11     SUBROUTINE DIAGNOSTICS_OUT(
12 jmc 1.15 I listId,
13 jmc 1.1 I myIter,
14 edhill 1.14 I myTime,
15 jmc 1.1 I myThid )
16    
17     C !DESCRIPTION:
18     C Write output for diagnostics fields.
19 jmc 1.15
20 jmc 1.1 C !USES:
21 jmc 1.3 IMPLICIT NONE
22 jmc 1.1 #include "SIZE.h"
23     #include "EEPARAMS.h"
24     #include "PARAMS.h"
25 edhill 1.7 #include "GRID.h"
26 jmc 1.3 #include "DIAGNOSTICS_SIZE.h"
27     #include "DIAGNOSTICS.h"
28 jmc 1.1
29     #ifdef ALLOW_FIZHI
30     #include "fizhi_SIZE.h"
31     #else
32 jmc 1.3 INTEGER Nrphys
33     PARAMETER (Nrphys=0)
34 jmc 1.1 #endif
35    
36    
37     C !INPUT PARAMETERS:
38 jmc 1.15 C listId :: Diagnostics list number being written
39 jmc 1.3 C myIter :: current iteration number
40 jmc 1.15 C myTime :: current time of simulation (s)
41 jmc 1.3 C myThid :: my Thread Id number
42 edhill 1.14 _RL myTime
43 jmc 1.15 INTEGER listId, myIter, myThid
44 jmc 1.1 CEOP
45    
46 jmc 1.3 C !LOCAL VARIABLES:
47 jmc 1.15 C i,j,k :: loop indices
48 jmc 1.29 C lm :: loop index (averageCycle)
49 jmc 1.15 C md :: field number in the list "listId".
50     C ndId :: diagnostics Id number (in available diagnostics list)
51     C mate :: counter mate Id number (in available diagnostics list)
52     C ip :: diagnostics pointer to storage array
53     C im :: counter-mate pointer to storage array
54 jmc 1.29 INTEGER i, j, k, lm
55 jmc 1.15 INTEGER bi, bj
56     INTEGER md, ndId, ip, im
57     INTEGER mate, mVec
58 jmc 1.3 CHARACTER*8 parms1
59 jmc 1.1 _RL qtmp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr+Nrphys,nSx,nSy)
60     _RL undef, getcon
61 jmc 1.3 EXTERNAL getcon
62     INTEGER ILNBLNK
63     EXTERNAL ILNBLNK
64     INTEGER ilen
65 jmc 1.20 INTEGER nlevsout
66 jmc 1.1
67 jmc 1.6 INTEGER ioUnit
68 jmc 1.11 CHARACTER*(MAX_LEN_FNAM) fn
69 jmc 1.1 CHARACTER*(MAX_LEN_MBUF) suff
70 jmc 1.3 CHARACTER*(MAX_LEN_MBUF) msgBuf
71 jmc 1.29 #ifdef ALLOW_MDSIO
72 jmc 1.3 LOGICAL glf
73 jmc 1.29 INTEGER nRec
74     #endif
75 jmc 1.1 #ifdef ALLOW_MNC
76 jmc 1.3 INTEGER ii
77 jmc 1.1 CHARACTER*(MAX_LEN_FNAM) diag_mnc_bn
78 jmc 1.3 INTEGER CW_DIMS, NLEN
79     PARAMETER ( CW_DIMS = 10 )
80     PARAMETER ( NLEN = 80 )
81     INTEGER dim(CW_DIMS), ib(CW_DIMS), ie(CW_DIMS)
82     CHARACTER*(NLEN) dn(CW_DIMS)
83 edhill 1.7 CHARACTER*(NLEN) d_cw_name
84 jmc 1.3 CHARACTER*(NLEN) dn_blnk
85 jmc 1.20 #ifdef DIAG_MNC_COORD_NEEDSWORK
86     CHARACTER*(5) ctmp
87 edhill 1.7 _RS ztmp(Nr+Nrphys)
88 jmc 1.20 #endif
89 jmc 1.1 #endif /* ALLOW_MNC */
90    
91 jmc 1.3 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
92    
93 jmc 1.6 ioUnit= standardMessageUnit
94 jmc 1.1 undef = getcon('UNDEF')
95     WRITE(suff,'(I10.10)') myIter
96 jmc 1.15 ilen = ILNBLNK(fnames(listId))
97     WRITE( fn, '(A,A,A)' ) fnames(listId)(1:ilen),'.',suff(1:10)
98 jmc 1.1
99     #ifdef ALLOW_MNC
100     IF (useMNC .AND. diag_mnc) THEN
101     DO i = 1,MAX_LEN_FNAM
102     diag_mnc_bn(i:i) = ' '
103     ENDDO
104     DO i = 1,NLEN
105     dn_blnk(i:i) = ' '
106     ENDDO
107 jmc 1.15 WRITE( diag_mnc_bn, '(A)' ) fnames(listId)(1:ilen)
108 jmc 1.1
109     C Update the record dimension by writing the iteration number
110     CALL MNC_CW_SET_UDIM(diag_mnc_bn, -1, myThid)
111 edhill 1.14 CALL MNC_CW_RL_W_S('D',diag_mnc_bn,0,0,'T',myTime,myThid)
112 jmc 1.1 CALL MNC_CW_SET_UDIM(diag_mnc_bn, 0, myThid)
113 edhill 1.26 CALL MNC_CW_I_W_S('I',diag_mnc_bn,0,0,'iter',myIter,myThid)
114 edhill 1.21
115     C NOTE: at some point it would be a good idea to add a time_bounds
116     C variable that has dimension (2,T) and clearly denotes the
117     C beginning and ending times for each diagnostics period
118 jmc 1.1
119     dn(1)(1:NLEN) = dn_blnk(1:NLEN)
120 jmc 1.15 WRITE(dn(1),'(a,i6.6)') 'Zmd', nlevels(listId)
121     dim(1) = nlevels(listId)
122 jmc 1.1 ib(1) = 1
123 jmc 1.15 ie(1) = nlevels(listId)
124 jmc 1.1
125 jmc 1.29 CALL MNC_CW_ADD_GNAME('diag_levels', 1,
126 jmc 1.1 & dim, dn, ib, ie, myThid)
127 jmc 1.29 CALL MNC_CW_ADD_VNAME('diag_levels', 'diag_levels',
128 jmc 1.1 & 0,0, myThid)
129 edhill 1.7 CALL MNC_CW_ADD_VATTR_TEXT('diag_levels','description',
130     & 'Idicies of vertical levels within the source arrays',
131 jmc 1.1 & myThid)
132 jmc 1.29
133 edhill 1.9 CALL MNC_CW_RL_W('D',diag_mnc_bn,0,0,
134 jmc 1.15 & 'diag_levels', levs(1,listId), myThid)
135 jmc 1.1
136 edhill 1.7 CALL MNC_CW_DEL_VNAME('diag_levels', myThid)
137 jmc 1.1 CALL MNC_CW_DEL_GNAME('diag_levels', myThid)
138 edhill 1.7
139 edhill 1.16 #ifdef DIAG_MNC_COORD_NEEDSWORK
140     C This part has been placed in an #ifdef because, as its currently
141     C written, it will only work with variables defined on a dynamics
142     C grid. As we start using diagnostics for physics grids, ice
143     C levels, land levels, etc. the different vertical coordinate
144     C dimensions will have to be taken into account.
145    
146 edhill 1.25 C 20051021 JMC & EH3 : We need to extend this so that a few
147     C variables each defined on different grids do not have the same
148     C vertical dimension names so we should be using a pattern such
149     C as: Z[uml]td000000 where the 't' is the type as specified by
150     C gdiag(10)
151    
152 edhill 1.7 C Now define: Zmdxxxxxx, Zudxxxxxx, Zldxxxxxx
153     ctmp(1:5) = 'mul '
154     DO i = 1,3
155     dn(1)(1:NLEN) = dn_blnk(1:NLEN)
156 jmc 1.15 WRITE(dn(1),'(3a,i6.6)') 'Z',ctmp(i:i),'d',nlevels(listId)
157 edhill 1.7 CALL MNC_CW_ADD_GNAME(dn(1), 1, dim, dn, ib, ie, myThid)
158     CALL MNC_CW_ADD_VNAME(dn(1), dn(1), 0,0, myThid)
159 edhill 1.10
160     C The following three ztmp() loops should eventually be modified
161     C to reflect the fractional nature of levs(j,l) -- they should
162     C do something like:
163 jmc 1.29 C ztmp(j) = rC(INT(FLOOR(levs(j,l))))
164     C + ( rC(INT(FLOOR(levs(j,l))))
165 edhill 1.10 C + rC(INT(CEIL(levs(j,l)))) )
166     C / ( levs(j,l) - FLOOR(levs(j,l)) )
167     C for averaged levels.
168     IF (i .EQ. 1) THEN
169 jmc 1.15 DO j = 1,nlevels(listId)
170     ztmp(j) = rC(NINT(levs(j,listId)))
171 edhill 1.10 ENDDO
172     CALL MNC_CW_ADD_VATTR_TEXT(dn(1),'description',
173     & 'Dimensional coordinate value at the mid point',
174     & myThid)
175     ELSEIF (i .EQ. 2) THEN
176 jmc 1.15 DO j = 1,nlevels(listId)
177     ztmp(j) = rF(NINT(levs(j,listId)) + 1)
178 edhill 1.10 ENDDO
179     CALL MNC_CW_ADD_VATTR_TEXT(dn(1),'description',
180     & 'Dimensional coordinate value at the upper point',
181     & myThid)
182     ELSEIF (i .EQ. 3) THEN
183 jmc 1.15 DO j = 1,nlevels(listId)
184     ztmp(j) = rF(NINT(levs(j,listId)))
185 edhill 1.10 ENDDO
186     CALL MNC_CW_ADD_VATTR_TEXT(dn(1),'description',
187     & 'Dimensional coordinate value at the lower point',
188     & myThid)
189     ENDIF
190 edhill 1.7 CALL MNC_CW_RS_W('D',diag_mnc_bn,0,0, dn(1), ztmp, myThid)
191     CALL MNC_CW_DEL_VNAME(dn(1), myThid)
192     CALL MNC_CW_DEL_GNAME(dn(1), myThid)
193     ENDDO
194 edhill 1.16 #endif /* DIAG_MNC_COORD_NEEDSWORK */
195 edhill 1.7
196 jmc 1.1 ENDIF
197     #endif /* ALLOW_MNC */
198    
199 jmc 1.29 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
200    
201 jmc 1.15 DO md = 1,nfields(listId)
202     ndId = jdiag(md,listId)
203     parms1 = gdiag(ndId)(1:8)
204 jmc 1.29 mate = 0
205     mVec = 0
206     IF ( parms1(5:5).EQ.'C' ) THEN
207     C- Check for Mate of a Counter Diagnostic
208     READ(parms1,'(5X,I3)') mate
209     ELSEIF ( parms1(1:1).EQ.'U' .OR. parms1(1:1).EQ.'V' ) THEN
210     C- Check for Mate of a Vector Diagnostic
211     READ(parms1,'(5X,I3)') mVec
212     ENDIF
213 jmc 1.15 IF ( idiag(md,listId).NE.0 .AND. parms1(5:5).NE.'D' ) THEN
214 jmc 1.3 C-- Start processing 1 Fld :
215 jmc 1.29 DO lm=1,averageCycle(listId)
216 jmc 1.3
217 jmc 1.29 ip = ABS(idiag(md,listId)) + kdiag(ndId)*(lm-1)
218 jmc 1.15 im = mdiag(md,listId)
219 jmc 1.29 IF (mate.GT.0) im = im + kdiag(mate)*(lm-1)
220     IF (mVec.GT.0) im = im + kdiag(mVec)*(lm-1)
221    
222 jmc 1.15 IF ( ndiag(ip,1,1).EQ.0 ) THEN
223 jmc 1.3 C- Empty diagnostics case :
224    
225     _BEGIN_MASTER( myThid )
226     WRITE(msgBuf,'(A,I10)')
227     & '- WARNING - from DIAGNOSTICS_OUT at iter=', myIter
228 jmc 1.15 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
229 jmc 1.3 & SQUEEZE_RIGHT, myThid)
230     WRITE(msgBuf,'(A,I4,3A,I3,2A)')
231 jmc 1.15 & '- WARNING - diag.#',ndId, ' : ',flds(md,listId),
232     & ' (#',md,' ) in outp.Stream: ',fnames(listId)
233     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
234 jmc 1.3 & SQUEEZE_RIGHT, myThid)
235 jmc 1.29 IF ( averageCycle(listId).GT.1 ) THEN
236     WRITE(msgBuf,'(A,2(I2,A))')
237     & '- WARNING - has not been filled (ndiag(lm=',lm,')=',
238     & ndiag(ip,1,1), ' )'
239     ELSE
240     WRITE(msgBuf,'(A,2(I2,A))')
241     & '- WARNING - has not been filled (ndiag=',
242     & ndiag(ip,1,1), ' )'
243     ENDIF
244 jmc 1.15 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
245 jmc 1.3 & SQUEEZE_RIGHT, myThid)
246     WRITE(msgBuf,'(A)')
247     & 'WARNING DIAGNOSTICS_OUT => write ZEROS instead'
248 jmc 1.15 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
249 jmc 1.3 & SQUEEZE_RIGHT, myThid)
250     _END_MASTER( myThid )
251     DO bj = myByLo(myThid), myByHi(myThid)
252     DO bi = myBxLo(myThid), myBxHi(myThid)
253 jmc 1.15 DO k = 1,nlevels(listId)
254 jmc 1.3 DO j = 1-OLy,sNy+OLy
255     DO i = 1-OLx,sNx+OLx
256     qtmp1(i,j,k,bi,bj) = 0. _d 0
257     ENDDO
258     ENDDO
259     ENDDO
260     ENDDO
261     ENDDO
262    
263     ELSE
264     C- diagnostics is not empty :
265    
266 jmc 1.29 IF ( debugLevel.GE.debLevA .AND. myThid.EQ.1 ) THEN
267     WRITE(ioUnit,'(A,I3,3A,I8,2A)')
268 jmc 1.15 & ' Computing Diagnostic # ', ndId, ' ', cdiag(ndId),
269     & ' Counter:',ndiag(ip,1,1),' Parms: ',gdiag(ndId)
270 jmc 1.29 IF ( mate.GT.0 ) THEN
271     WRITE(ioUnit,'(3A,I3,2A)')
272 jmc 1.15 & ' use Counter Mate for ', cdiag(ndId),
273     & ' Diagnostic # ',mate, ' ', cdiag(mate)
274 jmc 1.29 ELSEIF ( mVec.GT.0 ) THEN
275 jmc 1.15 IF ( im.GT.0 .AND. ndiag(MAX(1,im),1,1).GT.0 ) THEN
276 jmc 1.29 WRITE(ioUnit,'(3A,I3,3A)')
277 jmc 1.15 & ' Vector Mate for ', cdiag(ndId),
278     & ' Diagnostic # ',mVec, ' ', cdiag(mVec),
279     & ' exists '
280 jmc 1.3 ELSE
281 jmc 1.29 WRITE(ioUnit,'(3A,I3,3A)')
282 jmc 1.15 & ' Vector Mate for ', cdiag(ndId),
283     & ' Diagnostic # ',mVec, ' ', cdiag(mVec),
284     & ' not enabled'
285 jmc 1.3 ENDIF
286     ENDIF
287 jmc 1.6 ENDIF
288 jmc 1.3
289 jmc 1.6 DO bj = myByLo(myThid), myByHi(myThid)
290     DO bi = myBxLo(myThid), myBxHi(myThid)
291 jmc 1.15 DO k = 1,nlevels(listId)
292 jmc 1.6 CALL GETDIAG(
293 jmc 1.15 I levs(k,listId),undef,
294 jmc 1.6 O qtmp1(1-OLx,1-OLy,k,bi,bj),
295 jmc 1.15 I ndId,mate,ip,im,bi,bj,myThid)
296 jmc 1.3 ENDDO
297 jmc 1.6 ENDDO
298     ENDDO
299 jmc 1.1
300 jmc 1.3 C- end of empty diag / not empty block
301     ENDIF
302 jmc 1.1
303 molod 1.17 nlevsout = nlevels(listId)
304    
305     C-----------------------------------------------------------------------
306 jmc 1.20 C Check to see if we need to interpolate before output
307 molod 1.17 C-----------------------------------------------------------------------
308 jmc 1.29 IF ( fflags(listId)(2:2).EQ.'P' ) THEN
309 jmc 1.20 C- Do vertical interpolation:
310 jmc 1.29 c IF ( fluidIsAir ) THEN
311     C jmc: for now, this can only work in an atmospheric set-up (fluidIsAir);
312     C find some problems with 5-levels AIM => use it only with FIZHI
313     IF ( useFIZHI ) THEN
314     CALL DIAGNOSTICS_INTERP_VERT(
315 jmc 1.20 I listId, md, ndId, ip, im,
316     U nlevsout,
317     U qtmp1,
318     I undef,
319     I myTime, myIter, myThid )
320 jmc 1.29 ELSE
321     WRITE(msgBuf,'(2A)') 'DIAGNOSTICS_OUT: ',
322     & 'INTERP_VERT not safe in this config'
323     CALL PRINT_ERROR( msgBuf , myThid )
324     WRITE(msgBuf,'(2A,I3,2A)') 'DIAGNOSTICS_OUT: ',
325     & ' for list l=', listId, ', filename: ', fnames(listId)
326     CALL PRINT_ERROR( msgBuf , myThid )
327     STOP 'ABNORMAL END: S/R DIAGNOSTICS_OUT'
328     ENDIF
329     ENDIF
330 molod 1.17
331 jmc 1.1 #ifdef ALLOW_MDSIO
332 jmc 1.3 C Prepare for mdsio optionality
333     IF (diag_mdsio) THEN
334 jmc 1.29 glf = globalFiles
335     nRec = lm + (md-1)*averageCycle(listId)
336 jmc 1.23 IF (fflags(listId)(1:1) .EQ. 'R') THEN
337 edhill 1.13 C Force it to be 32-bit precision
338 jmc 1.23 CALL MDSWRITEFIELD_NEW(fn,precFloat32,glf,.FALSE.,
339 jmc 1.29 & 'RL',Nr+Nrphys,nlevsout,qtmp1,nRec,myIter,myThid)
340 jmc 1.15 ELSEIF (fflags(listId)(1:1) .EQ. 'D') THEN
341 edhill 1.13 C Force it to be 64-bit precision
342 jmc 1.23 CALL MDSWRITEFIELD_NEW(fn,precFloat64,glf,.FALSE.,
343 jmc 1.29 & 'RL',Nr+Nrphys,nlevsout,qtmp1,nRec,myIter,myThid)
344 jmc 1.23 ELSE
345     C This is the old default behavior
346     CALL MDSWRITEFIELD_NEW(fn,writeBinaryPrec,glf,.FALSE.,
347 jmc 1.29 & 'RL',Nr+Nrphys,nlevsout,qtmp1,nRec,myIter,myThid)
348 edhill 1.13 ENDIF
349 jmc 1.3 ENDIF
350 jmc 1.1 #endif /* ALLOW_MDSIO */
351    
352     #ifdef ALLOW_MNC
353 jmc 1.3 IF (useMNC .AND. diag_mnc) THEN
354 jmc 1.1
355 jmc 1.3 _BEGIN_MASTER( myThid )
356 jmc 1.1
357 jmc 1.3 DO ii = 1,CW_DIMS
358 edhill 1.7 d_cw_name(1:NLEN) = dn_blnk(1:NLEN)
359 jmc 1.3 dn(ii)(1:NLEN) = dn_blnk(1:NLEN)
360     ENDDO
361    
362 edhill 1.7 C Note that the "d_cw_name" variable is a hack that hides a
363     C subtlety within MNC. Basically, each MNC-wrapped file is
364     C caching its own concept of what each "grid name" (that is, a
365     C dimension group name) means. So one cannot re-use the same
366     C "grid" name for different collections of dimensions within a
367 jmc 1.15 C given file. By appending the "ndId" values to each name, we
368 edhill 1.7 C guarantee uniqueness within each MNC-produced file.
369 jmc 1.15 WRITE(d_cw_name,'(a,i6.6)') 'd_cw_',ndId
370 edhill 1.7
371 edhill 1.5 C XY dimensions
372     dim(1) = sNx + 2*OLx
373     dim(2) = sNy + 2*OLy
374     ib(1) = OLx + 1
375     ib(2) = OLy + 1
376 jmc 1.29 IF (gdiag(ndId)(2:2) .EQ. 'M') THEN
377 edhill 1.5 dn(1)(1:2) = 'X'
378     ie(1) = OLx + sNx
379     dn(2)(1:2) = 'Y'
380     ie(2) = OLy + sNy
381 jmc 1.15 ELSEIF (gdiag(ndId)(2:2) .EQ. 'U') THEN
382 edhill 1.5 dn(1)(1:3) = 'Xp1'
383     ie(1) = OLx + sNx + 1
384     dn(2)(1:2) = 'Y'
385     ie(2) = OLy + sNy
386 jmc 1.15 ELSEIF (gdiag(ndId)(2:2) .EQ. 'V') THEN
387 edhill 1.5 dn(1)(1:2) = 'X'
388     ie(1) = OLx + sNx
389     dn(2)(1:3) = 'Yp1'
390     ie(2) = OLy + sNy + 1
391 jmc 1.15 ELSEIF (gdiag(ndId)(2:2) .EQ. 'Z') THEN
392 edhill 1.5 dn(1)(1:3) = 'Xp1'
393     ie(1) = OLx + sNx + 1
394     dn(2)(1:3) = 'Yp1'
395     ie(2) = OLy + sNy + 1
396     ENDIF
397 jmc 1.29
398 jmc 1.3 C Z is special since it varies
399 molod 1.24 WRITE(dn(3),'(a,i6.6)') 'Zd', nlevsout
400 jmc 1.15 IF ( (gdiag(ndId)(10:10) .EQ. 'R')
401     & .AND. (gdiag(ndId)(9:9) .EQ. 'M') ) THEN
402 molod 1.24 WRITE(dn(3),'(a,i6.6)') 'Zmd', nlevsout
403 edhill 1.7 ENDIF
404 jmc 1.15 IF ( (gdiag(ndId)(10:10) .EQ. 'R')
405     & .AND. (gdiag(ndId)(9:9) .EQ. 'L') ) THEN
406 molod 1.24 WRITE(dn(3),'(a,i6.6)') 'Zld', nlevsout
407 edhill 1.7 ENDIF
408 jmc 1.15 IF ( (gdiag(ndId)(10:10) .EQ. 'R')
409     & .AND. (gdiag(ndId)(9:9) .EQ. 'U') ) THEN
410 molod 1.24 WRITE(dn(3),'(a,i6.6)') 'Zud', nlevsout
411 edhill 1.7 ENDIF
412 jmc 1.3 dim(3) = Nr+Nrphys
413     ib(3) = 1
414 molod 1.24 ie(3) = nlevsout
415 jmc 1.1
416 edhill 1.5 C Time dimension
417     dn(4)(1:1) = 'T'
418     dim(4) = -1
419     ib(4) = 1
420     ie(4) = 1
421    
422 jmc 1.29 CALL MNC_CW_ADD_GNAME(d_cw_name, 4,
423 jmc 1.1 & dim, dn, ib, ie, myThid)
424 jmc 1.29 CALL MNC_CW_ADD_VNAME(cdiag(ndId), d_cw_name,
425 jmc 1.1 & 4,5, myThid)
426 jmc 1.15 CALL MNC_CW_ADD_VATTR_TEXT(cdiag(ndId),'description',
427     & tdiag(ndId),myThid)
428     CALL MNC_CW_ADD_VATTR_TEXT(cdiag(ndId),'units',
429     & udiag(ndId),myThid)
430 edhill 1.28
431     C Per the observations of Baylor, this has been commented out
432     C until we have code that can write missing_value attributes
433     C in a way thats compatible with most of the more popular
434     C netCDF tools including ferret. Using all-zeros completely
435     C breaks ferret.
436    
437     C CALL MNC_CW_ADD_VATTR_DBL(cdiag(ndId),'missing_value',
438     C & 0.0 _d 0,myThid)
439 jmc 1.1
440 edhill 1.22 IF ( ( (writeBinaryPrec .EQ. precFloat32)
441     & .AND. (fflags(listId)(1:1) .NE. 'D')
442     & .AND. (fflags(listId)(1:1) .NE. 'R') )
443 jmc 1.15 & .OR. (fflags(listId)(1:1) .EQ. 'R')) THEN
444 edhill 1.13 CALL MNC_CW_RL_W('R',diag_mnc_bn,0,0,
445 jmc 1.15 & cdiag(ndId), qtmp1, myThid)
446 jmc 1.29 ELSEIF ( (writeBinaryPrec .EQ. precFloat64)
447 edhill 1.22 & .OR. (fflags(listId)(1:1) .EQ. 'D') ) THEN
448 edhill 1.13 CALL MNC_CW_RL_W('D',diag_mnc_bn,0,0,
449 jmc 1.15 & cdiag(ndId), qtmp1, myThid)
450 edhill 1.13 ENDIF
451 jmc 1.29
452 jmc 1.15 CALL MNC_CW_DEL_VNAME(cdiag(ndId), myThid)
453 edhill 1.7 CALL MNC_CW_DEL_GNAME(d_cw_name, myThid)
454 jmc 1.1
455 jmc 1.3 _END_MASTER( myThid )
456 jmc 1.1
457 jmc 1.3 ENDIF
458 jmc 1.1 #endif /* ALLOW_MNC */
459    
460 jmc 1.29 ENDDO
461 jmc 1.15 C-- end of Processing Fld # md
462 jmc 1.3 ENDIF
463     ENDDO
464 jmc 1.1
465 jmc 1.15 RETURN
466 jmc 1.3 END
467 jmc 1.15
468 jmc 1.1 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22