[Search for users] [Overall Top Noters] [List of all Conferences] [Download this site]

Conference noted::hackers_v1

Title:-={ H A C K E R S }=-
Notice:Write locked - see NOTED::HACKERS
Moderator:DIEHRD::MORRIS
Created:Thu Feb 20 1986
Last Modified:Mon Aug 03 1992
Last Successful Update:Fri Jun 06 1997
Number of topics:680
Total number of notes:5456

524.0. "ANALYSE/DISK/USAGE DTR domain ??" by KAOFS::READ (Bob) Thu Jul 30 1987 18:50

    Does anyone have something that will read the output of
    ANALYSE/DISK/USAGE for disk tracking purposes?  I'd prefer a Datatrieve
    domain, but would settle for a programme or procedure ... 
    
    thanks,
    bob.
T.RTitleUserPersonal
Name
DateLines
524.1Yep, but what are you looking for?MONSTR::DUTKONestor Dutko, VMS/VAXclusters CSSEThu Jul 30 1987 22:152
     What type of output are you looking for?  I have something I wrote
     a while ago...
524.2KAOFS::READBobFri Jul 31 1987 17:5614
    I'm looking to be able to produce some sort of report in a flat
    file with <filename>, <allocation>, <file_owner> such that I can
    access it using Datatrieve.  So, a DTR domain would be really neat,
    or a programme that would produce a flat file that I could then
    define a domain for would be OK too.
    
    I have a user-type who wants to mung said data from a set of 25
    RA81s, to get some disk usage stats from our disk farm.  Obviously,
    I'd have to put <volnam> into each entry as well.
    
    Any and all info is appreciated!
    
    thanks,
    boob.
524.3$USGDEFMONSTR::DUTKONestor Dutko, VMS/VAXclusters CSSETue Aug 04 1987 11:5235
    Huh?  Now I am confused.  In the base note, you asked for a program
    which would give you a data file, on which Datatrieve could be used
    to gather usage statistics.
    
    Have you taken a look at the USAGE file?  The documentation for
    this beast is in the ANALYZE/DISK (ie VERIFY) utility.  The record
    layout is defined in $USGDEF in STARLET.MLB.  I have even enclosed
    the Datatrieve record definition here.  What else do you need? 
    
    I really can't see WHY you need a program to break out the data
    from a usage file, so that you could mung it again?  I know HACKS
    are supposed to be dirty, but COME ON, may as well do it in one
    fell swoop!
    
    RECORD DISK_USAGE_RECORD USING 
    01 DISK_USAGE_RECORD. 
            03 TYPE BYTE. 
            03 K_FILE. 
                    05 UIC. 
                            10 MEMBER WORD. 
                            10 GROUP WORD. 
                    05 FILE_ALLOC LONG. 
                    05 FILE_USAGE LONG. 
                    05 DIRECT_LENGTH WORD. 
                    05 FILE_LENGTH WORD. 
                    05 FILESPEC PIC X(406) EDIT_STRING T(50).
            03 IDENT REDEFINES K_FILE. 
                    05 SERIAL_NUMBER LONG. 
                    05 VOL_SET_NAME PIC X(12). 
                    05 VOL_NAME PIC X(12). 
                    05 VOL_OWNER_NAME PIC X(12). 
                    05 VOL_FORMAT_TYPE PIC X(12). 
                    05 CREATION_TIME DATE. 
                    05 FILLER PIC X(362). 
    ; 
524.4Here's an old program to process USAGE.DATCADSYS::SLATERKen SlaterThu Aug 13 1987 03:38439
To:    FILE				Date: 13-Dec-1983
From:  Ken Slater

Subj: DISKUSAGE

DISKUSAGE is a program which reads disk usage files as produced by the VMS
ANAL/DISK/USAGE command and produces a report of disk usage by top level 
directories on the disk. I believe it to be faster than older DCL programs
which are around and do the same thing, and it provides slightly more 
information. It sorts the output by descending blocks allocated.

Input is from logical name USAGE which defaults to SYS$DISK:[]USAGE.DAT, this
nicely is what the ANAL/DISK/USAGE produces by default.

Output is to logical USAGERPT which defaults to SYS$DISK:[]USAGERPT.LIS.

Sample DISKUSAGE session:

$ SET PROCESS/PRIV=READALL		! Need this to look at all the files
$ ANAL/DISK/USAGE	DISK$WORKSPACE2
$ SET PROCESS/PRIV=NOREADALL
$ RUN DISKUSAGE
	... messages from DISKUSAGE about how hard it's working
$ DELETE USAGE.DAT;0			! This can be several hundred blocks.
$ TYPE USAGERPT.LIS

DISKUSAGE V1.0-001                    13-DEC-1983 16:21:59.37

Volume One Name = WORKSPACE2          Volume Owner  = SLATER      
Volume Set Name =                     Volume Format = DECFILE11B  
Volume Serial # = 00000030434         Data Collected  12-DEC-1983 19:35:51.77


 TOTAL   BLOCKS   BLOCKS
 FILES    USED   ALLOCATED            TOP LEVEL DIRECTORY
======= ======== ========= =========================================
     73    44221     44470 [IVTEST]
     13      213      1114 [000000]
      6      794       813 [DRCWORK]
      1        0         1 [IVWORK]
      1        0         1 [WORKIV]
======= ======== ========= =========================================
     94    45228     46399    5 total top level directories

PL/I Source code follows...

/* DISKUSAGE: This program reads the disk usage file (default USAGE.DAT)
    produced by ANAL/DISK/USAGE and produces a report of usage by top level
    (MFD) directory enteries. The report lists total files, blocks allocated and
    blocks used under each top level directory, sorted in desending order of 
    blocks allocated. Note that the blocks allocated includes header blocks,
    which is not included in the DIRECTORY/SIZE command reports.

    INPUT: Tries to translate logical name USAGE, then applies the default
    	SYS$DISK:[]USAGE.DAT. The file format must be that produced by the
    	ANAL/DISK/USAGE command (See Utilies - Verify for documentation).

    OUTPUT: The report is written to USAGERPT, after translation the defaults
    	SYS$DISK:[]USGAERPT.LIS are applied. The report is written with 
    	standard VMS record format so it may be easily edited. mailed or 
    	printed.

    STATUS & ERROR OUTPUT: is written to SYS$OUTPUT to advise of progress or
    	error conditions.

    This program was written and developed on VMS V3.4. I have tried to
anticipate changes in VMS V4.0 and have provided for 39 character file names
and 255 character file specifications. However I cannot assure you that this
program will work under that version of VMS. 
               [12-Aug-1987 It has been working up through V4.6]

    There is one hard limit in this program: The size of the array that
accumulates the totals. There must be one array element for each directory
entry. As shipped, the program provides for 256 entries as defined by the
symbolic constant MAX_TOTAL. If you get an array overflow message, make this
larger and re-compile. On our systems, I have never seen more than 50 top
level directories, even on a (large) RA81 disk, so the shipped size should be
adequate. 


  AUTHOR/MODIFERS:          (KHS) Ken Slater 

    DATE     WHO  VERSION  MODIFICATION HISTORY
  ---------  ---  -------  ---------------------------------------------------
  13-Dec-83  KHS  1.0-001  Created from scratch.

*/

%REPLACE version BY 'DISKUSAGE V1.0-001';



diskusage: PROCEDURE RETURNS ( FIXED BIN(31) ) OPTIONS ( MAIN, IDENT(version) );

%REPLACE max_total     BY 255;		/* Max in totals array      */
%REPLACE max_file_name BY  39;		/* Max char per file name   */
%REPLACE max_file_spec BY 256;		/* Max char per file spec   */
%REPLACE hash_error    BY  -1;		/* Hash array overflow      */
%REPLACE slot_empty    BY  -2;		/* Array slot not in use    */
%REPLACE abort         BY '1'b;		/* For error_msg - abort    */
%REPLACE cont          BY '0'b;		/* For error_msg - continue */
%REPLACE msg_interval  BY 1000;		/* Read progress report     */
%REPLACE true          BY '1'b;
%REPLACE false         BY '0'b;

%INCLUDE sys$asctim;			/* Declare time conversion service */
%INCLUDE $stsdef;			/* Declare status values    */

DECLARE usage FILE RECORD INPUT;
DECLARE rpt   FILE RECORD OUTPUT;

DECLARE 01 fmt1,		/* Usage Header Record */
    02 rec_type		 FIXED BIN(7),		/* 1 for format 1 */
    02 vol_serial_number FIXED BIN(31),
    02 vol_set_name      CHAR(12),
    02 vol_one_name	 CHAR(12),
    02 vol_owner_name	 CHAR(12),
    02 vol_format	 CHAR(12),
    02 time_stamp   	 BIT(64) ALIGNED;

DECLARE 01 fmt2,		/* Usage Data Record */
    02 rec_type		 FIXED BIN(7),		/* 2 for format 2 */
    02 uic		 FIXED BIN(31),
    02 blk_alloc	 FIXED BIN(31),
    02 blk_used		 FIXED BIN(31),
    02 dir_str_len	 FIXED BIN(15),
    02 file_str_len	 FIXED BIN(15),
    02 file_str(1:max_file_spec) CHAR(1);

DECLARE 01 totals(0:max_total),		/* Totalization array */
    02 name_len FIXED BIN(7),
    02 name	CHAR(max_file_name),
    02 alloc	FIXED BIN(31),
    02 used	FIXED BIN(31),
    02 files	FIXED BIN(31);

DECLARE 01 work,			/* Totalization work record */
    02 name_len FIXED BIN(7),
    02 name	CHAR(max_file_name),
    02 alloc	FIXED BIN(31),
    02 used	FIXED BIN(31),
    02 files	FIXED BIN(31) INITIAL(1);

DECLARE out_buf  CHARACTER(80) VARYING;	/* Output buffer */
DECLARE time_str CHARACTER(23);         /* ASCII time from system time fmt */

DECLARE (total_files, total_alloc, total_used, total_direct) 
    		FIXED BIN(31) INITIAL(0);	/* For grand totals */

DECLARE record_count FIXED BIN(31) INITIAL(0);	/* Counts fmt2 records */

DECLARE (biggest,biggest_index) FIXED BIN(31);	/* For report sorting    */

DECLARE overflow_flag BIT(1) INITIAL(false);	/* Array overflow flag   */

DECLARE i FIXED BIN(31);		/* Loop index & temporary */
DECLARE c CHAR(1);			/* Character temporary    */



hash_lookup: PROCEDURE(look_name) RETURNS(FIXED BIN(31));
    DECLARE look_name CHAR(max_file_name);

    /* Given a name (look_name) to locate in the totals array, the following
       values will be returned:
    	  0..max_total    - Array index to name if already in array
    	  0..max_total    - Array index to empty slot if name not present
 	  hash_error (<0) - If name not found and array full
       Check the value of totals(i).name_len to see if a slot is used; it is
       equal to slot_empty if not used.

       The simple hash algorithm is: Add up all non-blank characters and the
    	  non-blank length; then modulo this by the array size.
    */

    DECLARE hash_index FIXED BIN(31) INITIAL(0); /* Computed hash code */
    DECLARE i FIXED BIN(31);			 /* Loop index & temp  */

    /* Compute the hash index */

    DO i=1 to max_file_name WHILE( SUBSTR(look_name,i,1) ^= ' ' );
    	hash_index = hash_index + RANK( SUBSTR(look_name,i,1) );
    	END;
    hash_index = MOD( hash_index + i, max_total );

    /* Given the intial has index, scan through the entire array. If the
       name is found or and empty slot is encountered the hash_index is
       returned. */

    DO i=0 to max_total;
    	IF totals(hash_index).name     = look_name  THEN RETURN(hash_index);
    	IF totals(hash_index).name_len = slot_empty THEN RETURN(hash_index);
    	hash_index = MOD( hash_index + 1, max_total );
    	END;

    /* If here, the array is full and the name is not in the array */
    RETURN(hash_error);

END hash_lookup;



error_msg: PROCEDURE ( abort_flag, message );

    DECLARE abort_flag BIT(1);
    DECLARE message CHARACTER(80) VARYING;
    DECLARE junk FIXED BIN(31);	/* Unused return status value */

    %INCLUDE sys$exit;		/* Declare VMS exit service */

    PUT SKIP(2) EDIT ( 'DISKUSAGE Error: ', message ) ( 2 A );

    IF abort_flag THEN DO;
    	PUT SKIP LIST ( 'DISKUSAGE terminated by error.' );
    	CLOSE FILE(usage);
    	CLOSE FILE(rpt);
    	junk = SYS$EXIT(4);	/* Abort and return error status */
    	END;
    ELSE RETURN;

END error_msg;




/* Start of main procedure of DISKUSAGE */

    /* Say hello to the user */
    PUT SKIP(2) LIST ( version );
    PUT SKIP;

    /* Initialize totals array */
    DO i=0 TO max_total;
    	totals(i).name_len = slot_empty;
    	totals(i).name     = ' ';
    	totals(i).alloc    = 0;
    	totals(i).used	   = 0;
    	totals(i).files    = 0;
    	END;

    /* Open the usage file and read in the header record */

    ON ENDFILE(usage) GOTO done_readin;

    ON UNDEFINEDFILE(usage) CALL error_msg(abort,'Can''t open input file.');

    OPEN FILE(usage) TITLE('USAGE') RECORD INPUT
    	ENVIRONMENT( DEFAULT_FILE_NAME ('SYS$DISK:[]USAGE.DAT') );

    READ FILE(usage) INTO(fmt1);
    IF fmt1.rec_type ^= 1 
    	THEN CALL error_msg(abort,'First input record has improper format.');


    /* Now loop through all the data records, summarizing them in the
       totals array. ERROR conditon is disabled to prevent the warning
       of unequal record lengths since input record has variable size */

    ON ERROR;

DO WHILE( true ); /* Read loop is exited by endfile condition */

    READ FILE(usage) INTO(fmt2);
    IF fmt2.rec_type ^= 2 
    	THEN CALL error_msg(abort, 'Non-format 2 record encountered on input.');

    /* Count the records and issue a progress report if needed */

    record_count = record_count + 1;
    IF MOD(record_count,msg_interval) = 0 THEN 
    	PUT SKIP EDIT (record_count,' Records processed.') ( X(8), F(6), A );

    /* Extract data from usage data record into work record, truncating
       file spec to top directory name */
    work.alloc = fmt2.blk_alloc;
    work.used  = fmt2.blk_used;
    work.name  = ' ';
    i = 2; 
    DO c = fmt2.file_str(i) REPEAT fmt2.file_str(i) WHILE( c ^= ']' & c ^= '.');
    	SUBSTR(work.name,i-1,1) = c;
    	i = i + 1;
    	END;
    work.name_len = i - 1;

    /* Add the new record to the totals array */
    i = hash_lookup(work.name);
    IF i = hash_error THEN DO; /* Array overflow */
    	IF ^overflow_flag THEN
    	    CALL error_msg(cont,'Array overflow, some data lost.');
    	overflow_flag = TRUE;
    	END;
    ELSE IF totals(i).name_len = slot_empty 
    	THEN totals(i) = work; /* Add new item to array */
    ELSE DO;		       /* Sum into old item     */
    	    totals(i).used  = totals(i).used  + work.used;
    	    totals(i).alloc = totals(i).alloc + work.alloc;
    	    totals(i).files = totals(i).files + 1;
    	    END;

    END; /* Read Loop */

done_readin:
    REVERT ERROR;
    CLOSE FILE(usage);

    /* Issue the final progress report */
    PUT SKIP EDIT (record_count,' Records processed.') ( X(8), F(6), A );



    /* Open the report file and output header info */
    
    ON UNDEFINEDFILE(rpt) CALL error_msg(abort,'Can''t open output file.');

    OPEN FILE(rpt) TITLE('USAGERPT') RECORD OUTPUT
    	ENVIRONMENT( DEFAULT_FILE_NAME ('SYS$DISK:[]USAGERPT.LIS') );

    sts$value = sys$asctim(,time_str,,);
    IF ^sts$success THEN CALL error_msg(cont,'Error fetching system time.');

    out_buf = version || '                    ' || time_str; 
    WRITE FILE(rpt) FROM(out_buf);
    out_buf = '';      WRITE FILE(rpt) FROM(out_buf);

    PUT STRING(out_buf) EDIT('Volume One Name = ', vol_one_name,
    			     'Volume Owner  = ',   vol_owner_name)
    			    ( A, A(12), X(8), A, A(12) );
    WRITE FILE(rpt) FROM(out_buf);

    PUT STRING(out_buf) EDIT('Volume Set Name = ', vol_set_name,
    			     'Volume Format = ',   vol_format)
    			    ( A, A(12), X(8), A, A(12) );
    WRITE FILE(rpt) FROM(out_buf);

    sts$value = sys$asctim(,time_str,time_stamp,);
    IF ^sts$success THEN CALL error_msg(cont,'Error in time conversion.');

    PUT STRING(out_buf) EDIT('Volume Serial # = ',  vol_serial_number,
    			     'Data Collected  ',   time_str)
    			    ( A, B3(12), X(8), A, A(23) );
    WRITE FILE(rpt) FROM(out_buf);

    out_buf = '';      WRITE FILE(rpt) FROM(out_buf);

    /* Write out a warning if overflow has occurred */

    IF overflow_flag THEN DO;
    	out_buf = '*** WARNING *** Array Overflow, some data lost!';
    	WRITE FILE(rpt) FROM(out_buf);
    	END;

    out_buf = '';      WRITE FILE(rpt) FROM(out_buf);

    /* Write out the totalization array column headers */

    out_buf = ' TOTAL   BLOCKS   BLOCKS';
    	WRITE FILE(rpt) FROM(out_buf);
    out_buf = ' FILES    USED   ALLOCATED ' ||
    			'           TOP LEVEL DIRECTORY';
    	WRITE FILE(rpt) FROM(out_buf);
    out_buf = '======= ======== ========= ' ||
    			'=========================================';
    	WRITE FILE(rpt) FROM(out_buf);

    /* Now we output the data by making repeated passes over the entire
       array (not very efficient but it runs very fast!). Each pass over
       the array selects the largest remaining record, after it is output
       it removed by setting it name_len to slot_empty. Termination occurs
       when a pass is made over the array and no records are found. */

    biggest_index = 0;
    DO WHILE(biggest_index >= 0);
        biggest = -1; biggest_index = -1;
        DO i=0 to max_total;
       	    IF totals(i).name_len ^= slot_empty & 
    	       totals(i).alloc > biggest THEN DO;
    	           biggest = totals(i).alloc;
    	           biggest_index = i;
    	           END;
    	    END;
    	i = biggest_index;
    
    	/* Here i is pointing at the array slot for the biggest allocation
    	   still remaining or is -1 indicating that no records remain. The
    	   code below is executed only if a valid record remains to be output */

    	IF biggest_index >= 0 THEN DO;

    	    /* Special fix for null directory of temporary files */

    	    IF totals(i).name = ' ' THEN DO;
    	        totals(i).name = ' *** Temporary - Marked for Delete *** ';
    	        totals(i).name_len = 40;
    	        END;

    	    PUT STRING(out_buf) EDIT( totals(i).files, totals(i).used,
    				      totals(i).alloc, '[', 
    			SUBSTR(totals(i).name,1,totals(i).name_len-1), ']') 
    		 		    ( F(7), X, F(8), X, F(9), X, 3 A );
    	    WRITE FILE(rpt) FROM(out_buf);

    	    /* Code below sums up for grand totals */

    	    total_files  = total_files  + totals(i).files;
    	    total_alloc  = total_alloc  + totals(i).alloc;
    	    total_used   = total_used   + totals(i).used;
    	    total_direct = total_direct + 1;

    	    /* Entry processed; "delete" from array */

    	    totals(i).name_len = slot_empty;
    	    END;

    	END; /* of DO WHILE loop */

    /* Now write the summary data */

    out_buf = '======= ======== ========= ' ||
    			'=========================================';
    	WRITE FILE(rpt) FROM(out_buf);


    PUT STRING(out_buf) EDIT(total_files, total_used, total_alloc, 
    			total_direct, ' total top level directories') 
    		 	( F(7), X, F(8), X, F(9), X, F(4), A );
    WRITE FILE(rpt) FROM(out_buf);

    /* All done, close up & clean up */

    CLOSE FILE(rpt);

    PUT SKIP EDIT (total_direct, ' Unique directories.')( X(8), F(6), A );

    PUT SKIP(2) LIST ('DISKUSAGE Done.');
    PUT SKIP;

    RETURN(1);	/* Return success */

END diskusage;