HP3000-L Archives

March 1998, Week 1

HP3000-L@RAVEN.UTC.EDU

Options: Use Monospaced Font
Show Text Part by Default
Show All Mail Headers

Message: [<< First] [< Prev] [Next >] [Last >>]
Topic: [<< First] [< Prev] [Next >] [Last >>]
Author: [<< First] [< Prev] [Next >] [Last >>]

Print Reply
Subject:
From:
Tim Ericson <[log in to unmask]>
Reply To:
Tim Ericson <[log in to unmask]>
Date:
Thu, 5 Mar 1998 11:40:22 -0800
Content-Type:
text/plain
Parts/Attachments:
text/plain (102 lines)
Ken Paul wrote:
<snip>
> The FAQ also shows a change to the DB.LISTF.VESOFT file to make it
> DDX aware.  I did not like the way it was done here and created my
> own DDX.LISTF.VESOFT file to be DDX aware.  I decided to put an 'X'
> after the dataset type if it was DDX (this is how HOWMESSY, from
> Robelle, does it).  I then had to shrink the LDEV display from 4 to
> 3 characters.  I also made the file always use DBSETMAXCAPACITY
> because according to the FAQ, if the set is not enabled for DDX the
> DBSETMAXCAPACITY=DBSETCAPACITY.

<snip again - and thanks for all the research, Ken>

I noticed this new feature just about as soon as we first started
using DDX (a year or so ago), because we use MPEX nightly to check for
datasets that are more than 70% full, and it stopped working correctly.

SO, I made my own "DBX" (I never noticed the FAQ file), and include it
here so others won't have to re-invent this wheel:

---------------------------------------------------------------------

VAR PREVROOT: STRING[8];
VAR PREVGROUPACCT: STRING[17];

SUBROUTINE LINEITEM;
VAR SETNAME: STRING[32];
VAR SETENTRIES: INTEGER;
VAR SETCAPACITY: INTEGER;
BEGIN
  SETNAME:=DBSETNAME;
  SETENTRIES:=DBSETENTRIES;
  IF DBSETDYNAMIC THEN
    SETCAPACITY:=DBSETMAXCAPACITY
  ELSE
    SETCAPACITY:=DBSETCAPACITY;
  IF SETNAME[0:7]='fserror' THEN
    SEG (BEGIN
    WRITEPROMPT (FILE:10);
    WRITEMPEMESSAGE (8, INTEGERPARSE(UNTILCR(STRLDROP(SETNAME,8))));
    END)
  ELSE
    BEGIN
      WRITELN (FILE:8,
               FMTOPENED:2,
               SETNAME[0:16]:16,
               DBSETTYPE:1,
               SETENTRIES:8,
               SETCAPACITY:8,
               (* Is it dynamic? *)
               (IF DBSETDYNAMIC THEN '*' ELSE ' '):1,
               (* If less than .1% full, output would be in E fmt *)
               (IF SETENTRIES//SETCAPACITY<=.0005 THEN 0
                  ELSE SETENTRIES//SETCAPACITY)*100:6:1, '%',
               SECTORS:8,
               CREDATE:'  MM/DD/YY ',
               MODDATE:' MM/DD/YY');
    END;
END;

PREVGROUPACCT:='';
PREVROOT:='';
MPEXHEADER1:="FILENAME  SET NAME      TYPE  ENTRY   CAPA-   %FULL"+
             " SECTORS    DATE      DATE ";
MPEXHEADER2:="                              COUNT     CITY       "+
             "           CREATED  MODIFIED";
MPEXHEADER3:="";

FOR RFILE IN MPEXFILESETGENERAL (1, TRUE)
  ALREADYSORTED (ACCOUNT:8, GROUP:8)
  SELECT INTCODE=-401
  DO
    BEGIN
      IF GROUP+'.'+ACCOUNT=PREVGROUPACCT AND STRRDROP(FILE,2)<>PREVROOT
THEN
        WRITELN;
      LINEITEM;
      PREVGROUPACCT:=GROUP+'.'+ACCOUNT;
      PREVROOT:=STRRDROP(FILE,2);
    END
  ONBREAKAFTER 2
    BEGIN
      WRITELN ;
      WRITELN ("                                                  ",
               TOTAL(2,SECTORS):9,
               "  SECTORS");
    END;

--------------------------------------------------------------------

I hope no one minds the bandwidth used.

  +------------------------------------------------------------------+
   My mind is my own, as are my ideas and opinions.
   My heart, body, and soul, however, all belong to others.      Tim.
  +------------------------------------------------------------------+
   Tim Ericson            tericson     DenKor Dental Management Corp.
   Sr. Programmer/Analyst   at denkor   (aka Willamette Dental Group)
     (& Systems Manager)      dot com    503-526-4440 (direct number)
   Programming HP3000s since 1983!     look! -> http://www.denkor.com
  +------------------------------------------------------------------+

ATOM RSS1 RSS2