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

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

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

revision 1.5 by molod, Thu Feb 26 22:20:36 2004 UTC revision 1.25 by jmc, Tue Feb 5 15:31:19 2008 UTC
# Line 1  Line 1 
1        subroutine getdiag (myThid,lev,ipoint,undef,qtmp)  C $Header$
2  C***********************************************************************          C $Name$
3  C  PURPOSE                                                                        
4    #include "DIAG_OPTIONS.h"
5    
6    C--   File diagnostics_utils.F: General purpose support routines
7    C--    Contents:
8    C--    o GETDIAG
9    C--    o DIAGNOSTICS_COUNT
10    C--    o DIAGS_MK_UNITS (Function)
11    C--    o DIAGS_MK_TITLE (Function)
12    C--    o DIAGNOSTICS_GET_POINTERS
13    
14    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
15    CBOP 0
16    C     !ROUTINE: GETDIAG
17    
18    C     !INTERFACE:
19          SUBROUTINE GETDIAG(
20         I                    levreal, undef,
21         O                    qtmp,
22         I                    ndId, mate, ip, im, bi, bj, myThid )
23    
24    C     !DESCRIPTION:
25  C     Retrieve averaged model diagnostic  C     Retrieve averaged model diagnostic
 C  INPUT:                                                                        
 C     lev ..... Diagnostic LEVEL  
 C  ipoint ..... DIAGNOSTIC NUMBER FROM MENU                                      
 C   undef ..... UNDEFINED VALUE                                                  
 C      bi ..... X-direction process(or) number  
 C      bj ..... Y-direction process(or) number  
 C                                                                                
 C  OUTPUT:                                                                        
 C    qtmp ..... AVERAGED DIAGNOSTIC QUANTITY  
 C                                                                                
 C***********************************************************************          
       implicit none  
26    
27    C     !USES:
28          IMPLICIT NONE
29  #include "EEPARAMS.h"  #include "EEPARAMS.h"
 #include "CPP_OPTIONS.h"  
30  #include "SIZE.h"  #include "SIZE.h"
31    #include "DIAGNOSTICS_SIZE.h"
32    #include "DIAGNOSTICS.h"
33    
34  #ifdef ALLOW_FIZHI  C     !INPUT PARAMETERS:
35  #include "fizhi_SIZE.h"  C     levreal :: Diagnostic LEVEL
36  #else  C     undef   :: UNDEFINED VALUE
37         integer Nrphys  C     ndId    :: DIAGNOSTIC NUMBER FROM MENU
38         parameter (Nrphys=1)  C     mate    :: counter DIAGNOSTIC NUMBER if any ; 0 otherwise
39  #endif  C     ip      :: pointer to storage array location for diag.
40    C     im      :: pointer to storage array location for mate
41  #include "diagnostics_SIZE.h"  C     bi      :: X-direction tile number
42  #include "diagnostics.h"  C     bj      :: Y-direction tile number
43    C     myThid  :: my thread Id number
44        integer myThid,lev,ipoint        _RL levreal
45        _RL undef        _RL undef
46        _RL qtmp(1-OLx:sNx+Olx,1-Oly:sNy+Oly,Nr+Nrphys,Nsx,Nsy)        INTEGER ndId, mate, ip, im
47          INTEGER bi,bj, myThid
48    
49        _RL factor  C     !OUTPUT PARAMETERS:
50        integer i,j,ipnt,klev  C     qtmp    ..... AVERAGED DIAGNOSTIC QUANTITY
51        integer bi,bj        _RL qtmp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
52    CEOP
53    
54        if (ipoint.lt.1) go to 999  C     !LOCAL VARIABLES:
55          _RL factor
56          INTEGER i, j, ipnt,ipCt
57          INTEGER lev, levCt, klev
58    
59        klev = kdiag(ipoint)        IF (ndId.GE.1) THEN
60        if(klev.ge.lev) then         lev = NINT(levreal)
61        ipnt = idiag(ipoint) + lev - 1         klev = kdiag(ndId)
62        factor = 1.0         IF (lev.LE.klev) THEN
63        if(ndiag(ipoint).ne.0) factor = 1.0/ndiag(ipoint)  
64            IF ( mate.EQ.0 ) THEN
65        do bj=myByLo(myThid), myByHi(myThid)  C-      No counter diagnostics => average = Sum / ndiag :
66        do bi=myBxLo(myThid), myBxHi(myThid)  
67              ipnt = ip + lev - 1
68        do j = 1,sNy            factor = FLOAT(ndiag(ip,bi,bj))
69        do i = 1,sNx            IF (ndiag(ip,bi,bj).NE.0) factor = 1. _d 0 / factor
70         if( qdiag(i,j,ipnt,bi,bj).ne.undef ) then  
71          qtmp(i,j,lev,bi,bj) = qdiag(i,j,ipnt,bi,bj)*factor            DO j = 1,sNy+1
72         else              DO i = 1,sNx+1
73          qtmp(i,j,lev,bi,bj) = undef                IF ( qdiag(i,j,ipnt,bi,bj) .LE. undef ) THEN
74         endif                  qtmp(i,j) = qdiag(i,j,ipnt,bi,bj)*factor
75        enddo                ELSE
76        enddo                  qtmp(i,j) = undef
77                  ENDIF
78        enddo              ENDDO
79        enddo            ENDDO
80    
81        endif          ELSE
82    C-      With counter diagnostics => average = Sum / counter:
83   999  return  
84        end            ipnt = ip + lev - 1
85              levCt= MIN(lev,kdiag(mate))
86        subroutine getdiag2 (myThid,lev,ipoint,undef,qtmp)            ipCt = im + levCt - 1
87  C***********************************************************************                    DO j = 1,sNy+1
88  C  PURPOSE                                                                                    DO i = 1,sNx+1
89  C     Retrieve averaged model diagnostic                IF ( qdiag(i,j,ipCt,bi,bj) .NE. 0. ) THEN
90  C  INPUT:                                                                                        qtmp(i,j) = qdiag(i,j,ipnt,bi,bj)
91  C     lev ..... Diagnostic LEVEL       &                    / qdiag(i,j,ipCt,bi,bj)
92  C  ipoint ..... DIAGNOSTIC NUMBER FROM MENU                                                    ELSE
93  C   undef ..... UNDEFINED VALUE                                                                  qtmp(i,j) = undef
94  C                                                                                              ENDIF
95  C  OUTPUT:                                                                                    ENDDO
96  C    qtmp ..... AVERAGED DIAGNOSTIC QUANTITY            ENDDO
 C                                                                                
 C***********************************************************************          
       implicit none  
97    
98  #include "EEPARAMS.h"          ENDIF
99  #include "CPP_OPTIONS.h"         ENDIF
100  #include "SIZE.h"        ENDIF
101    
102  #ifdef ALLOW_FIZHI        RETURN
103  #include "fizhi_SIZE.h"        END
 #else  
        integer Nrphys  
        parameter (Nrphys=1)  
 #endif  
104    
105  #include "diagnostics_SIZE.h"  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
 #include "diagnostics.h"  
106    
107        integer myThid,lev,ipoint  CBOP 0
108        _RL undef  C     !ROUTINE: DIAGNOSTICS_COUNT
109        _RL qtmp(1-OLx:sNx+Olx,1-Oly:sNy+Oly,Nr+Nrphys,Nsx,Nsy)  C     !INTERFACE:
110          SUBROUTINE DIAGNOSTICS_COUNT (chardiag,
111         I                              biArg, bjArg, myThid)
112    
113        integer i,j,ipnt,klev  C     !DESCRIPTION:
114        integer bi,bj  C***********************************************************************
115    C   routine to increment the diagnostic counter only
116    C***********************************************************************
117    C     !USES:
118          IMPLICIT NONE
119    
120        if (ipoint.lt.1) go to 999  C     == Global variables ===
121    #include "EEPARAMS.h"
122    #include "SIZE.h"
123    #include "DIAGNOSTICS_SIZE.h"
124    #include "DIAGNOSTICS.h"
125    
126        klev = kdiag(ipoint)  C     !INPUT PARAMETERS:
       if(klev.ge.lev) then  
       ipnt = idiag(ipoint) + lev - 1  
   
       do bj=myByLo(myThid), myByHi(myThid)  
       do bi=myBxLo(myThid), myBxHi(myThid)  
   
       do j = 1,sNy  
       do i = 1,sNx  
        if( qdiag(i,j,ipnt,bi,bj).ne.undef ) then  
         qtmp(i,j,lev,bi,bj) = qdiag(i,j,ipnt,bi,bj)  
        else  
         qtmp(i,j,lev,bi,bj) = undef  
        endif  
       enddo  
       enddo  
   
       enddo  
       enddo  
   
       endif  
   
  999  return  
       end  
       subroutine clrindx (myThid,listnum)  
127  C***********************************************************************  C***********************************************************************
128  C  C  Arguments Description
129  C  PURPOSE  C  ----------------------
130  C     DRIVER TO CLEAR DIAGNOSTICS SPECIFIED IN DIAGNOSTIC INDEX LIST  C     chardiag :: Character expression for diag to increment the counter
131  C  C     biArg    :: X-direction tile number, or 0 if called outside bi,bj loops
132  C  ARGUMENT DESCRIPTION  C     bjArg    :: Y-direction tile number, or 0 if called outside bi,bj loops
133  C     listnum ....  diagnostics list number  C     myThid   :: my thread Id number
 C  
134  C***********************************************************************  C***********************************************************************
135          CHARACTER*8 chardiag
136          INTEGER biArg, bjArg
137          INTEGER myThid
138    CEOP
139    
140    C     !LOCAL VARIABLES:
141    C ===============
142          INTEGER m, n
143          INTEGER bi, bj
144          INTEGER ipt
145    c     CHARACTER*(MAX_LEN_MBUF) msgBuf
146    
147    C--   Run through list of active diagnostics to find which counter
148    C     to increment (needs to be a valid & active diagnostic-counter)
149          DO n=1,nlists
150           DO m=1,nActive(n)
151            IF ( chardiag.EQ.flds(m,n) .AND. idiag(m,n).GT.0 ) THEN
152             ipt = idiag(m,n)
153             IF (ndiag(ipt,1,1).GE.0) THEN
154    C-    Increment the counter for the diagnostic
155              IF ( biArg.EQ.0 .AND. bjArg.EQ.0 ) THEN
156               DO bj=myByLo(myThid), myByHi(myThid)
157                DO bi=myBxLo(myThid), myBxHi(myThid)
158                 ndiag(ipt,bi,bj) = ndiag(ipt,bi,bj) + 1
159                ENDDO
160               ENDDO
161              ELSE
162                 bi = MIN(biArg,nSx)
163                 bj = MIN(bjArg,nSy)
164                 ndiag(ipt,bi,bj) = ndiag(ipt,bi,bj) + 1
165              ENDIF
166    C-    Increment is done
167             ENDIF
168            ENDIF
169           ENDDO
170          ENDDO
171    
172          RETURN
173          END
174    
175    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
176    
177        implicit none  CBOP 0
178    C     !ROUTINE: DIAGS_MK_UNITS
179    
180    C     !INTERFACE:
181          CHARACTER*16 FUNCTION DIAGS_MK_UNITS(
182         I                            diagUnitsInPieces, myThid )
183    
184    C     !DESCRIPTION:
185    C     *==========================================================*
186    C     | FUNCTION DIAGS_MK_UNITS
187    C     | o Return the diagnostic units string (16c) removing
188    C     |   blanks from the input string
189    C     *==========================================================*
190    
191    C     !USES:
192          IMPLICIT NONE
193  #include "EEPARAMS.h"  #include "EEPARAMS.h"
 #include "CPP_OPTIONS.h"  
 #include "SIZE.h"  
194    
195  #ifdef ALLOW_FIZHI  C     !INPUT PARAMETERS:
196  #include "fizhi_SIZE.h"  C     diagUnitsInPieces :: string for diagnostic units: in several
197  #else  C                          pieces, with blanks in between
198         integer Nrphys  C     myThid            ::  my thread Id number
199         parameter (Nrphys=1)        CHARACTER*(*) diagUnitsInPieces
200  #endif        INTEGER      myThid
201    CEOP
202  #include "diagnostics_SIZE.h"  
203  #include "diagnostics.h"  C     !LOCAL VARIABLES:
204          CHARACTER*(MAX_LEN_MBUF) msgBuf
205        integer myThid, listnum        INTEGER i,j,n
206    
207        integer m, n        DIAGS_MK_UNITS = '          '
208        character*8 parms1        n = LEN(diagUnitsInPieces)
209        character*1 parse1(8)  
210        character*3 mate_index        j = 0
211        integer mate        DO i=1,n
212           IF (diagUnitsInPieces(i:i) .NE. ' ' ) THEN
213        equivalence (     parms1 , parse1(1) )           j = j+1
214        equivalence ( mate_index , parse1(6) )           IF ( j.LE.16 ) DIAGS_MK_UNITS(j:j) = diagUnitsInPieces(i:i)
215           ENDIF
216        do n=1,nfields(listnum)        ENDDO
217         do m=1,ndiagt  
218          if( flds(n,listnum).eq.cdiag(m) .and. idiag(m).ne.0 ) then        IF ( j.GT.16 ) THEN
219           call clrdiag (myThid,m)           WRITE(msgBuf,'(2A,I4,A)') '**WARNING** ',
220         &   'DIAGS_MK_UNITS: too long (',j,' >16) input string'
221  c Check for Counter Diagnostic          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
222  c ----------------------------       &       SQUEEZE_RIGHT , myThid)
223           parms1 =  gdiag(m)           WRITE(msgBuf,'(3A)') '**WARNING** ',
224           if( parse1(5).eq.'C' ) then       &   'DIAGS_MK_UNITS: input=', diagUnitsInPieces
225            read (mate_index,100) mate          CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
226            call clrdiag (myThid,mate)       &       SQUEEZE_RIGHT , myThid)
227           endif        ENDIF
228          endif  
229         enddo        RETURN
230        enddo        END
231                      
232    100 format(i3)  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
233        RETURN        
234        END            CBOP 0
235    C     !ROUTINE: DIAGS_MK_TITLE
236    
237        subroutine clrdiag (myThid,index)  C     !INTERFACE:
238  C***********************************************************************                CHARACTER*80 FUNCTION DIAGS_MK_TITLE(
239  C  PURPOSE                                                                             I                            diagTitleInPieces, myThid )
240  C     ZERO OUT MODEL DIAGNOSTIC ARRAY ELEMENTS  
241  C***********************************************************************          C     !DESCRIPTION:
242                                                                                    C     *==========================================================*
243        implicit none  C     | FUNCTION DIAGS_MK_TITLE
244    C     | o Return the diagnostic title string (80c) removing
245    C     |   consecutive blanks from the input string
246    C     *==========================================================*
247    
248    C     !USES:
249          IMPLICIT NONE
250  #include "EEPARAMS.h"  #include "EEPARAMS.h"
 #include "CPP_OPTIONS.h"  
 #include "SIZE.h"  
251    
252  #ifdef ALLOW_FIZHI  C     !INPUT PARAMETERS:
253  #include "fizhi_SIZE.h"  C     diagTitleInPieces :: string for diagnostic units: in several
254  #else  C                          pieces, with blanks in between
255         integer Nrphys  C     myThid            ::  my Thread Id number
256         parameter (Nrphys=1)        CHARACTER*(*) diagTitleInPieces
257  #endif        INTEGER      myThid
258    CEOP
259  #include "diagnostics_SIZE.h"  
260  #include "diagnostics.h"  C     !LOCAL VARIABLES:
261          CHARACTER*(MAX_LEN_MBUF) msgBuf
262        integer myThid, index        LOGICAL flag
263          INTEGER i,j,n
264        integer bi,bj  
265        integer i,j,k  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
266    
267  C **********************************************************************                DIAGS_MK_TITLE = '                                        '
268  C ****              SET DIAGNOSTIC AND COUNTER TO ZERO              ****               &               //'                                        '
269  C **********************************************************************                n = LEN(diagTitleInPieces)
270                                                                                    
271        do bj=myByLo(myThid), myByHi(myThid)        j = 0
272        do bi=myBxLo(myThid), myBxHi(myThid)        flag = .FALSE.
273         do k = 1,kdiag(index)        DO i=1,n
274          do j = 1,sNy         IF (diagTitleInPieces(i:i) .NE. ' ' ) THEN
275          do i = 1,sNx           IF ( flag ) THEN
276           qdiag(i,j,idiag(index)+k-1,bi,bj) = 0.0             j = j+1
277          enddo             IF (j.LE.80) DIAGS_MK_TITLE(j:j) = ' '
278          enddo           ENDIF
279         enddo           j = j+1
280        enddo           IF ( j.LE.80 ) DIAGS_MK_TITLE(j:j) = diagTitleInPieces(i:i)
281        enddo           flag = .FALSE.
282           ELSE
283             flag = j.GE.1
284           ENDIF
285          ENDDO
286    
287          IF ( j.GT.80 ) THEN
288             WRITE(msgBuf,'(2A,I4,A)') '**WARNING** ',
289         &   'DIAGS_MK_TITLE: too long (',j,' >80) input string'
290            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
291         &       SQUEEZE_RIGHT , myThid)
292             WRITE(msgBuf,'(3A)') '**WARNING** ',
293         &   'DIAGS_MK_TITLE: input=', diagTitleInPieces
294            CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
295         &       SQUEEZE_RIGHT , myThid)
296          ENDIF
297    
298        ndiag(index) = 0        RETURN
299          END
300    
301        return  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
       end  
302    
303        subroutine setdiag (myThid,num,ndiagmx)  CBOP 0
304  C***********************************************************************  C     !ROUTINE: DIAGNOSTICS_GET_POINTERS
305  C  C     !INTERFACE:
306  C  PURPOSE        SUBROUTINE DIAGNOSTICS_GET_POINTERS(
307  C     SET POINTER LOCATIONS, NAMES, LEVELS and TITLES FOR DIAGNOSTIC NUM       I                       diagName, listId,
308  C       O                       ndId, ip,
309  C***********************************************************************       I                       myThid )
310    
311    C     !DESCRIPTION:
312    C     *================================================================*
313    C     | o Returns the diagnostic Id number and diagnostic
314    C     |   pointer to storage array for a specified diagnostic.
315    C     *================================================================*
316    C     | Note: A diagnostics field can be stored multiple times
317    C     |       (for different output frequency,phase, ...).
318    C     | operates in 2 ways:
319    C     | o listId =0 => find 1 diagnostics Id & pointer which name matches.
320    C     | o listId >0 => find the unique diagnostic Id & pointer with
321    C     |      the right name and same output time as "listId" output-list
322    C     | o return ip=0 if did not find the right diagnostic;
323    C     |   (ndId <>0 if diagnostic exist but output time does not match)
324    C     *================================================================*
325    
326        implicit none  C     !USES:
327  #include "CPP_OPTIONS.h"        IMPLICIT NONE
328    #include "EEPARAMS.h"
329  #include "SIZE.h"  #include "SIZE.h"
330    #include "DIAGNOSTICS_SIZE.h"
331    #include "DIAGNOSTICS.h"
332    
333  #ifdef ALLOW_FIZHI  C     !INPUT PARAMETERS:
334  #include "fizhi_SIZE.h"  C     diagName :: diagnostic identificator name (8 characters long)
335  #else  C     listId   :: list number that specify the output frequency
336         integer Nrphys  C     myThid   :: my Thread Id number
337         parameter (Nrphys=1)  C     !OUTPUT PARAMETERS:
338  #endif  C     ndId     :: diagnostics  Id number (in available diagnostics list)
339    C     ip       :: diagnostics  pointer to storage array
340  #include "diagnostics_SIZE.h"  
341  #include "diagnostics.h"  
342          CHARACTER*8 diagName
343        integer num,myThid,ndiagmx        INTEGER listId
344        integer ipointer        INTEGER ndId, ip
345          INTEGER myThid
346        DATA IPOINTER / 1 /  CEOP
347    
348        character*8 parms1  C     !LOCAL VARIABLES:
349        character*1 parse1(8)        INTEGER n,m
350        character*3 mate_index  
351        integer     mate        ip   = 0
352          ndId = 0
353        equivalence (     parms1 , parse1(1) )  
354        equivalence ( mate_index , parse1(6) )        IF ( listId.LE.0 ) THEN
355    C--   select the 1rst one which name matches:
356  C **********************************************************************  
357  C ****                SET POINTERS FOR DIAGNOSTIC NUM               ****  C-    search for this diag. in the active 2D/3D diagnostics list
358  C **********************************************************************          DO n=1,nlists
359             DO m=1,nActive(n)
360        parms1 = gdiag(num)             IF ( ip.EQ.0 .AND. diagName.EQ.flds(m,n)
361         &                  .AND. idiag(m,n).NE.0 ) THEN
362        IF( IDIAG(NUM).EQ.0 ) THEN              ip   = ABS(idiag(m,n))
363          if(ndiagmx+kdiag(num).gt.numdiags) then              ndId = jdiag(m,n)
364            write(6,4000)num,cdiag(num)             ENDIF
365          else           ENDDO
366            IDIAG(NUM) = IPOINTER          ENDDO
367            IPOINTER   = IPOINTER + KDIAG(NUM)  
368            ndiagmx    = ndiagmx  + KDIAG(NUM)        ELSEIF ( listId.LE.nlists ) THEN
369            if(myThid.eq.1) WRITE(6,2000)KDIAG(NUM),NUM,CDIAG(NUM),ndiagmx  C--   select the unique diagnostic with output-time identical to listId
370          endif  
371        ELSE  C-    search for this diag. in the active 2D/3D diagnostics list
372            if(myThid.eq.1) WRITE(6,3000) NUM, CDIAG(NUM)          DO n=1,nlists
373        ENDIF           IF ( ip.EQ.0
374         &        .AND. freq(n) .EQ. freq(listId)
375         &        .AND. phase(n).EQ.phase(listId)
376         &        .AND. averageFreq(n) .EQ.averageFreq(listId)
377         &        .AND. averagePhase(n).EQ.averagePhase(listId)
378         &        .AND. averageCycle(n).EQ.averageCycle(listId)
379         &      ) THEN
380              DO m=1,nActive(n)
381               IF ( ip.EQ.0 .AND. diagName.EQ.flds(m,n)
382         &                  .AND. idiag(m,n).NE.0 ) THEN
383                ip   = ABS(idiag(m,n))
384                ndId = jdiag(m,n)
385               ENDIF
386              ENDDO
387             ELSEIF ( ip.EQ.0 ) THEN
388              DO m=1,nActive(n)
389               IF ( ip.EQ.0 .AND. diagName.EQ.flds(m,n)
390         &                  .AND. idiag(m,n).NE.0 ) THEN
391                ndId = jdiag(m,n)
392               ENDIF
393              ENDDO
394             ENDIF
395            ENDDO
396    
 c Check for Counter Diagnostic  
 c ----------------------------  
       if( parse1(5).eq.'C') then  
       read (mate_index,100) mate  
   
       IF( IDIAG(mate).EQ.0 ) THEN  
        if(ndiagmx+kdiag(num).gt.numdiags) then  
         write(6,5000)num,cdiag(num)  
        else  
         IDIAG(mate) = IPOINTER  
         IPOINTER    = IPOINTER + KDIAG(mate)  
         ndiagmx     = ndiagmx  + KDIAG(mate)  
         if(myThid.eq.1)WRITE(6,2000)KDIAG(mate),mate,CDIAG(mate),ndiagmx  
        endif  
397        ELSE        ELSE
398            if(myThid.eq.1) WRITE(6,3000) mate, CDIAG(mate)          STOP 'DIAGNOSTICS_GET_POINTERS: invalid listId number'
399        ENDIF        ENDIF
       endif  
400    
401        RETURN        RETURN
   
   100 format(i3)  
  2000 FORMAT(1X,'Allocating ',I2,' Level(s) for Diagnostic # ',I3,  
      .          ' (',A8,'),  Total Number of Diagnostics: ',I5)  
  3000 FORMAT(1X,'Diagnostic # ',I3,' (',A8,') has already been set')  
  4000 FORMAT(1X,'Unable to allocate space for Diagnostic # ',I3,  
      .                      ' (',A8,')')  
  5000 FORMAT(1X,'Unable to allocate space for Counter Diagnostic # ',  
      .    I3,' (',A8,')',' WARNING - Diag will not accumulate properly')  
402        END        END

Legend:
Removed from v.1.5  
changed lines
  Added in v.1.25

  ViewVC Help
Powered by ViewVC 1.1.22