/[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.44 - (hide annotations) (download)
Thu Jan 7 01:09:40 2010 UTC (14 years, 4 months ago) by jmc
Branch: MAIN
Changes since 1.43: +39 -5 lines
time info in meta file: if time-averaged output, write the 2 edges of
 the time-averaging interval.

1 jmc 1.44 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_out.F,v 1.43 2010/01/03 00:42:45 jmc 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 jmc 1.30 INTEGER NrMax
30 jmc 1.33 PARAMETER( NrMax = numLevels )
31 jmc 1.1
32     C !INPUT PARAMETERS:
33 jmc 1.15 C listId :: Diagnostics list number being written
34 jmc 1.3 C myIter :: current iteration number
35 jmc 1.15 C myTime :: current time of simulation (s)
36 jmc 1.3 C myThid :: my Thread Id number
37 edhill 1.14 _RL myTime
38 jmc 1.15 INTEGER listId, myIter, myThid
39 jmc 1.1 CEOP
40    
41 jmc 1.40 C !FUNCTIONS:
42     INTEGER ILNBLNK
43     EXTERNAL ILNBLNK
44     #ifdef ALLOW_FIZHI
45     _RL getcon
46     EXTERNAL getcon
47     #endif
48    
49 jmc 1.3 C !LOCAL VARIABLES:
50 jmc 1.15 C i,j,k :: loop indices
51 jmc 1.29 C lm :: loop index (averageCycle)
52 jmc 1.15 C md :: field number in the list "listId".
53     C ndId :: diagnostics Id number (in available diagnostics list)
54     C mate :: counter mate Id number (in available diagnostics list)
55     C ip :: diagnostics pointer to storage array
56     C im :: counter-mate pointer to storage array
57 jmc 1.32 C
58     C-- COMMON /LOCAL_DIAGNOSTICS_OUT/ local common block (for multi-threaded)
59     C qtmp1 :: thread-shared temporary array (needs to be in common block):
60     C to write a diagnostic field to file, copy it first from (big)
61     C diagnostic storage qdiag into it.
62     COMMON /LOCAL_DIAGNOSTICS_OUT/ qtmp1
63     _RL qtmp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,NrMax,nSx,nSy)
64    
65 jmc 1.43 INTEGER i, j, k, lm
66 jmc 1.15 INTEGER bi, bj
67     INTEGER md, ndId, ip, im
68     INTEGER mate, mVec
69 jmc 1.35 CHARACTER*10 gcode
70 jmc 1.40 _RL undef
71 jmc 1.30 _RL tmpLev
72 jmc 1.3 INTEGER ilen
73 jmc 1.1
74 jmc 1.6 INTEGER ioUnit
75 jmc 1.11 CHARACTER*(MAX_LEN_FNAM) fn
76 jmc 1.1 CHARACTER*(MAX_LEN_MBUF) suff
77 jmc 1.3 CHARACTER*(MAX_LEN_MBUF) msgBuf
78 jmc 1.44 INTEGER prec, nRec, nTimRec
79     _RL timeRec(2)
80 jmc 1.29 #ifdef ALLOW_MDSIO
81 jmc 1.3 LOGICAL glf
82 jmc 1.29 #endif
83 jmc 1.1 #ifdef ALLOW_MNC
84 jmc 1.41 INTEGER ll, llMx, jj, jjMx
85 jmc 1.43 INTEGER ii, klev
86 jmc 1.1 CHARACTER*(MAX_LEN_FNAM) diag_mnc_bn
87 jmc 1.3 INTEGER CW_DIMS, NLEN
88     PARAMETER ( CW_DIMS = 10 )
89     PARAMETER ( NLEN = 80 )
90     INTEGER dim(CW_DIMS), ib(CW_DIMS), ie(CW_DIMS)
91     CHARACTER*(NLEN) dn(CW_DIMS)
92 edhill 1.7 CHARACTER*(NLEN) d_cw_name
93 jmc 1.3 CHARACTER*(NLEN) dn_blnk
94 jmc 1.20 #ifdef DIAG_MNC_COORD_NEEDSWORK
95     CHARACTER*(5) ctmp
96 jmc 1.30 _RS ztmp(NrMax)
97 jmc 1.20 #endif
98 mlosch 1.39 LOGICAL useMissingValue, useMisValForThisDiag
99 mlosch 1.37 REAL*8 misvalLoc
100     REAL*8 misval_r8(2)
101     REAL*4 misval_r4(2)
102     INTEGER misvalIntLoc, misval_int(2)
103 jmc 1.1 #endif /* ALLOW_MNC */
104    
105 jmc 1.3 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
106    
107 jmc 1.44 C--- set file properties
108 jmc 1.6 ioUnit= standardMessageUnit
109 jmc 1.40 undef = UNSET_RL
110     #ifdef ALLOW_FIZHI
111     c IF ( useFIZHI ) undef = getcon('UNDEF')
112 jmc 1.1 undef = getcon('UNDEF')
113 jmc 1.40 #endif
114 jmc 1.1 WRITE(suff,'(I10.10)') myIter
115 jmc 1.15 ilen = ILNBLNK(fnames(listId))
116     WRITE( fn, '(A,A,A)' ) fnames(listId)(1:ilen),'.',suff(1:10)
117 jmc 1.1
118 jmc 1.44 C-- Set time information:
119     IF ( freq(listId).LT.0. ) THEN
120     C- Snap-shot: store a unique time (which is consistent with State-Var timing)
121     nTimRec = 1
122     timeRec(1) = myTime
123     ELSE
124     C- Time-average: store the 2 edges of the time-averaging interval.
125     C this time is consitent with intermediate Var (i.e., non-state, e.g, flux,
126     C tendencies) timing. For State-Var, this is shifted by + halt time-step.
127     nTimRec = 2
128    
129     C- end of time-averaging interval:
130     timeRec(2) = myTime
131    
132     C- begining of time-averaging interval:
133     c timeRec(1) = myTime - freq(listId)
134     C a) find the time of the previous multiple of output freq:
135     timeRec(1) = myTime-deltaTClock*0.5 _d 0
136     timeRec(1) = (timeRec(1)-phase(listId))/freq(listId)
137     i = INT( timeRec(1) )
138     timeRec(1) = phase(listId) + freq(listId)*FLOAT(i)
139     c if ( listId.eq.2 ) write(0,*) 'f',i,timeRec(1)/deltaTClock
140     timeRec(1) = MAX( timeRec(1), startTime )
141    
142     C b) round off to nearest multiple of time-step:
143     timeRec(1) = (timeRec(1)-baseTime)/deltaTClock
144     i = NINT( timeRec(1) )
145     C if just half way, NINT will return the next time-step: correct this
146     tmpLev = FLOAT(i) - 0.5 _d 0
147     IF ( timeRec(1).EQ.tmpLev ) i = i - 1
148     timeRec(1) = baseTime + deltaTClock*FLOAT(i)
149     c if ( listId.eq.2 ) write(0,*) i,timeRec(1)/deltaTClock
150     ENDIF
151    
152 jmc 1.1 #ifdef ALLOW_MNC
153 jmc 1.41 C-- this is a trick to reverse the order of the loops on md (= field)
154     C and lm (= averagePeriod): binary output: lm loop inside md loop ;
155     C mnc ouput: md loop inside lm loop.
156 jmc 1.1 IF (useMNC .AND. diag_mnc) THEN
157 jmc 1.41 jjMx = averageCycle(listId)
158     llMx = 1
159     ELSE
160     jjMx = 1
161     llMx = averageCycle(listId)
162     ENDIF
163     DO jj=1,jjMx
164    
165     IF (useMNC .AND. diag_mnc) THEN
166 mlosch 1.39 C Handle missing value attribute (land points)
167 jmc 1.41 useMissingValue = .FALSE.
168 mlosch 1.38 #ifdef DIAGNOSTICS_MISSING_VALUE
169 jmc 1.41 useMissingValue = .TRUE.
170 mlosch 1.39 #endif /* DIAGNOSTICS_MISSING_VALUE */
171 jmc 1.41 IF ( misvalFlt(listId) .NE. UNSET_RL ) THEN
172     misvalLoc = misvalFlt(listId)
173     ELSE
174     misvalLoc = undef
175     ENDIF
176 mlosch 1.38 C Defaults to UNSET_I
177 jmc 1.41 misvalIntLoc = misvalInt(listId)
178     DO ii=1,2
179     C misval_r4(ii) = UNSET_FLOAT4
180     C misval_r8(ii) = UNSET_FLOAT8
181     misval_r4(ii) = misvalLoc
182     misval_r8(ii) = misvalLoc
183     misval_int(ii) = UNSET_I
184     ENDDO
185     DO i = 1,MAX_LEN_FNAM
186     diag_mnc_bn(i:i) = ' '
187     ENDDO
188     DO i = 1,NLEN
189     dn_blnk(i:i) = ' '
190     ENDDO
191     WRITE( diag_mnc_bn, '(A)' ) fnames(listId)(1:ilen)
192 jmc 1.1
193     C Update the record dimension by writing the iteration number
194 jmc 1.41 klev = myIter + jj - jjMx
195     tmpLev = myTime + deltaTClock*(jj -jjMx)
196     CALL MNC_CW_SET_UDIM(diag_mnc_bn, -1, myThid)
197     CALL MNC_CW_RL_W_S('D',diag_mnc_bn,0,0,'T',tmpLev,myThid)
198     CALL MNC_CW_SET_UDIM(diag_mnc_bn, 0, myThid)
199     CALL MNC_CW_I_W_S('I',diag_mnc_bn,0,0,'iter',klev,myThid)
200 edhill 1.21
201     C NOTE: at some point it would be a good idea to add a time_bounds
202     C variable that has dimension (2,T) and clearly denotes the
203     C beginning and ending times for each diagnostics period
204 jmc 1.1
205 jmc 1.41 dn(1)(1:NLEN) = dn_blnk(1:NLEN)
206     WRITE(dn(1),'(a,i6.6)') 'Zmd', nlevels(listId)
207     dim(1) = nlevels(listId)
208     ib(1) = 1
209     ie(1) = nlevels(listId)
210    
211     CALL MNC_CW_ADD_GNAME('diag_levels', 1,
212     & dim, dn, ib, ie, myThid)
213     CALL MNC_CW_ADD_VNAME('diag_levels', 'diag_levels',
214     & 0,0, myThid)
215     CALL MNC_CW_ADD_VATTR_TEXT('diag_levels','description',
216     & 'Idicies of vertical levels within the source arrays',
217     & myThid)
218 mlosch 1.39 C suppress the missing value attribute (iflag = 0)
219 jmc 1.41 IF (useMissingValue)
220 mlosch 1.39 & CALL MNC_CW_VATTR_MISSING('diag_levels', 0,
221 jmc 1.40 I misval_r8, misval_r4, misval_int,
222 mlosch 1.38 I myThid )
223 jmc 1.29
224 jmc 1.41 CALL MNC_CW_RL_W('D',diag_mnc_bn,0,0,
225     & 'diag_levels', levs(1,listId), myThid)
226 jmc 1.1
227 jmc 1.41 CALL MNC_CW_DEL_VNAME('diag_levels', myThid)
228     CALL MNC_CW_DEL_GNAME('diag_levels', myThid)
229 edhill 1.7
230 edhill 1.16 #ifdef DIAG_MNC_COORD_NEEDSWORK
231     C This part has been placed in an #ifdef because, as its currently
232     C written, it will only work with variables defined on a dynamics
233     C grid. As we start using diagnostics for physics grids, ice
234     C levels, land levels, etc. the different vertical coordinate
235     C dimensions will have to be taken into account.
236    
237 edhill 1.25 C 20051021 JMC & EH3 : We need to extend this so that a few
238     C variables each defined on different grids do not have the same
239     C vertical dimension names so we should be using a pattern such
240     C as: Z[uml]td000000 where the 't' is the type as specified by
241     C gdiag(10)
242    
243 edhill 1.7 C Now define: Zmdxxxxxx, Zudxxxxxx, Zldxxxxxx
244 jmc 1.41 ctmp(1:5) = 'mul '
245     DO i = 1,3
246     dn(1)(1:NLEN) = dn_blnk(1:NLEN)
247     WRITE(dn(1),'(3a,i6.6)') 'Z',ctmp(i:i),'d',nlevels(listId)
248     CALL MNC_CW_ADD_GNAME(dn(1), 1, dim, dn, ib, ie, myThid)
249     CALL MNC_CW_ADD_VNAME(dn(1), dn(1), 0,0, myThid)
250 edhill 1.10
251     C The following three ztmp() loops should eventually be modified
252     C to reflect the fractional nature of levs(j,l) -- they should
253     C do something like:
254 jmc 1.29 C ztmp(j) = rC(INT(FLOOR(levs(j,l))))
255     C + ( rC(INT(FLOOR(levs(j,l))))
256 edhill 1.10 C + rC(INT(CEIL(levs(j,l)))) )
257     C / ( levs(j,l) - FLOOR(levs(j,l)) )
258     C for averaged levels.
259 jmc 1.41 IF (i .EQ. 1) THEN
260     DO j = 1,nlevels(listId)
261     ztmp(j) = rC(NINT(levs(j,listId)))
262     ENDDO
263     CALL MNC_CW_ADD_VATTR_TEXT(dn(1),'description',
264     & 'Dimensional coordinate value at the mid point',
265     & myThid)
266     ELSEIF (i .EQ. 2) THEN
267     DO j = 1,nlevels(listId)
268     ztmp(j) = rF(NINT(levs(j,listId)) + 1)
269     ENDDO
270     CALL MNC_CW_ADD_VATTR_TEXT(dn(1),'description',
271     & 'Dimensional coordinate value at the upper point',
272     & myThid)
273     ELSEIF (i .EQ. 3) THEN
274     DO j = 1,nlevels(listId)
275     ztmp(j) = rF(NINT(levs(j,listId)))
276     ENDDO
277     CALL MNC_CW_ADD_VATTR_TEXT(dn(1),'description',
278     & 'Dimensional coordinate value at the lower point',
279     & myThid)
280     ENDIF
281 mlosch 1.39 C suppress the missing value attribute (iflag = 0)
282 jmc 1.41 IF (useMissingValue)
283     & CALL MNC_CW_VATTR_MISSING(dn(1), 0,
284     I misval_r8, misval_r4, misval_int,
285     I myThid )
286     CALL MNC_CW_RS_W('D',diag_mnc_bn,0,0, dn(1), ztmp, myThid)
287     CALL MNC_CW_DEL_VNAME(dn(1), myThid)
288     CALL MNC_CW_DEL_GNAME(dn(1), myThid)
289     ENDDO
290 edhill 1.16 #endif /* DIAG_MNC_COORD_NEEDSWORK */
291 edhill 1.7
292 jmc 1.41 ENDIF
293 jmc 1.1 #endif /* ALLOW_MNC */
294    
295 jmc 1.29 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
296    
297 jmc 1.41 DO md = 1,nfields(listId)
298 jmc 1.15 ndId = jdiag(md,listId)
299 jmc 1.35 gcode = gdiag(ndId)(1:10)
300 jmc 1.29 mate = 0
301     mVec = 0
302 jmc 1.35 IF ( gcode(5:5).EQ.'C' ) THEN
303 jmc 1.29 C- Check for Mate of a Counter Diagnostic
304 jmc 1.35 mate = hdiag(ndId)
305     ELSEIF ( gcode(1:1).EQ.'U' .OR. gcode(1:1).EQ.'V' ) THEN
306 jmc 1.29 C- Check for Mate of a Vector Diagnostic
307 jmc 1.36 mVec = hdiag(ndId)
308 jmc 1.29 ENDIF
309 jmc 1.35 IF ( idiag(md,listId).NE.0 .AND. gcode(5:5).NE.'D' ) THEN
310 jmc 1.3 C-- Start processing 1 Fld :
311 jmc 1.41 #ifdef ALLOW_MNC
312     DO ll=1,llMx
313     lm = jj+ll-1
314     #else
315 jmc 1.29 DO lm=1,averageCycle(listId)
316 jmc 1.41 #endif
317 jmc 1.3
318 jmc 1.29 ip = ABS(idiag(md,listId)) + kdiag(ndId)*(lm-1)
319 jmc 1.15 im = mdiag(md,listId)
320 jmc 1.29 IF (mate.GT.0) im = im + kdiag(mate)*(lm-1)
321     IF (mVec.GT.0) im = im + kdiag(mVec)*(lm-1)
322    
323 jmc 1.15 IF ( ndiag(ip,1,1).EQ.0 ) THEN
324 jmc 1.3 C- Empty diagnostics case :
325    
326     _BEGIN_MASTER( myThid )
327     WRITE(msgBuf,'(A,I10)')
328     & '- WARNING - from DIAGNOSTICS_OUT at iter=', myIter
329 jmc 1.15 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
330 jmc 1.3 & SQUEEZE_RIGHT, myThid)
331 jmc 1.35 WRITE(msgBuf,'(A,I6,3A,I4,2A)')
332 jmc 1.15 & '- WARNING - diag.#',ndId, ' : ',flds(md,listId),
333     & ' (#',md,' ) in outp.Stream: ',fnames(listId)
334     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
335 jmc 1.3 & SQUEEZE_RIGHT, myThid)
336 jmc 1.29 IF ( averageCycle(listId).GT.1 ) THEN
337 jmc 1.35 WRITE(msgBuf,'(A,2(I3,A))')
338 jmc 1.29 & '- WARNING - has not been filled (ndiag(lm=',lm,')=',
339     & ndiag(ip,1,1), ' )'
340     ELSE
341 jmc 1.35 WRITE(msgBuf,'(A,2(I3,A))')
342 jmc 1.29 & '- WARNING - has not been filled (ndiag=',
343     & ndiag(ip,1,1), ' )'
344     ENDIF
345 jmc 1.15 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
346 jmc 1.3 & SQUEEZE_RIGHT, myThid)
347     WRITE(msgBuf,'(A)')
348     & 'WARNING DIAGNOSTICS_OUT => write ZEROS instead'
349 jmc 1.15 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
350 jmc 1.3 & SQUEEZE_RIGHT, myThid)
351     _END_MASTER( myThid )
352     DO bj = myByLo(myThid), myByHi(myThid)
353     DO bi = myBxLo(myThid), myBxHi(myThid)
354 jmc 1.15 DO k = 1,nlevels(listId)
355 jmc 1.3 DO j = 1-OLy,sNy+OLy
356     DO i = 1-OLx,sNx+OLx
357     qtmp1(i,j,k,bi,bj) = 0. _d 0
358     ENDDO
359     ENDDO
360     ENDDO
361     ENDDO
362     ENDDO
363    
364     ELSE
365     C- diagnostics is not empty :
366    
367 jmc 1.29 IF ( debugLevel.GE.debLevA .AND. myThid.EQ.1 ) THEN
368 jmc 1.35 WRITE(ioUnit,'(A,I6,3A,I8,2A)')
369 jmc 1.15 & ' Computing Diagnostic # ', ndId, ' ', cdiag(ndId),
370     & ' Counter:',ndiag(ip,1,1),' Parms: ',gdiag(ndId)
371 jmc 1.29 IF ( mate.GT.0 ) THEN
372 jmc 1.35 WRITE(ioUnit,'(3A,I6,2A)')
373 jmc 1.15 & ' use Counter Mate for ', cdiag(ndId),
374     & ' Diagnostic # ',mate, ' ', cdiag(mate)
375 jmc 1.29 ELSEIF ( mVec.GT.0 ) THEN
376 jmc 1.15 IF ( im.GT.0 .AND. ndiag(MAX(1,im),1,1).GT.0 ) THEN
377 jmc 1.35 WRITE(ioUnit,'(3A,I6,3A)')
378 jmc 1.15 & ' Vector Mate for ', cdiag(ndId),
379     & ' Diagnostic # ',mVec, ' ', cdiag(mVec),
380     & ' exists '
381 jmc 1.3 ELSE
382 jmc 1.35 WRITE(ioUnit,'(3A,I6,3A)')
383 jmc 1.15 & ' Vector Mate for ', cdiag(ndId),
384     & ' Diagnostic # ',mVec, ' ', cdiag(mVec),
385     & ' not enabled'
386 jmc 1.3 ENDIF
387     ENDIF
388 jmc 1.6 ENDIF
389 jmc 1.3
390 jmc 1.30 IF ( fflags(listId)(2:2).EQ.'P' ) THEN
391     C- get all the levels (for vertical interpolation)
392     DO bj = myByLo(myThid), myByHi(myThid)
393     DO bi = myBxLo(myThid), myBxHi(myThid)
394     DO k = 1,kdiag(ndId)
395     tmpLev = k
396     CALL GETDIAG(
397     I tmpLev,undef,
398     O qtmp1(1-OLx,1-OLy,k,bi,bj),
399     I ndId,mate,ip,im,bi,bj,myThid)
400     ENDDO
401     ENDDO
402     ENDDO
403     ELSE
404     C- get only selected levels:
405     DO bj = myByLo(myThid), myByHi(myThid)
406     DO bi = myBxLo(myThid), myBxHi(myThid)
407     DO k = 1,nlevels(listId)
408     CALL GETDIAG(
409     I levs(k,listId),undef,
410     O qtmp1(1-OLx,1-OLy,k,bi,bj),
411     I ndId,mate,ip,im,bi,bj,myThid)
412     ENDDO
413     ENDDO
414 jmc 1.3 ENDDO
415 jmc 1.30 ENDIF
416 jmc 1.1
417 jmc 1.3 C- end of empty diag / not empty block
418     ENDIF
419 jmc 1.1
420 molod 1.17 C-----------------------------------------------------------------------
421 jmc 1.20 C Check to see if we need to interpolate before output
422 molod 1.17 C-----------------------------------------------------------------------
423 jmc 1.29 IF ( fflags(listId)(2:2).EQ.'P' ) THEN
424 jmc 1.20 C- Do vertical interpolation:
425 jmc 1.30 IF ( fluidIsAir ) THEN
426 jmc 1.29 C jmc: for now, this can only work in an atmospheric set-up (fluidIsAir);
427     CALL DIAGNOSTICS_INTERP_VERT(
428 jmc 1.30 I listId, md, ndId, ip, im, lm,
429 jmc 1.20 U qtmp1,
430 jmc 1.30 I undef, myTime, myIter, myThid )
431 jmc 1.29 ELSE
432     WRITE(msgBuf,'(2A)') 'DIAGNOSTICS_OUT: ',
433 jmc 1.30 & 'INTERP_VERT not allowed in this config'
434 jmc 1.29 CALL PRINT_ERROR( msgBuf , myThid )
435     STOP 'ABNORMAL END: S/R DIAGNOSTICS_OUT'
436     ENDIF
437     ENDIF
438 molod 1.17
439 jmc 1.31 C-- Ready to write field "md", element "lm" in averageCycle(listId)
440    
441     C- write to binary file, using MDSIO pkg:
442 jmc 1.34 IF ( diag_mdsio ) THEN
443 jmc 1.29 nRec = lm + (md-1)*averageCycle(listId)
444 jmc 1.30 C default precision for output files
445     prec = writeBinaryPrec
446     C fFlag(1)=R(or D): force it to be 32-bit(or 64) precision
447     IF ( fflags(listId)(1:1).EQ.'R' ) prec = precFloat32
448     IF ( fflags(listId)(1:1).EQ.'D' ) prec = precFloat64
449 jmc 1.34 C a hack not to write meta files now: pass -nRec < 0 to MDS_WRITE S/R
450     CALL WRITE_REC_LEV_RL(
451     I fn, prec,
452     I NrMax, 1, nlevels(listId),
453     I qtmp1, -nRec, myIter, myThid )
454 jmc 1.3 ENDIF
455 jmc 1.1
456     #ifdef ALLOW_MNC
457 jmc 1.3 IF (useMNC .AND. diag_mnc) THEN
458 jmc 1.1
459 jmc 1.3 _BEGIN_MASTER( myThid )
460 jmc 1.1
461 jmc 1.3 DO ii = 1,CW_DIMS
462 edhill 1.7 d_cw_name(1:NLEN) = dn_blnk(1:NLEN)
463 jmc 1.3 dn(ii)(1:NLEN) = dn_blnk(1:NLEN)
464     ENDDO
465    
466 edhill 1.7 C Note that the "d_cw_name" variable is a hack that hides a
467     C subtlety within MNC. Basically, each MNC-wrapped file is
468     C caching its own concept of what each "grid name" (that is, a
469     C dimension group name) means. So one cannot re-use the same
470     C "grid" name for different collections of dimensions within a
471 jmc 1.15 C given file. By appending the "ndId" values to each name, we
472 edhill 1.7 C guarantee uniqueness within each MNC-produced file.
473 jmc 1.15 WRITE(d_cw_name,'(a,i6.6)') 'd_cw_',ndId
474 edhill 1.7
475 edhill 1.5 C XY dimensions
476     dim(1) = sNx + 2*OLx
477     dim(2) = sNy + 2*OLy
478     ib(1) = OLx + 1
479     ib(2) = OLy + 1
480 jmc 1.29 IF (gdiag(ndId)(2:2) .EQ. 'M') THEN
481 edhill 1.5 dn(1)(1:2) = 'X'
482     ie(1) = OLx + sNx
483     dn(2)(1:2) = 'Y'
484     ie(2) = OLy + sNy
485 jmc 1.15 ELSEIF (gdiag(ndId)(2:2) .EQ. 'U') THEN
486 edhill 1.5 dn(1)(1:3) = 'Xp1'
487     ie(1) = OLx + sNx + 1
488     dn(2)(1:2) = 'Y'
489     ie(2) = OLy + sNy
490 jmc 1.15 ELSEIF (gdiag(ndId)(2:2) .EQ. 'V') THEN
491 edhill 1.5 dn(1)(1:2) = 'X'
492     ie(1) = OLx + sNx
493     dn(2)(1:3) = 'Yp1'
494     ie(2) = OLy + sNy + 1
495 jmc 1.15 ELSEIF (gdiag(ndId)(2:2) .EQ. 'Z') THEN
496 edhill 1.5 dn(1)(1:3) = 'Xp1'
497     ie(1) = OLx + sNx + 1
498     dn(2)(1:3) = 'Yp1'
499     ie(2) = OLy + sNy + 1
500     ENDIF
501 jmc 1.29
502 jmc 1.3 C Z is special since it varies
503 jmc 1.30 WRITE(dn(3),'(a,i6.6)') 'Zd', nlevels(listId)
504 jmc 1.15 IF ( (gdiag(ndId)(10:10) .EQ. 'R')
505     & .AND. (gdiag(ndId)(9:9) .EQ. 'M') ) THEN
506 jmc 1.30 WRITE(dn(3),'(a,i6.6)') 'Zmd', nlevels(listId)
507 edhill 1.7 ENDIF
508 jmc 1.15 IF ( (gdiag(ndId)(10:10) .EQ. 'R')
509     & .AND. (gdiag(ndId)(9:9) .EQ. 'L') ) THEN
510 jmc 1.30 WRITE(dn(3),'(a,i6.6)') 'Zld', nlevels(listId)
511 edhill 1.7 ENDIF
512 jmc 1.15 IF ( (gdiag(ndId)(10:10) .EQ. 'R')
513     & .AND. (gdiag(ndId)(9:9) .EQ. 'U') ) THEN
514 jmc 1.30 WRITE(dn(3),'(a,i6.6)') 'Zud', nlevels(listId)
515 edhill 1.7 ENDIF
516 jmc 1.30 dim(3) = NrMax
517 jmc 1.3 ib(3) = 1
518 jmc 1.30 ie(3) = nlevels(listId)
519 jmc 1.1
520 edhill 1.5 C Time dimension
521     dn(4)(1:1) = 'T'
522     dim(4) = -1
523     ib(4) = 1
524     ie(4) = 1
525    
526 jmc 1.29 CALL MNC_CW_ADD_GNAME(d_cw_name, 4,
527 jmc 1.1 & dim, dn, ib, ie, myThid)
528 jmc 1.29 CALL MNC_CW_ADD_VNAME(cdiag(ndId), d_cw_name,
529 jmc 1.1 & 4,5, myThid)
530 jmc 1.15 CALL MNC_CW_ADD_VATTR_TEXT(cdiag(ndId),'description',
531     & tdiag(ndId),myThid)
532     CALL MNC_CW_ADD_VATTR_TEXT(cdiag(ndId),'units',
533     & udiag(ndId),myThid)
534 edhill 1.28
535 mlosch 1.37 C Missing values only for scalar diagnostics at mass points (so far)
536 mlosch 1.39 useMisValForThisDiag = useMissingValue
537     & .AND.gdiag(ndId)(1:2).EQ.'SM'
538     IF ( useMisValForThisDiag ) THEN
539 mlosch 1.37 C assign missing values and set flag for adding the netCDF atttibute
540     CALL MNC_CW_VATTR_MISSING(cdiag(ndId), 2,
541 jmc 1.40 I misval_r8, misval_r4, misval_int,
542 mlosch 1.37 I myThid )
543     C and now use the missing values for masking out the land points
544     DO bj = myByLo(myThid), myByHi(myThid)
545     DO bi = myBxLo(myThid), myBxHi(myThid)
546     DO k = 1,nlevels(listId)
547     klev = NINT(levs(k,listId))
548     DO j = 1-OLy,sNy+OLy
549     DO i = 1-OLx,sNx+OLx
550 jmc 1.43 IF ( maskC(i,j,klev,bi,bj) .EQ. 0. )
551 mlosch 1.37 & qtmp1(i,j,k,bi,bj) = misvalLoc
552     ENDDO
553     ENDDO
554     ENDDO
555     ENDDO
556     ENDDO
557     ELSE
558     C suppress the missing value attribute (iflag = 0)
559 mlosch 1.38 C Note: We have to call the following subroutine for each mnc that has
560     C been created "on the fly" by mnc_cw_add_vname and will be deleted
561     C by mnc_cw_del_vname, because all of these variables use the same
562 jmc 1.40 C identifier so that mnc_cw_vfmv(indv) needs to be overwritten for
563 mlosch 1.38 C each of these variables
564 mlosch 1.37 CALL MNC_CW_VATTR_MISSING(cdiag(ndId), 0,
565 jmc 1.40 I misval_r8, misval_r4, misval_int,
566 mlosch 1.37 I myThid )
567     ENDIF
568 jmc 1.1
569 jmc 1.41 IF ( ((writeBinaryPrec .EQ. precFloat32)
570     & .AND. (fflags(listId)(1:1) .NE. 'D'))
571     & .OR. (fflags(listId)(1:1) .EQ. 'R') ) THEN
572 edhill 1.13 CALL MNC_CW_RL_W('R',diag_mnc_bn,0,0,
573 jmc 1.15 & cdiag(ndId), qtmp1, myThid)
574 jmc 1.29 ELSEIF ( (writeBinaryPrec .EQ. precFloat64)
575 edhill 1.22 & .OR. (fflags(listId)(1:1) .EQ. 'D') ) THEN
576 edhill 1.13 CALL MNC_CW_RL_W('D',diag_mnc_bn,0,0,
577 jmc 1.15 & cdiag(ndId), qtmp1, myThid)
578 edhill 1.13 ENDIF
579 jmc 1.29
580 jmc 1.15 CALL MNC_CW_DEL_VNAME(cdiag(ndId), myThid)
581 edhill 1.7 CALL MNC_CW_DEL_GNAME(d_cw_name, myThid)
582 jmc 1.1
583 jmc 1.3 _END_MASTER( myThid )
584 jmc 1.1
585 jmc 1.3 ENDIF
586 jmc 1.1 #endif /* ALLOW_MNC */
587    
588 jmc 1.41 C-- end loop on lm (or ll if ALLOW_MNC) counter
589 jmc 1.29 ENDDO
590 jmc 1.15 C-- end of Processing Fld # md
591 jmc 1.3 ENDIF
592 jmc 1.41 ENDDO
593    
594     #ifdef ALLOW_MNC
595     C-- end loop on jj counter
596 jmc 1.3 ENDDO
597 jmc 1.41 #endif
598 jmc 1.1
599 jmc 1.31 #ifdef ALLOW_MDSIO
600     IF (diag_mdsio) THEN
601     C- Note: temporary: since it's a pain to add more arguments to
602     C all MDSIO S/R, uses instead this specific S/R to write only
603     C meta files but with more informations in it.
604 jmc 1.34 glf = globalFiles
605 jmc 1.31 nRec = nfields(listId)*averageCycle(listId)
606     CALL MDS_WR_METAFILES(fn, prec, glf, .FALSE.,
607     & 0, 0, nlevels(listId), ' ',
608 jmc 1.44 & nfields(listId), flds(1,listId), nTimRec, timeRec,
609 jmc 1.31 & nRec, myIter, myThid)
610     ENDIF
611     #endif /* ALLOW_MDSIO */
612    
613 jmc 1.15 RETURN
614 jmc 1.3 END
615 jmc 1.15
616 jmc 1.1 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22