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

Diff of /MITgcm/pkg/diagnostics/diagnostics_out.F

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

revision 1.2 by jmc, Tue Dec 14 02:30:58 2004 UTC revision 1.57 by jmc, Mon Jun 27 22:27:23 2011 UTC
# Line 8  CBOP 0 Line 8  CBOP 0
8  C     !ROUTINE: DIAGNOSTICS_OUT  C     !ROUTINE: DIAGNOSTICS_OUT
9    
10  C     !INTERFACE:  C     !INTERFACE:
11        SUBROUTINE  DIAGNOSTICS_OUT(        SUBROUTINE DIAGNOSTICS_OUT(
12       I     listnum,       I     listId,
13         I     myTime,
14       I     myIter,       I     myIter,
15       I     myThid )       I     myThid )
16    
17  C     !DESCRIPTION:  C     !DESCRIPTION:
18  C     Write output for diagnostics fields.  C     Write output for diagnostics fields.
19          
20  C     !USES:  C     !USES:
21        implicit none        IMPLICIT NONE
22  #include "SIZE.h"  #include "SIZE.h"
23  #include "EEPARAMS.h"  #include "EEPARAMS.h"
24  #include "PARAMS.h"  #include "PARAMS.h"
25    #include "GRID.h"
 #ifdef ALLOW_FIZHI  
 #include "fizhi_SIZE.h"  
 #else  
       integer Nrphys  
       parameter (Nrphys=0)  
 #endif  
   
26  #include "DIAGNOSTICS_SIZE.h"  #include "DIAGNOSTICS_SIZE.h"
27  #include "DIAGNOSTICS.h"  #include "DIAGNOSTICS.h"
28    
29          INTEGER NrMax
30          PARAMETER( NrMax = numLevels )
31    
32  C     !INPUT PARAMETERS:  C     !INPUT PARAMETERS:
33        integer myThid, myIter, listnum  C     listId  :: Diagnostics list number being written
34    C     myIter  :: current iteration number
35    C     myTime  :: current time of simulation (s)
36    C     myThid  :: my Thread Id number
37          _RL     myTime
38          INTEGER listId, myIter, myThid
39  CEOP  CEOP
40    
41        integer i, j, k, m, n, bi, bj  C     !FUNCTIONS:
42        character*8 parms1        INTEGER ILNBLNK
43        character*1 parse1(8)        EXTERNAL ILNBLNK
44        character*3 mate_index  #ifdef ALLOW_FIZHI
45        integer mate        _RL   getcon
46        _RL qtmp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr+Nrphys,nSx,nSy)        EXTERNAL getcon
47        _RL qtmp2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr+Nrphys,nSx,nSy)  #endif
       _RL undef, getcon  
       external getcon  
       integer ilnblnk  
       external ilnblnk  
       integer ilen  
   
       equivalence (     parms1 , parse1(1) )  
       equivalence ( mate_index , parse1(6) )  
48    
49        CHARACTER*(MAX_LEN_FNAM) pref  C     !LOCAL VARIABLES:
50    C     i,j,k :: loop indices
51    C     bi,bj :: tile indices
52    C     lm    :: loop index (averageCycle)
53    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    C     nLevOutp :: number of levels to write in output file
59    C
60    C--   COMMON /LOCAL_DIAGNOSTICS_OUT/ local common block (for multi-threaded)
61    C     qtmp1 :: temporary array; used to store a copy of diag. output field.
62    C     qtmp2 :: temporary array; used to store a copy of a 2nd diag. field.
63    C-  Note: local common block no longer needed.
64    c     COMMON /LOCAL_DIAGNOSTICS_OUT/ qtmp1
65          _RL qtmp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,NrMax,nSx,nSy)
66          _RL qtmp2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,NrMax,nSx,nSy)
67    
68          INTEGER i, j, k, lm
69          INTEGER bi, bj
70          INTEGER md, ndId, nn, ip, im
71          INTEGER mate, mDbl, mVec
72          CHARACTER*10 gcode
73          _RL undefRL
74          INTEGER nLevOutp, kLev
75    
76          INTEGER iLen
77          INTEGER ioUnit
78          CHARACTER*(MAX_LEN_FNAM) fn
79        CHARACTER*(MAX_LEN_MBUF) suff        CHARACTER*(MAX_LEN_MBUF) suff
80        CHARACTER*(80) fn        CHARACTER*(MAX_LEN_MBUF) msgBuf
81        logical glf        INTEGER prec, nRec, nTimRec
82          _RL     timeRec(2)
83          _RL     tmpLoc
84    #ifdef ALLOW_MDSIO
85          LOGICAL glf
86    #endif
87  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
       integer ii  
88        CHARACTER*(MAX_LEN_FNAM) diag_mnc_bn        CHARACTER*(MAX_LEN_FNAM) diag_mnc_bn
   
       integer CW_DIMS, NLEN  
       parameter ( CW_DIMS = 10 )  
       parameter ( NLEN    = 80 )  
       integer dim(CW_DIMS), ib(CW_DIMS), ie(CW_DIMS)  
       character*(NLEN) dn(CW_DIMS)  
       character*(NLEN) dn_blnk  
89  #endif /*  ALLOW_MNC  */  #endif /*  ALLOW_MNC  */
90    
91        undef = getcon('UNDEF')  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
       glf = globalFiles  
       WRITE(suff,'(I10.10)') myIter  
       pref = fnames(listnum)  
       ilen=ilnblnk( pref )  
       WRITE( fn, '(A,A,A)' ) pref(1:ilen),'.',suff(1:10)  
92    
93  #ifdef ALLOW_MNC  C---  set file properties
94        IF (useMNC .AND. diag_mnc) THEN        ioUnit= standardMessageUnit
95          DO i = 1,MAX_LEN_FNAM        undefRL = UNSET_RL
96            diag_mnc_bn(i:i) = ' '  #ifdef ALLOW_FIZHI
97          ENDDO        IF ( useFIZHI ) undefRL = getcon('UNDEF')
98          DO i = 1,NLEN  #endif
99            dn_blnk(i:i) = ' '        IF ( misvalFlt(listId).NE.UNSET_RL ) undefRL = misvalFlt(listId)
         ENDDO  
 c       WRITE( diag_mnc_bn, '(A,A)' ) 'diag.', pref(1:ilen)  
         WRITE( diag_mnc_bn, '(A)' ) pref(1:ilen)  
   
 C       Update the record dimension by writing the iteration number  
         CALL MNC_CW_SET_UDIM(diag_mnc_bn, -1, myThid)  
         CALL MNC_CW_I_W_S('I',diag_mnc_bn,0,0,'iter',myIter,myThid)  
         CALL MNC_CW_SET_UDIM(diag_mnc_bn, 0, myThid)  
   
         dn(1)(1:NLEN) = dn_blnk(1:NLEN)  
         write(dn(1),'(a,i6.6)') 'Zd', nlevels(listnum)  
         dim(1) = nlevels(listnum)  
         ib(1)  = 1  
         ie(1)  = nlevels(listnum)  
   
         CALL MNC_CW_ADD_GNAME('diag_levels', 1,  
      &       dim, dn, ib, ie, myThid)  
         CALL MNC_CW_ADD_VNAME('level_indicies', 'diag_levels',  
      &       0,0, myThid)  
         CALL MNC_CW_ADD_VATTR_TEXT('level_indicies','description',  
      &    'Idicies of vertical levels within the data source arrays',  
      &       myThid)  
           
         CALL MNC_CW_RL_W('I',diag_mnc_bn,0,0,  
      &       'level_indicies', levs(1,listnum), myThid)  
100    
101          CALL MNC_CW_DEL_VNAME('level_indicies', myThid)        WRITE(suff,'(I10.10)') myIter
102          CALL MNC_CW_DEL_GNAME('diag_levels', myThid)        iLen = ILNBLNK(fnames(listId))
103          WRITE( fn, '(A,A,A)' ) fnames(listId)(1:iLen),'.',suff(1:10)
104    C-    for now, if integrate vertically, output field has just 1 level:
105          nLevOutp = nlevels(listId)
106          IF ( fflags(listId)(2:2).EQ.'I' ) nLevOutp = 1
107    
108    C--   Set time information:
109          IF ( freq(listId).LT.0. ) THEN
110    C-    Snap-shot: store a unique time (which is consistent with State-Var timing)
111            nTimRec = 1
112            timeRec(1) = myTime
113          ELSE
114    C-    Time-average: store the 2 edges of the time-averaging interval.
115    C      this time is consitent with intermediate Var (i.e., non-state, e.g, flux,
116    C      tendencies) timing. For State-Var, this is shifted by + halt time-step.
117            nTimRec = 2
118    
119    C-    end of time-averaging interval:
120            timeRec(2) = myTime
121    
122    C-    begining of time-averaging interval:
123    c       timeRec(1) = myTime - freq(listId)
124    C     a) find the time of the previous multiple of output freq:
125            timeRec(1) = myTime-deltaTClock*0.5 _d 0
126            timeRec(1) = (timeRec(1)-phase(listId))/freq(listId)
127            i = INT( timeRec(1) )
128            IF ( timeRec(1).LT.0. ) THEN
129              tmpLoc = FLOAT(i)
130              IF ( timeRec(1).NE.tmpLoc ) i = i - 1
131            ENDIF
132            timeRec(1) = phase(listId) + freq(listId)*FLOAT(i)
133    c       if ( listId.eq.2 ) write(0,*) 'f',i,timeRec(1)/deltaTClock
134            timeRec(1) = MAX( timeRec(1), startTime )
135    
136    C     b) round off to nearest multiple of time-step:
137            timeRec(1) = (timeRec(1)-baseTime)/deltaTClock
138            i = NINT( timeRec(1) )
139    C     if just half way, NINT will return the next time-step: correct this
140            tmpLoc = FLOAT(i) - 0.5 _d 0
141            IF ( timeRec(1).EQ.tmpLoc ) i = i - 1
142            timeRec(1) = baseTime + deltaTClock*FLOAT(i)
143    c       if ( listId.eq.2 ) write(0,*) i,timeRec(1)/deltaTClock
144        ENDIF        ENDIF
145    C--   Convert time to iteration number (debug)
146    c     DO i=1,nTimRec
147    c       timeRec(i) = timeRec(i)/deltaTClock
148    c     ENDDO
149    
150    C--   Place the loop on lm (= averagePeriod) outside the loop on md (= field):
151          DO lm=1,averageCycle(listId)
152    
153    #ifdef ALLOW_MNC
154           IF (useMNC .AND. diag_mnc) THEN
155             CALL DIAGNOSTICS_MNC_SET(
156         I                    nLevOutp, listId, lm,
157         O                    diag_mnc_bn,
158         I                    undefRL, myTime, myIter, myThid )
159           ENDIF
160  #endif /*  ALLOW_MNC  */  #endif /*  ALLOW_MNC  */
161    
162        do n = 1,nfields(listnum)  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
         do m = 1,ndiagt  
           if( flds(n,listnum).eq.cdiag(m) .and. idiag(m).ne.0 ) then  
             parms1 = gdiag(m)  
             if (ndiag(m).ne.0.and.parse1(5).ne.'D') then  
               if( myThid.eq.1 )  
      &             write(6,2000) m,cdiag(m),ndiag(m),gdiag(m)  
               if (parse1(5).ne.'C') then  
   
                 do k = 1,nlevels(listnum)  
                   call getdiag (levs(k,listnum),m,undef,qtmp1,myThid)  
                 enddo  
   
 C               Check for Mate of a Vector Diagnostic  
 C               -------------------------------------  
                 if ( parse1(1).eq.'U' .or. parse1(1).eq.'V' ) then  
                   read (mate_index,100) mate  
                   if( idiag(mate).ne.0 ) then  
                     if( myThid.eq.1 )  
      &                   write(6,2001) cdiag(m),mate,cdiag(mate)  
                   else  
                     if( myThid.eq.1 )  
      &                   write(6,2002) cdiag(m),mate,cdiag(mate)  
                   endif  
                 endif  
                   
               else  
   
 C               Check for Mate of a Counter Diagnostic  
 C               --------------------------------------  
                 read (mate_index,100) mate  
                     if( myThid.eq.1 )  
      &                   write(6,2003) cdiag(m),mate,cdiag(mate)  
                 do k = 1,nlevels(listnum)  
                   call getdiag2(levs(k,listnum),m,undef,qtmp1,myThid)  
                   call getdiag2(levs(k,listnum),mate,undef,qtmp2,myThid)  
                   do bj = myByLo(myThid), myByHi(myThid)  
                     do bi = myBxLo(myThid), myBxHi(myThid)  
                       do j = 1,sNy  
                         do i = 1,sNx  
                           if (qtmp2(i,j,k,bi,bj).ne.0.) then  
                             qtmp1(i,j,k,bi,bj) =  
      &                           qtmp1(i,j,k,bi,bj) / qtmp2(i,j,k,bi,bj)  
                           else  
                             qtmp1(i,j,k,bi,bj) = undef  
                           endif  
                         enddo  
                       enddo  
                     enddo  
                   enddo  
                 enddo  
163    
164                endif         DO md = 1,nfields(listId)
165              endif          ndId = jdiag(md,listId)
166            gcode = gdiag(ndId)(1:10)
167            mate = 0
168            mVec = 0
169            mDbl = 0
170            IF ( gcode(5:5).EQ.'C' ) THEN
171    C-      Check for Mate of a Counter Diagnostic
172               mate = hdiag(ndId)
173            ELSEIF ( gcode(5:5).EQ.'P' ) THEN
174    C-      Also load the mate (if stored) for Post-Processing
175               nn = ndId
176               DO WHILE ( gdiag(nn)(5:5).EQ.'P' )
177                 nn = hdiag(nn)
178               ENDDO
179               IF ( mdiag(md,listId).NE.0 ) mDbl = hdiag(nn)
180            ELSEIF ( gcode(1:1).EQ.'U' .OR. gcode(1:1).EQ.'V' ) THEN
181    C-      Check for Mate of a Vector Diagnostic
182               mVec = hdiag(ndId)
183            ENDIF
184            IF ( idiag(md,listId).NE.0 .AND. gcode(5:5).NE.'D' ) THEN
185    C--     Start processing 1 Fld :
186    
187              ip = ABS(idiag(md,listId)) + kdiag(ndId)*(lm-1)
188              im = mdiag(md,listId)
189              IF (mate.GT.0) im = im + kdiag(mate)*(lm-1)
190              IF (mDbl.GT.0) im = im + kdiag(mDbl)*(lm-1)
191              IF (mVec.GT.0) im = im + kdiag(mVec)*(lm-1)
192    
193              IF ( ndiag(ip,1,1).EQ.0 ) THEN
194    C-        Empty diagnostics case :
195    
196                _BEGIN_MASTER( myThid )
197                WRITE(msgBuf,'(A,I10)')
198         &        '- WARNING - from DIAGNOSTICS_OUT at iter=', myIter
199                CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
200         &                          SQUEEZE_RIGHT, myThid)
201                WRITE(msgBuf,'(A,I6,3A,I4,2A)')
202         &       '- WARNING -   diag.#',ndId, ' : ',flds(md,listId),
203         &       ' (#',md,' ) in outp.Stream: ',fnames(listId)
204                CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
205         &                          SQUEEZE_RIGHT, myThid)
206                IF ( averageCycle(listId).GT.1 ) THEN
207                 WRITE(msgBuf,'(A,2(I3,A))')
208         &        '- WARNING -   has not been filled (ndiag(lm=',lm,')=',
209         &                                            ndiag(ip,1,1), ' )'
210                ELSE
211                 WRITE(msgBuf,'(A,2(I3,A))')
212         &        '- WARNING -   has not been filled (ndiag=',
213         &                                            ndiag(ip,1,1), ' )'
214                ENDIF
215                CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
216         &                          SQUEEZE_RIGHT, myThid)
217                WRITE(msgBuf,'(A)')
218         &       'WARNING DIAGNOSTICS_OUT  => write ZEROS instead'
219                CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
220         &                          SQUEEZE_RIGHT, myThid)
221                _END_MASTER( myThid )
222                DO bj = myByLo(myThid), myByHi(myThid)
223                  DO bi = myBxLo(myThid), myBxHi(myThid)
224                    DO k = 1,nLevOutp
225                      DO j = 1-OLy,sNy+OLy
226                        DO i = 1-OLx,sNx+OLx
227                          qtmp1(i,j,k,bi,bj) = 0. _d 0
228                        ENDDO
229                      ENDDO
230                    ENDDO
231                  ENDDO
232                ENDDO
233    
234              ELSE
235    C-        diagnostics is not empty :
236    
237                IF ( debugLevel.GE.debLevB .AND. myThid.EQ.1 ) THEN
238                  IF ( gcode(5:5).EQ.'P' ) THEN
239                   WRITE(ioUnit,'(A,I6,7A,I8,2A)')
240         &         ' Post-Processing Diag # ', ndId, '  ', cdiag(ndId),
241         &         '   Parms: ',gdiag(ndId)
242                   IF ( mDbl.EQ.0 ) THEN
243                    WRITE(ioUnit,'(2(3A,I6,A,I8))') '   from diag: ',
244         &            cdiag(nn), ' (#', nn, ') Cnt=', ndiag(ip,1,1)
245                   ELSE
246                    WRITE(ioUnit,'(2(3A,I6,A,I8))') '   from diag: ',
247         &            cdiag(nn), ' (#', nn, ') Cnt=', ndiag(ip,1,1),
248         &          ' and diag: ',
249         &            cdiag(mDbl),' (#',mDbl,') Cnt=',ndiag(im,1,1)
250                   ENDIF
251                  ELSE
252                   WRITE(ioUnit,'(A,I6,3A,I8,2A)')
253         &         ' Computing Diagnostic # ', ndId, '  ', cdiag(ndId),
254         &         '     Counter:',ndiag(ip,1,1),'   Parms: ',gdiag(ndId)
255                  ENDIF
256                  IF ( mate.GT.0 ) THEN
257                   WRITE(ioUnit,'(3A,I6,2A)')
258         &         '       use Counter Mate for  ', cdiag(ndId),
259         &         '     Diagnostic # ',mate, '  ', cdiag(mate)
260                  ELSEIF ( mVec.GT.0 ) THEN
261                    IF ( im.GT.0 .AND. ndiag(MAX(1,im),1,1).GT.0 ) THEN
262                     WRITE(ioUnit,'(3A,I6,3A)')
263         &             '           Vector  Mate for  ', cdiag(ndId),
264         &             '     Diagnostic # ',mVec, '  ', cdiag(mVec),
265         &             ' exists '
266                    ELSE
267                     WRITE(ioUnit,'(3A,I6,3A)')
268         &             '           Vector  Mate for  ', cdiag(ndId),
269         &             '     Diagnostic # ',mVec, '  ', cdiag(mVec),
270         &             ' not enabled'
271                    ENDIF
272                  ENDIF
273                ENDIF
274    
275  #ifdef ALLOW_MDSIO              IF ( fflags(listId)(2:2).EQ.' ' ) THEN
276  C           Prepare for mdsio optionality  C-       get only selected levels:
277              IF (diag_mdsio) THEN                DO bj = myByLo(myThid), myByHi(myThid)
278                call mdswritefield_new(fn,writeBinaryPrec,glf,'RL',                 DO bi = myBxLo(myThid), myBxHi(myThid)
279       &             Nr+Nrphys,nlevels(listnum),qtmp1,n,myIter,myThid)                  DO k = 1,nlevels(listId)
280                      kLev = NINT(levs(k,listId))
281                      CALL DIAGNOSTICS_GET_DIAG(
282         I                         kLev, undefRL,
283         O                         qtmp1(1-OLx,1-OLy,k,bi,bj),
284         I                         ndId, mate, ip, im, bi, bj, myThid )
285                    ENDDO
286                   ENDDO
287                  ENDDO
288                  IF ( mDbl.GT.0 ) THEN
289                   DO bj = myByLo(myThid), myByHi(myThid)
290                    DO bi = myBxLo(myThid), myBxHi(myThid)
291                     DO k = 1,nlevels(listId)
292                      kLev = NINT(levs(k,listId))
293                      CALL DIAGNOSTICS_GET_DIAG(
294         I                         kLev, undefRL,
295         O                         qtmp2(1-OLx,1-OLy,k,bi,bj),
296         I                         mDbl, 0, im, 0, bi, bj, myThid )
297                     ENDDO
298                    ENDDO
299                   ENDDO
300                  ENDIF
301                ELSE
302    C-       get all the levels (for vertical post-processing)
303                  DO bj = myByLo(myThid), myByHi(myThid)
304                   DO bi = myBxLo(myThid), myBxHi(myThid)
305                      CALL DIAGNOSTICS_GET_DIAG(
306         I                         0, undefRL,
307         O                         qtmp1(1-OLx,1-OLy,1,bi,bj),
308         I                         ndId, mate, ip, im, bi, bj, myThid )
309                   ENDDO
310                  ENDDO
311                  IF ( mDbl.GT.0 ) THEN
312                   DO bj = myByLo(myThid), myByHi(myThid)
313                    DO bi = myBxLo(myThid), myBxHi(myThid)
314                     DO k = 1,nlevels(listId)
315                      CALL DIAGNOSTICS_GET_DIAG(
316         I                         0, undefRL,
317         O                         qtmp2(1-OLx,1-OLy,k,bi,bj),
318         I                         mDbl, 0, im, 0, bi, bj, myThid )
319                     ENDDO
320                    ENDDO
321                   ENDDO
322                  ENDIF
323              ENDIF              ENDIF
 #endif /*  ALLOW_MDSIO  */  
324    
325  #ifdef ALLOW_MNC  C-----------------------------------------------------------------------
326              IF (useMNC .AND. diag_mnc) THEN  C--     Apply specific post-processing (e.g., interpolate) before output
327    C-----------------------------------------------------------------------
328                IF ( fflags(listId)(2:2).EQ.'P' ) THEN
329    C-          Do vertical interpolation:
330                 IF ( fluidIsAir ) THEN
331    C jmc: for now, this can only work in an atmospheric set-up (fluidIsAir);
332                  CALL DIAGNOSTICS_INTERP_VERT(
333         I                         listId, md, ndId, ip, im, lm,
334         U                         qtmp1, qtmp2,
335         I                         undefRL, myTime, myIter, myThid )
336                 ELSE
337                   WRITE(msgBuf,'(2A)') 'DIAGNOSTICS_OUT: ',
338         &           'INTERP_VERT not allowed in this config'
339                   CALL PRINT_ERROR( msgBuf , myThid )
340                   STOP 'ABNORMAL END: S/R DIAGNOSTICS_OUT'
341                 ENDIF
342                ENDIF
343                IF ( fflags(listId)(2:2).EQ.'I' ) THEN
344    C-          Integrate vertically: for now, output field has just 1 level:
345                  CALL DIAGNOSTICS_SUM_LEVELS(
346         I                         listId, md, ndId, ip, im, lm,
347         U                         qtmp1,
348         I                         undefRL, myTime, myIter, myThid )
349                ENDIF
350                IF ( gcode(5:5).EQ.'P' ) THEN
351    C-          Do Post-Processing:
352                 IF ( flds(md,listId).EQ.'PhiVEL  '
353    c    &       .OR. flds(md,listId).EQ.'PsiVEL  '
354         &          ) THEN
355                  CALL DIAGNOSTICS_CALC_PHIVEL(
356         I                         listId, md, ndId, ip, im, lm,
357         U                         qtmp1, qtmp2,
358         I                         myTime, myIter, myThid )
359                 ELSE
360                   WRITE(msgBuf,'(2A)') 'DIAGNOSTICS_OUT: ',
361         &           'unknown Processing method for diag="',cdiag(ndId),'"'
362                   CALL PRINT_ERROR( msgBuf , myThid )
363                   STOP 'ABNORMAL END: S/R DIAGNOSTICS_OUT'
364                 ENDIF
365                ENDIF
366    
367                _BEGIN_MASTER( myThid )  C--     End of empty diag / not-empty diag block
368              ENDIF
369    
370                do ii = 1,CW_DIMS  C--     Ready to write field "md", element "lm" in averageCycle(listId)
                 dn(ii)(1:NLEN) = dn_blnk(1:NLEN)  
               enddo  
   
               dn(1)(1:2) = 'Xd'  
               dim(1) = sNx + 2*OLx  
               ib(1)  = OLx + 1  
               ie(1)  = OLx + sNx  
               dn(2)(1:2) = 'Yd'  
               dim(2) = sNy + 2*OLy  
               ib(2)  = OLy + 1  
               ie(2)  = OLy + sNy  
   
 C             Z is special since it varies  
               write(dn(3),'(a,i6.6)') 'Zd', nlevels(listnum)  
               dim(3) = Nr+Nrphys  
               ib(3)  = 1  
               ie(3)  = nlevels(listnum)  
   
               CALL MNC_CW_ADD_GNAME('diag_cw_temp', 3,  
      &             dim, dn, ib, ie, myThid)  
               CALL MNC_CW_ADD_VNAME(cdiag(m), 'diag_cw_temp',  
      &             4,5, myThid)  
               CALL MNC_CW_ADD_VATTR_TEXT(cdiag(m),'description',  
      &             tdiag(m),myThid)  
               CALL MNC_CW_ADD_VATTR_TEXT(cdiag(m),'units',  
      &             udiag(m),myThid)  
371    
372                CALL MNC_CW_RL_W('D',diag_mnc_bn,0,0,  C-        write to binary file, using MDSIO pkg:
373       &             cdiag(m), qtmp1, myThid)            IF ( diag_mdsio ) THEN
374    c           nRec = lm + (md-1)*averageCycle(listId)
375                nRec = md + (lm-1)*nfields(listId)
376    C           default precision for output files
377                prec = writeBinaryPrec
378    C           fFlag(1)=R(or D): force it to be 32-bit(or 64) precision
379                IF ( fflags(listId)(1:1).EQ.'R' ) prec = precFloat32
380                IF ( fflags(listId)(1:1).EQ.'D' ) prec = precFloat64
381    C         a hack not to write meta files now: pass -nRec < 0 to MDS_WRITE S/R
382                CALL WRITE_REC_LEV_RL(
383         I                            fn, prec,
384         I                            NrMax, 1, nLevOutp,
385         I                            qtmp1, -nRec, myIter, myThid )
386              ENDIF
387    
388                CALL MNC_CW_DEL_VNAME(cdiag(m), myThid)  #ifdef ALLOW_MNC
389                CALL MNC_CW_DEL_GNAME('diag_cw_temp', myThid)            IF (useMNC .AND. diag_mnc) THEN
390                CALL DIAGNOSTICS_MNC_OUT(
391         I                       NrMax, nLevOutp, listId, ndId, mate,
392         I                       diag_mnc_bn, qtmp1,
393         I                       undefRL, myTime, myIter, myThid )
394              ENDIF
395    #endif /*  ALLOW_MNC  */
396    
397                _END_MASTER( myThid )  C--     end of Processing Fld # md
398            ENDIF
399           ENDDO
400    
401              ENDIF  C--   end loop on lm counter (= averagePeriod)
402  #endif /*  ALLOW_MNC  */        ENDDO
403    
404    #ifdef ALLOW_MDSIO
405          IF (diag_mdsio) THEN
406    C-    Note: temporary: since it is a pain to add more arguments to
407    C     all MDSIO S/R, uses instead this specific S/R to write only
408    C     meta files but with more informations in it.
409                glf = globalFiles
410                nRec = averageCycle(listId)*nfields(listId)
411                CALL MDS_WR_METAFILES(fn, prec, glf, .FALSE.,
412         &              0, 0, nLevOutp, ' ',
413         &              nfields(listId), flds(1,listId), nTimRec, timeRec,
414         &              nRec, myIter, myThid)
415          ENDIF
416    #endif /*  ALLOW_MDSIO  */
417    
418          RETURN
419          END
420    
           endif  
         enddo  
       enddo  
   
  100  format(i3)  
  2000 format(1x,'Computing Diagnostic # ',i3,2x,a8,5x,'Counter: ',  
      &     i4,6x,'Parms: ',a16)  
  2001 format(1x,'          Vector  Mate for  ',a8,5x,  
      &     'Diagnostic # ',i3,2x,a8,' exists ')  
  2002 format(1x,'        Vector  Mate for  ',a8,5x,  
      &     'Diagnostic # ',i3,2x,a8,' not enabled')  
  2003 format(1x,'      use Counter Mate for  ',a8,5x,  
      &     'Diagnostic # ',i3,2x,a8)  
         
       return  
       end  
                                                                       
421  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

Legend:
Removed from v.1.2  
changed lines
  Added in v.1.57

  ViewVC Help
Powered by ViewVC 1.1.22