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

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

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


Revision 1.4 - (show annotations) (download)
Mon Jun 27 22:27:23 2011 UTC (12 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64a, checkpoint64c, checkpoint64b, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint63
Changes since 1.3: +8 -18 lines
use run-time parameter "useMissingValue" to fill land-point (i.e., where mask=0)
 with MissingValue (MNC output file only).
This replaces CPP-option DIAGNOSTICS_MISSING_VALUE.

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_mnc_out.F,v 1.3 2011/06/23 15:29:01 jmc Exp $
2 C $Name: $
3
4 #include "DIAG_OPTIONS.h"
5 #undef DIAG_MNC_COORD_NEEDSWORK
6
7 C-- File diagnostics_mnc_out.F: Routines to write MNC diagnostics output
8 C-- Contents:
9 C-- o DIAGNOSTICS_MNC_SET
10 C-- o DIAGNOSTICS_MNC_OUT
11
12 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
13 CBOP 0
14 C !ROUTINE: DIAGNOSTICS_MNC_SET
15
16 C !INTERFACE:
17 SUBROUTINE DIAGNOSTICS_MNC_SET(
18 I nLevOutp, listId, lm,
19 O diag_mnc_bn,
20 I misValLoc, myTime, myIter, myThid )
21
22 C !DESCRIPTION:
23 C Set MNC file for writing diagnostics fields.
24
25 C !USES:
26 IMPLICIT NONE
27 #include "SIZE.h"
28 #include "EEPARAMS.h"
29 #include "PARAMS.h"
30 #include "GRID.h"
31 #include "DIAGNOSTICS_SIZE.h"
32 #include "DIAGNOSTICS.h"
33
34
35 C !INPUT/OUTPUT PARAMETERS:
36 C nLevOutp :: number of levels to write in output file
37 C listId :: Diagnostics list number being written
38 C lm :: loop index (averageCycle)
39 C diag_mnc_bn :: NetCDF output file name
40 C misValLoc :: local Missing Value
41 C myTime :: current time of simulation (s)
42 C myIter :: current iteration number
43 C myThid :: my Thread Id number
44 INTEGER nLevOutp
45 INTEGER listId, lm
46 CHARACTER*(MAX_LEN_FNAM) diag_mnc_bn
47 _RL misValLoc
48 _RL myTime
49 INTEGER myIter, myThid
50 CEOP
51
52 #ifdef ALLOW_MNC
53 C !FUNCTIONS:
54 INTEGER ILNBLNK
55 EXTERNAL ILNBLNK
56
57 C !LOCAL VARIABLES:
58 _RL tmpLev
59 INTEGER iLen
60
61 c CHARACTER*(MAX_LEN_MBUF) msgBuf
62 INTEGER ii, klev
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 c CHARACTER*(NLEN) d_cw_name
69 c CHARACTER*(NLEN) dn_blnk
70 #ifdef DIAG_MNC_COORD_NEEDSWORK
71 INTEGER NrMax
72 PARAMETER( NrMax = numLevels )
73 INTEGER i, j
74 CHARACTER*(5) ctmp
75 _RS ztmp(NrMax)
76 #endif
77 INTEGER misvalIntLoc
78 REAL*8 misval_r8(2)
79 REAL*4 misval_r4(2)
80 INTEGER misval_int(2)
81
82 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
83 c IF (useMNC .AND. diag_mnc) THEN
84
85 C Handle missing value attribute (land points)
86 C Defaults to UNSET_I
87 misvalIntLoc = misvalInt(listId)
88 DO ii=1,2
89 misval_r4(ii) = misValLoc
90 misval_r8(ii) = misValLoc
91 misval_int(ii) = UNSET_I
92 ENDDO
93 c DO i = 1,MAX_LEN_FNAM
94 c diag_mnc_bn(i:i) = ' '
95 c ENDDO
96 c DO i = 1,NLEN
97 c dn_blnk(i:i) = ' '
98 c ENDDO
99 iLen = ILNBLNK(fnames(listId))
100 WRITE( diag_mnc_bn, '(A)' ) fnames(listId)(1:iLen)
101
102 C Update the record dimension by writing the iteration number
103 klev = myIter + lm - averageCycle(listId)
104 tmpLev = myTime + deltaTClock*( lm - averageCycle(listId) )
105 CALL MNC_CW_SET_UDIM(diag_mnc_bn, -1, myThid)
106 CALL MNC_CW_RL_W_S('D',diag_mnc_bn,0,0,'T',tmpLev,myThid)
107 CALL MNC_CW_SET_UDIM(diag_mnc_bn, 0, myThid)
108 CALL MNC_CW_I_W_S('I',diag_mnc_bn,0,0,'iter',klev,myThid)
109
110 C NOTE: at some point it would be a good idea to add a time_bounds
111 C variable that has dimension (2,T) and clearly denotes the
112 C beginning and ending times for each diagnostics period
113
114 c dn(1)(1:NLEN) = dn_blnk(1:NLEN)
115 WRITE(dn(1),'(a,i6.6)') 'Zmd', nLevOutp
116 dim(1) = nLevOutp
117 ib(1) = 1
118 ie(1) = nLevOutp
119
120 CALL MNC_CW_ADD_GNAME('diag_levels', 1,
121 & dim, dn, ib, ie, myThid)
122 CALL MNC_CW_ADD_VNAME('diag_levels', 'diag_levels',
123 & 0,0, myThid)
124 CALL MNC_CW_ADD_VATTR_TEXT('diag_levels','description',
125 & 'Idicies of vertical levels within the source arrays',
126 & myThid)
127 C suppress the missing value attribute (iflag = 0)
128 CALL MNC_CW_VATTR_MISSING('diag_levels', 0,
129 I misval_r8, misval_r4, misval_int, myThid )
130
131 CALL MNC_CW_RL_W('D',diag_mnc_bn,0,0,
132 & 'diag_levels', levs(1,listId), myThid)
133
134 CALL MNC_CW_DEL_VNAME('diag_levels', myThid)
135 CALL MNC_CW_DEL_GNAME('diag_levels', myThid)
136
137 #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 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 C Now define: Zmdxxxxxx, Zudxxxxxx, Zldxxxxxx
151 ctmp(1:5) = 'mul '
152 DO i = 1,3
153 c dn(1)(1:NLEN) = dn_blnk(1:NLEN)
154 WRITE(dn(1),'(3a,i6.6)') 'Z',ctmp(i:i),'d',nlevels(listId)
155 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
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 DO j = 1,nlevels(listId)
168 ztmp(j) = rC(NINT(levs(j,listId)))
169 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 DO j = 1,nlevels(listId)
175 ztmp(j) = rF(NINT(levs(j,listId)) + 1)
176 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 DO j = 1,nlevels(listId)
182 ztmp(j) = rF(NINT(levs(j,listId)))
183 ENDDO
184 CALL MNC_CW_ADD_VATTR_TEXT(dn(1),'description',
185 & 'Dimensional coordinate value at the lower point',
186 & myThid)
187 ENDIF
188 C suppress the missing value attribute (iflag = 0)
189 IF (useMissingValue)
190 & CALL MNC_CW_VATTR_MISSING(dn(1), 0,
191 I misval_r8, misval_r4, misval_int, myThid )
192 CALL MNC_CW_RS_W('D',diag_mnc_bn,0,0, dn(1), ztmp, myThid)
193 CALL MNC_CW_DEL_VNAME(dn(1), myThid)
194 CALL MNC_CW_DEL_GNAME(dn(1), myThid)
195 ENDDO
196 #endif /* DIAG_MNC_COORD_NEEDSWORK */
197
198 c ENDIF
199 #endif /* ALLOW_MNC */
200
201 RETURN
202 END
203
204 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
205 CBOP 0
206 C !ROUTINE: DIAGNOSTICS_MNC_OUT
207
208 C !INTERFACE:
209 SUBROUTINE DIAGNOSTICS_MNC_OUT(
210 I NrMax, nLevOutp, listId, ndId, mate,
211 I diag_mnc_bn, qtmp,
212 I misValLoc, myTime, myIter, myThid )
213
214 C !DESCRIPTION:
215 C write diagnostics fields to MNC file.
216
217 C !USES:
218 IMPLICIT NONE
219 #include "SIZE.h"
220 #include "EEPARAMS.h"
221 #include "PARAMS.h"
222 #include "GRID.h"
223 #include "DIAGNOSTICS_SIZE.h"
224 #include "DIAGNOSTICS.h"
225
226 C !INPUT PARAMETERS:
227 C NrMax :: 3rd dimension of output-field array to write
228 C nLevOutp :: number of levels to write in output file
229 C listId :: Diagnostics list number being written
230 C ndId :: diagnostics Id number (in available diagnostics list)
231 C mate :: counter diagnostic number if any ; 0 otherwise
232 C diag_mnc_bn :: NetCDF output file name
233 C qtmp :: output-field array to write
234 C misValLoc :: local Missing Value
235 C myTime :: current time of simulation (s)
236 C myIter :: current iteration number
237 C myThid :: my Thread Id number
238 INTEGER NrMax
239 INTEGER nLevOutp
240 INTEGER listId, ndId, mate
241 CHARACTER*(MAX_LEN_FNAM) diag_mnc_bn
242 _RL qtmp(1-OLx:sNx+OLx,1-OLy:sNy+OLy,NrMax,nSx,nSy)
243 _RL misValLoc
244 _RL myTime
245 INTEGER myIter, myThid
246 CEOP
247
248 #ifdef ALLOW_MNC
249 C !FUNCTIONS:
250 c INTEGER ILNBLNK
251 c EXTERNAL ILNBLNK
252
253 C !LOCAL VARIABLES:
254 C i,j,k :: loop indices
255 C bi,bj :: tile indices
256 INTEGER i, j, k
257 INTEGER bi, bj
258
259 c CHARACTER*(MAX_LEN_MBUF) msgBuf
260 c INTEGER ll, llMx, jj, jjMx
261 INTEGER ii, klev
262 INTEGER CW_DIMS, NLEN
263 PARAMETER ( CW_DIMS = 10 )
264 PARAMETER ( NLEN = 80 )
265 INTEGER dim(CW_DIMS), ib(CW_DIMS), ie(CW_DIMS)
266 CHARACTER*(NLEN) dn(CW_DIMS)
267 CHARACTER*(NLEN) d_cw_name
268 c CHARACTER*(NLEN) dn_blnk
269 LOGICAL useMisValForThisDiag
270 REAL*8 misval_r8(2)
271 REAL*4 misval_r4(2)
272 INTEGER misval_int(2)
273
274 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
275 c IF (useMNC .AND. diag_mnc) THEN
276
277 _BEGIN_MASTER( myThid )
278
279 DO ii = 1,CW_DIMS
280 c d_cw_name(1:NLEN) = dn_blnk(1:NLEN)
281 c dn(ii)(1:NLEN) = dn_blnk(1:NLEN)
282 dn(ii) = ' '
283 ENDDO
284 DO ii=1,2
285 misval_r4(ii) = misValLoc
286 misval_r8(ii) = misValLoc
287 misval_int(ii) = UNSET_I
288 ENDDO
289
290 C Note that the "d_cw_name" variable is a hack that hides a
291 C subtlety within MNC. Basically, each MNC-wrapped file is
292 C caching its own concept of what each "grid name" (that is, a
293 C dimension group name) means. So one cannot re-use the same
294 C "grid" name for different collections of dimensions within a
295 C given file. By appending the "ndId" values to each name, we
296 C guarantee uniqueness within each MNC-produced file.
297 WRITE(d_cw_name,'(a,i6.6)') 'd_cw_',ndId
298
299 C XY dimensions
300 dim(1) = sNx + 2*OLx
301 dim(2) = sNy + 2*OLy
302 ib(1) = OLx + 1
303 ib(2) = OLy + 1
304 IF (gdiag(ndId)(2:2) .EQ. 'M') THEN
305 dn(1)(1:2) = 'X'
306 ie(1) = OLx + sNx
307 dn(2)(1:2) = 'Y'
308 ie(2) = OLy + sNy
309 ELSEIF (gdiag(ndId)(2:2) .EQ. 'U') THEN
310 dn(1)(1:3) = 'Xp1'
311 ie(1) = OLx + sNx + 1
312 dn(2)(1:2) = 'Y'
313 ie(2) = OLy + sNy
314 ELSEIF (gdiag(ndId)(2:2) .EQ. 'V') THEN
315 dn(1)(1:2) = 'X'
316 ie(1) = OLx + sNx
317 dn(2)(1:3) = 'Yp1'
318 ie(2) = OLy + sNy + 1
319 ELSEIF (gdiag(ndId)(2:2) .EQ. 'Z') THEN
320 dn(1)(1:3) = 'Xp1'
321 ie(1) = OLx + sNx + 1
322 dn(2)(1:3) = 'Yp1'
323 ie(2) = OLy + sNy + 1
324 ENDIF
325
326 C Z is special since it varies
327 WRITE(dn(3),'(a,i6.6)') 'Zd', nLevOutp
328 IF ( (gdiag(ndId)(10:10) .EQ. 'R')
329 & .AND. (gdiag(ndId)(9:9) .EQ. 'M') ) THEN
330 WRITE(dn(3),'(a,i6.6)') 'Zmd', nLevOutp
331 ENDIF
332 IF ( (gdiag(ndId)(10:10) .EQ. 'R')
333 & .AND. (gdiag(ndId)(9:9) .EQ. 'L') ) THEN
334 WRITE(dn(3),'(a,i6.6)') 'Zld', nLevOutp
335 ENDIF
336 IF ( (gdiag(ndId)(10:10) .EQ. 'R')
337 & .AND. (gdiag(ndId)(9:9) .EQ. 'U') ) THEN
338 WRITE(dn(3),'(a,i6.6)') 'Zud', nLevOutp
339 ENDIF
340 dim(3) = NrMax
341 ib(3) = 1
342 ie(3) = nLevOutp
343
344 C Time dimension
345 dn(4)(1:1) = 'T'
346 dim(4) = -1
347 ib(4) = 1
348 ie(4) = 1
349
350 CALL MNC_CW_ADD_GNAME( d_cw_name, 4,
351 & dim, dn, ib, ie, myThid )
352 CALL MNC_CW_ADD_VNAME( cdiag(ndId), d_cw_name,
353 & 4, 5, myThid )
354 CALL MNC_CW_ADD_VATTR_TEXT( cdiag(ndId),'description',
355 & tdiag(ndId), myThid )
356 CALL MNC_CW_ADD_VATTR_TEXT( cdiag(ndId),'units',
357 & udiag(ndId), myThid )
358
359 useMisValForThisDiag = mate.GT.0
360 C Use the missing values for masking out the land points:
361 C only for scalar diagnostics at mass points (so far)
362 IF ( useMissingValue.AND.gdiag(ndId)(1:2).EQ.'SM' ) THEN
363 useMisValForThisDiag = .TRUE.
364 C note: better to use 2-D mask if kdiag <> Nr or vert.integral
365 DO bj = myByLo(myThid), myByHi(myThid)
366 DO bi = myBxLo(myThid), myBxHi(myThid)
367 DO k = 1,nLevOutp
368 klev = NINT(levs(k,listId))
369 IF ( fflags(listId)(2:2).EQ.'I' ) kLev = 1
370 DO j = 1-OLy,sNy+OLy
371 DO i = 1-OLx,sNx+OLx
372 IF ( maskC(i,j,klev,bi,bj) .EQ. 0. )
373 & qtmp(i,j,k,bi,bj) = misValLoc
374 ENDDO
375 ENDDO
376 ENDDO
377 ENDDO
378 ENDDO
379 ENDIF
380 IF ( useMisValForThisDiag ) THEN
381 C assign missing values and set flag for adding the netCDF atttibute
382 CALL MNC_CW_VATTR_MISSING(cdiag(ndId), 2,
383 I misval_r8, misval_r4, misval_int, myThid )
384 ELSE
385 C suppress the missing value attribute (iflag = 0)
386 C Note: We have to call the following subroutine for each mnc that has
387 C been created "on the fly" by mnc_cw_add_vname and will be deleted
388 C by mnc_cw_del_vname, because all of these variables use the same
389 C identifier so that mnc_cw_vfmv(indv) needs to be overwritten for
390 C each of these variables
391 CALL MNC_CW_VATTR_MISSING( cdiag(ndId), 0,
392 I misval_r8, misval_r4, misval_int, myThid )
393 ENDIF
394
395 IF ( ((writeBinaryPrec .EQ. precFloat32).AND.
396 & (fflags(listId)(1:1) .NE. 'D'))
397 & .OR. (fflags(listId)(1:1) .EQ. 'R') ) THEN
398 CALL MNC_CW_RL_W( 'R',diag_mnc_bn,0,0,
399 & cdiag(ndId), qtmp, myThid)
400 ELSEIF ( (writeBinaryPrec .EQ. precFloat64)
401 & .OR. (fflags(listId)(1:1) .EQ. 'D') ) THEN
402 CALL MNC_CW_RL_W( 'D',diag_mnc_bn,0,0,
403 & cdiag(ndId), qtmp, myThid)
404 ENDIF
405
406 CALL MNC_CW_DEL_VNAME(cdiag(ndId), myThid)
407 CALL MNC_CW_DEL_GNAME(d_cw_name, myThid)
408
409 _END_MASTER( myThid )
410
411 c ENDIF
412 #endif /* ALLOW_MNC */
413
414 RETURN
415 END

  ViewVC Help
Powered by ViewVC 1.1.22