/[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.28 - (hide annotations) (download)
Tue Feb 7 15:52:02 2006 UTC (18 years, 3 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint58e_post, checkpoint58f_post, checkpoint58d_post, checkpoint58c_post, checkpoint58a_post, checkpoint58b_post
Changes since 1.27: +10 -3 lines
Per Baylor's observations, a zero missing_value attribute for the netCDF
  diagnostics output totally breaks ferret.  So I'm commenting it out
  until we come up with a more flexible/capable arrangement.

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

  ViewVC Help
Powered by ViewVC 1.1.22