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

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

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


Revision 1.8 - (hide annotations) (download)
Tue Feb 5 15:31:19 2008 UTC (16 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint65, checkpoint60, checkpoint61, checkpoint62, checkpoint63, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59o, checkpoint59n, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y, HEAD
Changes since 1.7: +27 -27 lines
minor modifications for many diagnostics:
- modify "available_diagnostics.log" and diagnostics summary (write mate number)
- use wider (integer) format (generally, use I6) to write diagnostics number
- rename numdiags --> numDiags (to differentiate from mdiag)

1 jmc 1.8 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagstats_mnc_out.F,v 1.7 2005/11/01 01:53:13 jmc Exp $
2 edhill 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: DIAGSTATS_MNC_OUT
9    
10     C !INTERFACE:
11     SUBROUTINE DIAGSTATS_MNC_OUT(
12     I statGlob, nLev, ndId,
13 edhill 1.2 I mId, listId, myTime, myIter, myThid )
14 edhill 1.1
15     C !DESCRIPTION:
16     C Write Global statistics to a netCDF file
17    
18     C !USES:
19     IMPLICIT NONE
20     #include "SIZE.h"
21     #include "EEPARAMS.h"
22     #include "EESUPPORT.h"
23     #include "PARAMS.h"
24     #include "GRID.h"
25     #include "DIAGNOSTICS_SIZE.h"
26     #include "DIAGNOSTICS.h"
27    
28     #ifdef ALLOW_FIZHI
29     #include "fizhi_SIZE.h"
30     #else
31     INTEGER Nrphys
32     PARAMETER (Nrphys=0)
33     #endif
34    
35     C !INPUT PARAMETERS:
36     C statGlob :: AVERAGED DIAGNOSTIC QUANTITY
37     C nLev :: 2nd Dimension (max Nb of levels) of statGlob array
38     C ndId :: diagnostic Id number (in diagnostics long list)
39     C mId :: field rank in list "listId"
40     C listId :: current output Stream list
41     C myIter :: current Iteration Number
42     C myTime :: current time of simulation (s)
43     C myThid :: my thread Id number
44     INTEGER nLev
45 edhill 1.2 _RL statGlob(0:nStats,0:nLev,0:nRegions)
46     _RL myTime
47 edhill 1.1 INTEGER ndId, mId, listId
48 edhill 1.2 INTEGER myIter, myThid
49 edhill 1.1 CEOP
50    
51     C !LOCAL VARIABLES:
52 jmc 1.6 #ifdef ALLOW_MNC
53 edhill 1.1 INTEGER im, ix, iv, ist
54     PARAMETER ( iv = nStats - 2 , im = nStats - 1 , ix = nStats )
55     INTEGER i, j, k
56     CHARACTER*(MAX_LEN_MBUF) tnam
57     CHARACTER*(3) stat_typ(5)
58     INTEGER ILNBLNK
59     EXTERNAL ILNBLNK
60     INTEGER ii, ilen
61     CHARACTER*(MAX_LEN_FNAM) diag_mnc_bn
62     INTEGER CW_DIMS, NLEN
63     PARAMETER ( CW_DIMS = 10 )
64     PARAMETER ( NLEN = 80 )
65     INTEGER dim(CW_DIMS), ib(CW_DIMS), ie(CW_DIMS)
66     CHARACTER*(NLEN) dn(CW_DIMS)
67     CHARACTER*(NLEN) d_cw_gname
68     CHARACTER*(NLEN) d_cw_gname0
69     CHARACTER*(NLEN) dn_blnk
70 jmc 1.6 #ifdef DIAGST_MNC_NEEDSWORK
71     CHARACTER*(5) ctmp
72 edhill 1.1 _RS ztmp(Nr+Nrphys)
73 jmc 1.6 #endif
74 edhill 1.1 _RL stmp(Nr+Nrphys+1,nRegions+1)
75     #endif /* ALLOW_MNC */
76    
77     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
78    
79     #ifdef ALLOW_MNC
80    
81     _BEGIN_MASTER( myThid)
82    
83     stat_typ(1) = 'vol'
84     stat_typ(2) = 'ave'
85     stat_typ(3) = 'std'
86     stat_typ(4) = 'min'
87     stat_typ(5) = 'max'
88    
89     #ifdef ALLOW_USE_MPI
90     IF ( diagSt_MNC .AND. mpiMyId.EQ.0 ) THEN
91     #else
92     IF ( diagSt_MNC ) THEN
93     #endif
94    
95     DO i = 1,MAX_LEN_FNAM
96     diag_mnc_bn(i:i) = ' '
97     ENDDO
98     DO i = 1,NLEN
99     dn_blnk(i:i) = ' '
100     ENDDO
101     ilen = ILNBLNK(diagSt_Fname(listId))
102     WRITE(diag_mnc_bn, '(a)') diagSt_Fname(listId)(1:ilen)
103    
104     IF (mId .EQ. 1) THEN
105     C Update the record dimension by writing the iteration number
106     CALL MNC_CW_SET_UDIM(diag_mnc_bn, -1, myThid)
107 edhill 1.5 CALL MNC_CW_RL_W_S('D',diag_mnc_bn,1,1,'T',myTime,myThid)
108 edhill 1.1 CALL MNC_CW_SET_UDIM(diag_mnc_bn, 0, myThid)
109 edhill 1.5 CALL MNC_CW_I_W_S('I',diag_mnc_bn,1,1,'iter',myIter,myThid)
110 edhill 1.1 ENDIF
111    
112     #ifdef DIAGST_MNC_NEEDSWORK
113     C This is turned off for the time being but it should eventually
114     C be re-worked and turned on so that coordinate dimensions are
115     C supplied along with the data. Unfortunately, the current
116     C diagnostics system has **NO** way of telling us whether a
117     C quantity is defined on a typical vertical grid (eg. the dynamics
118     C grid), a gridalt--style grid, or a single-level field that has
119     C no specified vertical location.
120    
121     dn(1)(1:NLEN) = dn_blnk(1:NLEN)
122     WRITE(dn(1),'(a,i6.6)') 'Zmd', kdiag(ndId)
123     dim(1) = kdiag(ndId)
124     ib(1) = 1
125     ie(1) = kdiag(ndId)
126    
127     CALL MNC_CW_ADD_GNAME('diag_levels', 1,
128     & dim, dn, ib, ie, myThid)
129     CALL MNC_CW_ADD_VNAME('diag_levels', 'diag_levels',
130     & 0,0, myThid)
131     CALL MNC_CW_ADD_VATTR_TEXT('diag_levels','description',
132     & 'Idicies of vertical levels within the source arrays',
133     & myThid)
134    
135 edhill 1.5 CALL MNC_CW_RL_W('D',diag_mnc_bn,1,1,
136 edhill 1.1 & 'diag_levels', levs(1,listId), myThid)
137    
138     CALL MNC_CW_DEL_VNAME('diag_levels', myThid)
139     CALL MNC_CW_DEL_GNAME('diag_levels', myThid)
140    
141     C Now define: Zmdxxxxxx, Zudxxxxxx, Zldxxxxxx
142     ctmp(1:5) = 'mul '
143     DO i = 1,3
144     dn(1)(1:NLEN) = dn_blnk(1:NLEN)
145     WRITE(dn(1),'(3a,i6.6)') 'Z',ctmp(i:i),'d',nlevels(listId)
146     CALL MNC_CW_ADD_GNAME(dn(1), 1, dim, dn, ib, ie, myThid)
147     CALL MNC_CW_ADD_VNAME(dn(1), dn(1), 0,0, myThid)
148    
149     C The following three ztmp() loops should eventually be modified
150     C to reflect the fractional nature of levs(j,l) -- they should
151     C do something like:
152     C ztmp(j) = rC(INT(FLOOR(levs(j,l))))
153     C + ( rC(INT(FLOOR(levs(j,l))))
154     C + rC(INT(CEIL(levs(j,l)))) )
155     C / ( levs(j,l) - FLOOR(levs(j,l)) )
156     C for averaged levels.
157     IF (i .EQ. 1) THEN
158     DO j = 1,nlevels(listId)
159     ztmp(j) = rC(NINT(levs(j,listId)))
160     ENDDO
161     CALL MNC_CW_ADD_VATTR_TEXT(dn(1),'description',
162     & 'Dimensional coordinate value at the mid point',
163     & myThid)
164     ELSEIF (i .EQ. 2) THEN
165     DO j = 1,nlevels(listId)
166     ztmp(j) = rF(NINT(levs(j,listId)) + 1)
167     ENDDO
168     CALL MNC_CW_ADD_VATTR_TEXT(dn(1),'description',
169     & 'Dimensional coordinate value at the upper point',
170     & myThid)
171     ELSEIF (i .EQ. 3) THEN
172     DO j = 1,nlevels(listId)
173     ztmp(j) = rF(NINT(levs(j,listId)))
174     ENDDO
175     CALL MNC_CW_ADD_VATTR_TEXT(dn(1),'description',
176     & 'Dimensional coordinate value at the lower point',
177     & myThid)
178     ENDIF
179 edhill 1.5 CALL MNC_CW_RS_W('D',diag_mnc_bn,1,1, dn(1), ztmp, myThid)
180 edhill 1.1 CALL MNC_CW_DEL_VNAME(dn(1), myThid)
181     CALL MNC_CW_DEL_GNAME(dn(1), myThid)
182     ENDDO
183     #endif /* DIAGST_MNC_NEEDSWORK */
184    
185     DO ii = 1,CW_DIMS
186     d_cw_gname(1:NLEN) = dn_blnk(1:NLEN)
187     dn(ii)(1:NLEN) = dn_blnk(1:NLEN)
188     ENDDO
189 jmc 1.8
190 edhill 1.1 C Z is special since it varies
191 edhill 1.3 WRITE(dn(1),'(a,i6.6)') 'Zd', kdiag(ndId)
192 edhill 1.1 IF ( (gdiag(ndId)(10:10) .EQ. 'R')
193     & .AND. (gdiag(ndId)(9:9) .EQ. 'M') ) THEN
194 edhill 1.3 WRITE(dn(1),'(a,i6.6)') 'Zmd', kdiag(ndId)
195 edhill 1.1 ENDIF
196     IF ( (gdiag(ndId)(10:10) .EQ. 'R')
197     & .AND. (gdiag(ndId)(9:9) .EQ. 'L') ) THEN
198 edhill 1.3 WRITE(dn(1),'(a,i6.6)') 'Zld', kdiag(ndId)
199 edhill 1.1 ENDIF
200     IF ( (gdiag(ndId)(10:10) .EQ. 'R')
201     & .AND. (gdiag(ndId)(9:9) .EQ. 'U') ) THEN
202 edhill 1.3 WRITE(dn(1),'(a,i6.6)') 'Zud', kdiag(ndId)
203 edhill 1.1 ENDIF
204     dim(1) = Nr+Nrphys+1
205     ib(1) = 1
206     ie(1) = kdiag(ndId)
207 jmc 1.8
208 edhill 1.1 C "region" dimension
209     dim(2) = nRegions + 1
210     ib(2) = 1
211     dn(2)(1:6) = 'region'
212     ie(2) = nRegions + 1
213 jmc 1.8
214 edhill 1.1 C Time dimension
215     dn(3)(1:1) = 'T'
216     dim(3) = -1
217     ib(3) = 1
218     ie(3) = 1
219 jmc 1.8
220 edhill 1.1 C Note that the "d_cw_gname" variable is a hack that hides a
221     C subtlety within MNC. Basically, each MNC-wrapped file is
222     C caching its own concept of what each "grid name" (that is, a
223     C dimension group name) means. So one cannot re-use the same
224     C "grid" name for different collections of dimensions within a
225     C given file. By appending the "ndId" values to each name, we
226     C guarantee uniqueness within each MNC-produced file.
227    
228     WRITE(d_cw_gname,'(a7,i6.6)') 'dst_cw_', ndId
229     CALL MNC_CW_ADD_GNAME(d_cw_gname, 3,
230     & dim, dn, ib, ie, myThid)
231    
232     WRITE(dn(1),'(a3)') 'Zd0'
233     ie(1) = 1
234     WRITE(d_cw_gname0,'(a9,i6.6)') 'dst_cw_0_', ndId
235     CALL MNC_CW_ADD_GNAME(d_cw_gname0, 3,
236     & dim, dn, ib, ie, myThid)
237 jmc 1.8
238 edhill 1.1 DO ist = 0,nStats
239 jmc 1.8
240 edhill 1.1 DO i = 1,MAX_LEN_FNAM
241     tnam(i:i) = ' '
242     ENDDO
243    
244 jmc 1.4 c IF ( kdiag(ndId) .GT. 1 ) THEN
245 jmc 1.8
246 edhill 1.1 ilen = ILNBLNK(cdiag(ndId))
247 jmc 1.8 WRITE(tnam,'(a,a1,a3)')
248 jmc 1.4 & cdiag(ndId)(1:ilen),'_',stat_typ(ist+1)
249 jmc 1.8
250 edhill 1.1 CALL MNC_CW_ADD_VNAME(tnam, d_cw_gname0,
251     & 0,0, myThid)
252     CALL MNC_CW_ADD_VATTR_TEXT(tnam,'description',
253     & tdiag(ndId),myThid)
254     CALL MNC_CW_ADD_VATTR_TEXT(tnam,'units',
255     & udiag(ndId),myThid)
256 jmc 1.8
257 edhill 1.1 C Copy the data into a temporary with the necessary shape
258     DO j = 0,nRegions
259     stmp(1,j+1) = statGlob(ist,0,j)
260     ENDDO
261 jmc 1.8
262 jmc 1.7 C-jmc: fflags is not for Statistics-Diagnostics, can be unset, and since
263     C- size of the output file will not be an issue here: Always write real*8
264     c IF ((fflags(listId)(1:1) .EQ. ' ')
265     c & .OR. (fflags(listId)(1:1) .EQ. 'R')) THEN
266 jmc 1.8 c
267 jmc 1.7 c CALL MNC_CW_RL_W('R',diag_mnc_bn,1,1,
268     c & tnam, stmp, myThid)
269 jmc 1.8 c
270 jmc 1.7 c ELSEIF (fflags(listId)(1:1) .EQ. 'D') THEN
271 jmc 1.8
272 edhill 1.5 CALL MNC_CW_RL_W('D',diag_mnc_bn,1,1,
273 edhill 1.1 & tnam, stmp, myThid)
274 jmc 1.8
275 jmc 1.7 c else
276     c write(0,*) myIter, ndId, listId
277     c write(0,'(3A)') '>',cdiag(ndId),'<'
278     c write(0,'(3A)') '>',fflags(listId),'<'
279     c STOP ' in DIAGSTATS_MNC_OUT'
280     c ENDIF
281 jmc 1.8
282 edhill 1.1 CALL MNC_CW_DEL_VNAME(tnam, myThid)
283 jmc 1.8
284 jmc 1.4 c ENDIF
285 jmc 1.8
286 jmc 1.4 IF ( kdiag(ndId) .GT. 1 ) THEN
287    
288     ilen = ILNBLNK(cdiag(ndId))
289 jmc 1.8 WRITE(tnam,'(a,a4,a3)')
290 jmc 1.4 & cdiag(ndId)(1:ilen),'_lv_',stat_typ(ist+1)
291 jmc 1.8
292 jmc 1.4 CALL MNC_CW_ADD_VNAME(tnam, d_cw_gname,
293     & 0,0, myThid)
294     CALL MNC_CW_ADD_VATTR_TEXT(tnam,'description',
295     & tdiag(ndId),myThid)
296     CALL MNC_CW_ADD_VATTR_TEXT(tnam,'units',
297     & udiag(ndId),myThid)
298 jmc 1.8
299 jmc 1.4 C Copy the data into a temporary with the necessary shape
300     DO j = 0,nRegions
301     DO k = 1,kdiag(ndId)
302     stmp(k,j+1) = statGlob(ist,k,j)
303     ENDDO
304     ENDDO
305 jmc 1.8
306 jmc 1.7 C-jmc: Always write real*8 (size of the output file will not be an issue here)
307 edhill 1.5 CALL MNC_CW_RL_W('D',diag_mnc_bn,1,1,
308 jmc 1.4 & tnam, stmp, myThid)
309 jmc 1.8
310 jmc 1.4 CALL MNC_CW_DEL_VNAME(tnam, myThid)
311 jmc 1.8
312 edhill 1.1 ENDIF
313 jmc 1.4
314 edhill 1.1 ENDDO
315 jmc 1.8
316 edhill 1.1 CALL MNC_CW_DEL_GNAME(d_cw_gname, myThid)
317     CALL MNC_CW_DEL_GNAME(d_cw_gname0, myThid)
318    
319     ENDIF
320 jmc 1.8
321 edhill 1.1 _END_MASTER( myThid )
322    
323     #endif /* ALLOW_MNC */
324    
325     RETURN
326     END
327     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22