/[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.54 by jmc, Tue Jun 21 18:00:48 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
88        integer ii        INTEGER ll, llMx, jj, jjMx
89        CHARACTER*(MAX_LEN_FNAM) diag_mnc_bn        CHARACTER*(MAX_LEN_FNAM) diag_mnc_bn
90          LOGICAL useMissingValue
91        integer CW_DIMS, NLEN        REAL*8 misValLoc
       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  
92  #endif /*  ALLOW_MNC  */  #endif /*  ALLOW_MNC  */
93    
94        undef = getcon('UNDEF')  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
95        glf = globalFiles  
96    C---  set file properties
97          ioUnit= standardMessageUnit
98          undefRL = UNSET_RL
99    #ifdef ALLOW_FIZHI
100          IF ( useFIZHI ) undefRL = getcon('UNDEF')
101    #endif
102        WRITE(suff,'(I10.10)') myIter        WRITE(suff,'(I10.10)') myIter
103        pref = fnames(listnum)        iLen = ILNBLNK(fnames(listId))
104        ilen=ilnblnk( pref )        WRITE( fn, '(A,A,A)' ) fnames(listId)(1:iLen),'.',suff(1:10)
105        WRITE( fn, '(A,A,A)' ) pref(1:ilen),'.',suff(1:10)  C-    for now, if integrate vertically, output field has just 1 level:
106          nLevOutp = nlevels(listId)
107          IF ( fflags(listId)(2:2).EQ.'I' ) nLevOutp = 1
108    
109    C--   Set time information:
110          IF ( freq(listId).LT.0. ) THEN
111    C-    Snap-shot: store a unique time (which is consistent with State-Var timing)
112            nTimRec = 1
113            timeRec(1) = myTime
114          ELSE
115    C-    Time-average: store the 2 edges of the time-averaging interval.
116    C      this time is consitent with intermediate Var (i.e., non-state, e.g, flux,
117    C      tendencies) timing. For State-Var, this is shifted by + halt time-step.
118            nTimRec = 2
119    
120    C-    end of time-averaging interval:
121            timeRec(2) = myTime
122    
123    C-    begining of time-averaging interval:
124    c       timeRec(1) = myTime - freq(listId)
125    C     a) find the time of the previous multiple of output freq:
126            timeRec(1) = myTime-deltaTClock*0.5 _d 0
127            timeRec(1) = (timeRec(1)-phase(listId))/freq(listId)
128            i = INT( timeRec(1) )
129            IF ( timeRec(1).LT.0. ) THEN
130              tmpLoc = FLOAT(i)
131              IF ( timeRec(1).NE.tmpLoc ) i = i - 1
132            ENDIF
133            timeRec(1) = phase(listId) + freq(listId)*FLOAT(i)
134    c       if ( listId.eq.2 ) write(0,*) 'f',i,timeRec(1)/deltaTClock
135            timeRec(1) = MAX( timeRec(1), startTime )
136    
137    C     b) round off to nearest multiple of time-step:
138            timeRec(1) = (timeRec(1)-baseTime)/deltaTClock
139            i = NINT( timeRec(1) )
140    C     if just half way, NINT will return the next time-step: correct this
141            tmpLoc = FLOAT(i) - 0.5 _d 0
142            IF ( timeRec(1).EQ.tmpLoc ) i = i - 1
143            timeRec(1) = baseTime + deltaTClock*FLOAT(i)
144    c       if ( listId.eq.2 ) write(0,*) i,timeRec(1)/deltaTClock
145          ENDIF
146    C--   Convert time to iteration number (debug)
147    c     DO i=1,nTimRec
148    c       timeRec(i) = timeRec(i)/deltaTClock
149    c     ENDDO
150    
151  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
152    C-- this is a trick to reverse the order of the loops on md (= field)
153    C   and lm (= averagePeriod): binary output: lm loop inside md loop ;
154    C                                 mnc ouput: md loop inside lm loop.
155        IF (useMNC .AND. diag_mnc) THEN        IF (useMNC .AND. diag_mnc) THEN
156          DO i = 1,MAX_LEN_FNAM          jjMx = averageCycle(listId)
157            diag_mnc_bn(i:i) = ' '          llMx = 1
158          ENDDO        ELSE
159          DO i = 1,NLEN          jjMx = 1
160            dn_blnk(i:i) = ' '          llMx = averageCycle(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)  
   
         CALL MNC_CW_DEL_VNAME('level_indicies', myThid)  
         CALL MNC_CW_DEL_GNAME('diag_levels', myThid)  
161        ENDIF        ENDIF
162          DO jj=1,jjMx
163    
164           IF (useMNC .AND. diag_mnc) THEN
165             misValLoc = undefRL
166             IF ( misvalFlt(listId).NE.UNSET_RL )
167         &        misValLoc = misvalFlt(listId)
168             CALL DIAGNOSTICS_MNC_SET(
169         I                    nLevOutp, listId, jj,
170         O                    diag_mnc_bn, useMissingValue,
171         I                    misValLoc, myTime, myIter, myThid )
172           ENDIF
173  #endif /*  ALLOW_MNC  */  #endif /*  ALLOW_MNC  */
174    
175        do n = 1,nfields(listnum)  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
176          do m = 1,ndiagt  
177            if( flds(n,listnum).eq.cdiag(m) .and. idiag(m).ne.0 ) then         DO md = 1,nfields(listId)
178              parms1 = gdiag(m)          ndId = jdiag(md,listId)
179              if (ndiag(m).ne.0.and.parse1(5).ne.'D') then          gcode = gdiag(ndId)(1:10)
180                if( myThid.eq.1 )          mate = 0
181       &             write(6,2000) m,cdiag(m),ndiag(m),gdiag(m)          mVec = 0
182                if (parse1(5).ne.'C') then          mDbl = 0
183            IF ( gcode(5:5).EQ.'C' ) THEN
184                  do k = 1,nlevels(listnum)  C-      Check for Mate of a Counter Diagnostic
185                    call getdiag (levs(k,listnum),m,undef,qtmp1,myThid)             mate = hdiag(ndId)
186                  enddo          ELSEIF ( gcode(5:5).EQ.'P' ) THEN
187    C-      Also load the mate (if stored) for Post-Processing
188  C               Check for Mate of a Vector Diagnostic             nn = ndId
189  C               -------------------------------------             DO WHILE ( gdiag(nn)(5:5).EQ.'P' )
190                  if ( parse1(1).eq.'U' .or. parse1(1).eq.'V' ) then               nn = hdiag(nn)
191                    read (mate_index,100) mate             ENDDO
192                    if( idiag(mate).ne.0 ) then             IF ( mdiag(md,listId).NE.0 ) mDbl = hdiag(nn)
193                      if( myThid.eq.1 )          ELSEIF ( gcode(1:1).EQ.'U' .OR. gcode(1:1).EQ.'V' ) THEN
194       &                   write(6,2001) cdiag(m),mate,cdiag(mate)  C-      Check for Mate of a Vector Diagnostic
195                    else             mVec = hdiag(ndId)
196                      if( myThid.eq.1 )          ENDIF
197       &                   write(6,2002) cdiag(m),mate,cdiag(mate)          IF ( idiag(md,listId).NE.0 .AND. gcode(5:5).NE.'D' ) THEN
198                    endif  C--     Start processing 1 Fld :
199                  endif  #ifdef ALLOW_MNC
200                             DO ll=1,llMx
201                else            lm = jj+ll-1
202    #else
203  C               Check for Mate of a Counter Diagnostic           DO lm=1,averageCycle(listId)
204  C               --------------------------------------  #endif
                 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  
205    
206                endif            ip = ABS(idiag(md,listId)) + kdiag(ndId)*(lm-1)
207              endif            im = mdiag(md,listId)
208              IF (mate.GT.0) im = im + kdiag(mate)*(lm-1)
209              IF (mDbl.GT.0) im = im + kdiag(mDbl)*(lm-1)
210              IF (mVec.GT.0) im = im + kdiag(mVec)*(lm-1)
211    
212              IF ( ndiag(ip,1,1).EQ.0 ) THEN
213    C-        Empty diagnostics case :
214    
215                _BEGIN_MASTER( myThid )
216                WRITE(msgBuf,'(A,I10)')
217         &        '- WARNING - from DIAGNOSTICS_OUT at iter=', myIter
218                CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
219         &                          SQUEEZE_RIGHT, myThid)
220                WRITE(msgBuf,'(A,I6,3A,I4,2A)')
221         &       '- WARNING -   diag.#',ndId, ' : ',flds(md,listId),
222         &       ' (#',md,' ) in outp.Stream: ',fnames(listId)
223                CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
224         &                          SQUEEZE_RIGHT, myThid)
225                IF ( averageCycle(listId).GT.1 ) THEN
226                 WRITE(msgBuf,'(A,2(I3,A))')
227         &        '- WARNING -   has not been filled (ndiag(lm=',lm,')=',
228         &                                            ndiag(ip,1,1), ' )'
229                ELSE
230                 WRITE(msgBuf,'(A,2(I3,A))')
231         &        '- WARNING -   has not been filled (ndiag=',
232         &                                            ndiag(ip,1,1), ' )'
233                ENDIF
234                CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
235         &                          SQUEEZE_RIGHT, myThid)
236                WRITE(msgBuf,'(A)')
237         &       'WARNING DIAGNOSTICS_OUT  => write ZEROS instead'
238                CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
239         &                          SQUEEZE_RIGHT, myThid)
240                _END_MASTER( myThid )
241                DO bj = myByLo(myThid), myByHi(myThid)
242                  DO bi = myBxLo(myThid), myBxHi(myThid)
243                    DO k = 1,nLevOutp
244                      DO j = 1-OLy,sNy+OLy
245                        DO i = 1-OLx,sNx+OLx
246                          qtmp1(i,j,k,bi,bj) = 0. _d 0
247                        ENDDO
248                      ENDDO
249                    ENDDO
250                  ENDDO
251                ENDDO
252    
253              ELSE
254    C-        diagnostics is not empty :
255    
256                IF ( debugLevel.GE.debLevB .AND. myThid.EQ.1 ) THEN
257                  IF ( gcode(5:5).EQ.'P' ) THEN
258                   WRITE(ioUnit,'(A,I6,7A,I8,2A)')
259         &         ' Post-Processing Diag # ', ndId, '  ', cdiag(ndId),
260         &         '   Parms: ',gdiag(ndId)
261                   IF ( mDbl.EQ.0 ) THEN
262                    WRITE(ioUnit,'(2(3A,I6,A,I8))') '   from diag: ',
263         &            cdiag(nn), ' (#', nn, ') Cnt=', ndiag(ip,1,1)
264                   ELSE
265                    WRITE(ioUnit,'(2(3A,I6,A,I8))') '   from diag: ',
266         &            cdiag(nn), ' (#', nn, ') Cnt=', ndiag(ip,1,1),
267         &          ' and diag: ',
268         &            cdiag(mDbl),' (#',mDbl,') Cnt=',ndiag(im,1,1)
269                   ENDIF
270                  ELSE
271                   WRITE(ioUnit,'(A,I6,3A,I8,2A)')
272         &         ' Computing Diagnostic # ', ndId, '  ', cdiag(ndId),
273         &         '     Counter:',ndiag(ip,1,1),'   Parms: ',gdiag(ndId)
274                  ENDIF
275                  IF ( mate.GT.0 ) THEN
276                   WRITE(ioUnit,'(3A,I6,2A)')
277         &         '       use Counter Mate for  ', cdiag(ndId),
278         &         '     Diagnostic # ',mate, '  ', cdiag(mate)
279                  ELSEIF ( mVec.GT.0 ) THEN
280                    IF ( im.GT.0 .AND. ndiag(MAX(1,im),1,1).GT.0 ) THEN
281                     WRITE(ioUnit,'(3A,I6,3A)')
282         &             '           Vector  Mate for  ', cdiag(ndId),
283         &             '     Diagnostic # ',mVec, '  ', cdiag(mVec),
284         &             ' exists '
285                    ELSE
286                     WRITE(ioUnit,'(3A,I6,3A)')
287         &             '           Vector  Mate for  ', cdiag(ndId),
288         &             '     Diagnostic # ',mVec, '  ', cdiag(mVec),
289         &             ' not enabled'
290                    ENDIF
291                  ENDIF
292                ENDIF
293    
294  #ifdef ALLOW_MDSIO              IF ( fflags(listId)(2:2).EQ.' ' ) THEN
295  C           Prepare for mdsio optionality  C-       get only selected levels:
296              IF (diag_mdsio) THEN                DO bj = myByLo(myThid), myByHi(myThid)
297                call mdswritefield_new(fn,writeBinaryPrec,glf,'RL',                 DO bi = myBxLo(myThid), myBxHi(myThid)
298       &             Nr+Nrphys,nlevels(listnum),qtmp1,n,myIter,myThid)                  DO k = 1,nlevels(listId)
299                      kLev = NINT(levs(k,listId))
300                      CALL DIAGNOSTICS_GET_DIAG(
301         I                         kLev, undefRL,
302         O                         qtmp1(1-OLx,1-OLy,k,bi,bj),
303         I                         ndId, mate, ip, im, bi, bj, myThid )
304                    ENDDO
305                   ENDDO
306                  ENDDO
307                  IF ( mDbl.GT.0 ) THEN
308                   DO bj = myByLo(myThid), myByHi(myThid)
309                    DO bi = myBxLo(myThid), myBxHi(myThid)
310                     DO k = 1,nlevels(listId)
311                      kLev = NINT(levs(k,listId))
312                      CALL DIAGNOSTICS_GET_DIAG(
313         I                         kLev, undefRL,
314         O                         qtmp2(1-OLx,1-OLy,k,bi,bj),
315         I                         mDbl, 0, im, 0, bi, bj, myThid )
316                     ENDDO
317                    ENDDO
318                   ENDDO
319                  ENDIF
320                ELSE
321    C-       get all the levels (for vertical post-processing)
322                  DO bj = myByLo(myThid), myByHi(myThid)
323                   DO bi = myBxLo(myThid), myBxHi(myThid)
324                      CALL DIAGNOSTICS_GET_DIAG(
325         I                         0, undefRL,
326         O                         qtmp1(1-OLx,1-OLy,1,bi,bj),
327         I                         ndId, mate, ip, im, bi, bj, myThid )
328                   ENDDO
329                  ENDDO
330                  IF ( mDbl.GT.0 ) THEN
331                   DO bj = myByLo(myThid), myByHi(myThid)
332                    DO bi = myBxLo(myThid), myBxHi(myThid)
333                     DO k = 1,nlevels(listId)
334                      CALL DIAGNOSTICS_GET_DIAG(
335         I                         0, undefRL,
336         O                         qtmp2(1-OLx,1-OLy,k,bi,bj),
337         I                         mDbl, 0, im, 0, bi, bj, myThid )
338                     ENDDO
339                    ENDDO
340                   ENDDO
341                  ENDIF
342              ENDIF              ENDIF
 #endif /*  ALLOW_MDSIO  */  
343    
344  #ifdef ALLOW_MNC  C-----------------------------------------------------------------------
345              IF (useMNC .AND. diag_mnc) THEN  C--     Apply specific post-processing (e.g., interpolate) before output
346    C-----------------------------------------------------------------------
347                IF ( fflags(listId)(2:2).EQ.'P' ) THEN
348    C-          Do vertical interpolation:
349                 IF ( fluidIsAir ) THEN
350    C jmc: for now, this can only work in an atmospheric set-up (fluidIsAir);
351                  CALL DIAGNOSTICS_INTERP_VERT(
352         I                         listId, md, ndId, ip, im, lm,
353         U                         qtmp1, qtmp2,
354         I                         undefRL, myTime, myIter, myThid )
355                 ELSE
356                   WRITE(msgBuf,'(2A)') 'DIAGNOSTICS_OUT: ',
357         &           'INTERP_VERT not allowed in this config'
358                   CALL PRINT_ERROR( msgBuf , myThid )
359                   STOP 'ABNORMAL END: S/R DIAGNOSTICS_OUT'
360                 ENDIF
361                ENDIF
362                IF ( fflags(listId)(2:2).EQ.'I' ) THEN
363    C-          Integrate vertically: for now, output field has just 1 level:
364                  CALL DIAGNOSTICS_SUM_LEVELS(
365         I                         listId, md, ndId, ip, im, lm,
366         U                         qtmp1,
367         I                         undefRL, myTime, myIter, myThid )
368                ENDIF
369                IF ( gcode(5:5).EQ.'P' ) THEN
370    C-          Do Post-Processing:
371                 IF ( flds(md,listId).EQ.'PhiVEL  '
372    c    &       .OR. flds(md,listId).EQ.'PsiVEL  '
373         &          ) THEN
374                  CALL DIAGNOSTICS_CALC_PHIVEL(
375         I                         listId, md, ndId, ip, im, lm,
376         U                         qtmp1, qtmp2,
377         I                         myTime, myIter, myThid )
378                 ELSE
379                   WRITE(msgBuf,'(2A)') 'DIAGNOSTICS_OUT: ',
380         &           'unknown Processing method for diag="',cdiag(ndId),'"'
381                   CALL PRINT_ERROR( msgBuf , myThid )
382                   STOP 'ABNORMAL END: S/R DIAGNOSTICS_OUT'
383                 ENDIF
384                ENDIF
385    
386                _BEGIN_MASTER( myThid )  C--     End of empty diag / not-empty diag block
387              ENDIF
388    
389                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)  
390    
391                CALL MNC_CW_RL_W('D',diag_mnc_bn,0,0,  C-        write to binary file, using MDSIO pkg:
392       &             cdiag(m), qtmp1, myThid)            IF ( diag_mdsio ) THEN
393                nRec = lm + (md-1)*averageCycle(listId)
394    C           default precision for output files
395                prec = writeBinaryPrec
396    C           fFlag(1)=R(or D): force it to be 32-bit(or 64) precision
397                IF ( fflags(listId)(1:1).EQ.'R' ) prec = precFloat32
398                IF ( fflags(listId)(1:1).EQ.'D' ) prec = precFloat64
399    C         a hack not to write meta files now: pass -nRec < 0 to MDS_WRITE S/R
400                CALL WRITE_REC_LEV_RL(
401         I                            fn, prec,
402         I                            NrMax, 1, nLevOutp,
403         I                            qtmp1, -nRec, myIter, myThid )
404              ENDIF
405    
406                CALL MNC_CW_DEL_VNAME(cdiag(m), myThid)  #ifdef ALLOW_MNC
407                CALL MNC_CW_DEL_GNAME('diag_cw_temp', myThid)            IF (useMNC .AND. diag_mnc) THEN
408                CALL DIAGNOSTICS_MNC_OUT(
409         I                       NrMax, nLevOutp, listId, ndId,
410         I                       diag_mnc_bn,
411         I                       useMissingValue, misValLoc,
412         I                       qtmp1,
413         I                       myTime, myIter, myThid )
414              ENDIF
415    #endif /*  ALLOW_MNC  */
416    
417                _END_MASTER( myThid )  C--      end loop on lm (or ll if ALLOW_MNC) counter
418             ENDDO
419    C--     end of Processing Fld # md
420            ENDIF
421           ENDDO
422    
423              ENDIF  #ifdef ALLOW_MNC
424  #endif /*  ALLOW_MNC  */  C--   end loop on jj counter
425          ENDDO
426    #endif
427    
428    #ifdef ALLOW_MDSIO
429          IF (diag_mdsio) THEN
430    C-    Note: temporary: since it is a pain to add more arguments to
431    C     all MDSIO S/R, uses instead this specific S/R to write only
432    C     meta files but with more informations in it.
433                glf = globalFiles
434                nRec = nfields(listId)*averageCycle(listId)
435                CALL MDS_WR_METAFILES(fn, prec, glf, .FALSE.,
436         &              0, 0, nLevOutp, ' ',
437         &              nfields(listId), flds(1,listId), nTimRec, timeRec,
438         &              nRec, myIter, myThid)
439          ENDIF
440    #endif /*  ALLOW_MDSIO  */
441    
442          RETURN
443          END
444    
           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  
                                                                       
445  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.54

  ViewVC Help
Powered by ViewVC 1.1.22