/[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.48 - (hide annotations) (download)
Tue Mar 16 00:14:47 2010 UTC (14 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62y, checkpoint62x
Changes since 1.47: +2 -2 lines
avoid unbalanced quote (single or double) in commented line

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

  ViewVC Help
Powered by ViewVC 1.1.22