COBOL TIPS #18
by
Shawn M. Gordon
President S.M.Gordon & Associates

Welcome back, as promised I am going to supply a more versatile example of the HPVOLINFO intrinsic. As I mentioned last month, this code compiles and runs correctly under MPE V Platform 2P, you will need to verify some of the parameters
under your specific version of the OS. I know when this first came out I had to do a couple of things to make it work right on a classic.

You may wonder what the point of using a program like this is when you have FREE5 and the DISCFREE commands. Well, I used it to add a feature to one of my products that does data set capacity trending and forecasting analysis. A logical extension to that was to be able to trend and forecast disk drive usage. So I used a version of this program to collect the drive information, and then do various functions with the data over time. On a spectrum this intrinsic runs almost instantly, on a classic it is a bit slower because the drive space information isn’t immediatly available. The HPVOLINFO intrinsic provides all sorts of neat information about what files are taking what space, you can tweak this program to get pretty much anything about the disk off.


$CONTROL USLINIT,BOUNDS
 IDENTIFICATION DIVISION.
 PROGRAM-ID. VOLINFO2.
 AUTHOR. SHAWN M.GORDON.
 DATE-WRITTEN. WED, NOV 18, 1992.
 DATE-COMPILED.
********************************************************
*
*  This program is designed to use the new HPVOLINFO
*  intrinsic to gather disk drive trending information.
*  For lack of a better place it is being added to the
*  DBTREND system.
*  Shawn M. Gordon
*
********************************************************
 ENVIRONMENT DIVISION.
 CONFIGURATION SECTION.
 SOURCE-COMPUTER. HP-3000.
 OBJECT-COMPUTER. HP-3000.
 SPECIAL-NAMES.
     CONDITION-CODE IS CC.
 INPUT-OUTPUT SECTION.
 DATA DIVISION.
*
********************************************************
 WORKING-STORAGE SECTION.

 01 EDIT-LNUM                 PIC Z,ZZZ,ZZZ,ZZ9.
 01 EDIT-SNUM                 PIC ZZ,ZZZ,ZZ9.
 01 EDIT-STAT                 PIC ---9.
 01 MISCELLANEOUS-DATA.
    03 VOL-SPEC-NUM           PIC S9(4)    COMP VALUE 0.
    03 VOL-SPEC               PIC X(56)    VALUE SPACES.
    03 HOLD-VSPEC             PIC X(56)    VALUE SPACES.
    03 STATINFO               PIC S9(09)   COMP VALUE 0.
    03 STATINFO-ARRAY  REDEFINES STATINFO.
       05 STAT-WORD1          PIC S9(04)   COMP.
       05 STAT-WORD2          PIC S9(04)   COMP.
*
 01 KOUNTERS.
    03 S1                     PIC S9(4)    COMP VALUE 0.
    03 S2                     PIC S9(4)    COMP VALUE 0.
    03 S3                     PIC S9(4)    COMP VALUE 0.
    03 S4                     PIC S9(4)    COMP VALUE 0.
*
 01 ITEMNUMS  USAGE COMP.
    03 ITEM02                 PIC S9(4)    VALUE 02.
    03 ITEM03                 PIC S9(4)    VALUE 03.
    03 ITEM06                 PIC S9(4)    VALUE 06.
    03 ITEM07                 PIC S9(4)    VALUE 07.
    03 ITEM08                 PIC S9(4)    VALUE 08.
    03 ITEM13                 PIC S9(4)    VALUE 13.
    03 ITEM14                 PIC S9(4)    VALUE 14.
    03 ITEM32                 PIC S9(4)    VALUE 32.
*
 01 ITEMS02.
    03 TOTAL-VOL-SETS         PIC S9(9)    COMP VALUE 0.

 01 ITEMS03.
    03 VOLS-NAMES          OCCURS 99.
       05 VOL-NAMES           PIC X(32).
       05 VN-REDEFINES      REDEFINES VOL-NAMES.
          07 VOL-MAX          PIC S9(9)    COMP.
          07 VOL-NAME         PIC X(28).

 01 ITEMS06.
    03 TOTAL-MEM-VOL          PIC S9(9)    COMP VALUE 0.

 01 ITEMS07.
    03 MEMS-NAMES          OCCURS 99.
       05 MEM-NAMES           PIC X(32).
       05 MN-REDEFINES      REDEFINES MEM-NAMES.
          07 MEM-MAX          PIC S9(9)    COMP.
          07 MEM-NAME         PIC X(28).

 01 ITEMS08.
    03 DRIVE-TYPE             PIC X(14)    VALUE SPACES.

 01 ITEMS13.
    03 LDEV                   PIC S9(4)    COMP VALUE 0.

 01 ITEMS14.
    03 TOTAL-SYSTEM           PIC S9(18)   COMP VALUE 0.

 01 ITEMS32.
    03 TOTAL-PERM-USED        PIC S9(18)   COMP VALUE 0.
*
*********************************************************
 PROCEDURE DIVISION.
*
 A1000-INIT.
     DISPLAY 'Begin run of VOLINFO2 at ' TIME-OF-DAY.
     DISPLAY SPACES.

* Retreive total number of volume sets on system - this is usually
* a 1 unless private volumes are being used.

     CALL INTRINSIC "HPVOLINFO" USING STATINFO, \\, \\,
                                      ITEM02, ITEMS02,
     IF STAT-WORD1 <> 0
        MOVE STAT-WORD1          TO EDIT-STAT
        DISPLAY 'INTRINSIC HPVOLINFO FAILED'
        DISPLAY 'ERROR CODE = ' EDIT-STAT
        DISPLAY 'LOCATION 1'
        STOP RUN.

     MOVE TOTAL-VOL-SETS         TO EDIT-SNUM.
     DISPLAY 'There are ' EDIT-SNUM
             ' Volume Sets on this system'.

* Retreive all volume set names into an array to be used later

     MOVE TOTAL-VOL-SETS         TO VOL-MAX(1).
     CALL INTRINSIC "HPVOLINFO" USING STATINFO, \\, \\,
                                      ITEM03, ITEMS03.
     IF STAT-WORD1 <> 0
        MOVE STAT-WORD1          TO EDIT-STAT
        DISPLAY 'INTRINSIC HPVOLINFO FAILED'
        DISPLAY 'ERROR CODE = ' EDIT-STAT
        DISPLAY 'LOCATION 2'
        STOP RUN.

* Now loop through each volume set to retrieve how many member
* volumes there are - this is going to be a serious nested loop.

     MOVE 1                      TO S1.
     MOVE VOL-NAME(1)            TO HOLD-VSPEC.
     STRING "%" DELIMITED BY SIZE
            VOL-NAME(1) DELIMITED BY SPACES
            "%" DELIMITED BY SIZE
            INTO VOL-SPEC.
     PERFORM TOTAL-VOL-SETS TIMES
        MOVE 2                   TO VOL-SPEC-NUM
        CALL INTRINSIC "HPVOLINFO" USING STATINFO, VOL-SPEC-NUM,
                                   VOL-SPEC, ITEM06, ITEMS06
        IF STAT-WORD1 <> 0
           MOVE STAT-WORD1       TO EDIT-STAT
           DISPLAY 'INTRINSIC HPVOLINFO FAILED'
           DISPLAY 'ERROR CODE = ' EDIT-STAT
           DISPLAY 'VOLUME NAME= ' VOL-SPEC
           STOP RUN
        END-IF
        MOVE TOTAL-MEM-VOL       TO EDIT-SNUM
        DISPLAY 'There are ' EDIT-SNUM ' disks on Volume Set '
                VOL-SPEC
        MOVE 1                   TO S2
        PERFORM B1000-DRIVE-NAME THRU B1000-EXIT

        ADD 1 TO S1
        MOVE SPACES              TO VOL-SPEC
        MOVE VOL-NAME(S1)        TO HOLD-VSPEC
        STRING "%" DELIMITED BY SIZE
               VOL-NAME(S1) DELIMITED BY SPACES
               "%" DELIMITED BY SIZE
               INTO VOL-SPEC
        END-STRING
     END-PERFORM.

     STOP RUN.
 A1000-EXIT.  EXIT.

 B1000-DRIVE-NAME.
* Retreive all member names for specified volume set

     MOVE TOTAL-MEM-VOL          TO MEM-MAX(1).
     CALL INTRINSIC "HPVOLINFO" USING STATINFO, VOL-SPEC-NUM,
                                      VOL-SPEC, ITEM07, ITEMS07.
     IF STAT-WORD1 <> 0
        MOVE STAT-WORD1          TO EDIT-STAT
        DISPLAY 'INTRINSIC HPVOLINFO FAILED'
        DISPLAY 'ERROR CODE = ' EDIT-STAT
        DISPLAY 'LOCATION 4'
        STOP RUN.

     MOVE 1                      TO S2.
     MOVE 4                      TO VOL-SPEC-NUM.
     MOVE SPACES                 TO VOL-SPEC.
     DISPLAY 'LDEV Drive Type     Volume Member Name'
             '          Total Capacity    Space Used'.
     DISPLAY '--------------------------------------'
             '--------------------------------------'.
     PERFORM TOTAL-MEM-VOL TIMES
        STRING "%" DELIMITED BY SIZE
               HOLD-VSPEC DELIMITED BY SPACES
               ":" DELIMITED BY SIZE
               MEM-NAME(S2) DELIMITED BY SPACES
               "%" DELIMITED BY SIZE
               INTO VOL-SPEC
        END-STRING

        CALL INTRINSIC "HPVOLINFO" USING STATINFO, VOL-SPEC-NUM,
                                         VOL-SPEC, ITEM08, ITEMS08,
                                         ITEM13, ITEMS13
        IF STAT-WORD1 <> 0
           MOVE STAT-WORD1       TO EDIT-STAT
           DISPLAY 'INTRINSIC HPVOLINFO FAILED'
           DISPLAY 'ERROR CODE = ' EDIT-STAT ' ' VOL-SPEC
           DISPLAY 'LOCATION 5'
           STOP RUN
        END-IF
        MOVE LDEV                TO EDIT-STAT
        DISPLAY EDIT-STAT ' ' DRIVE-TYPE ' '
                MEM-NAME(S2) NO ADVANCING

        CALL INTRINSIC "HPVOLINFO" USING STATINFO, VOL-SPEC-NUM,
                                         VOL-SPEC, ITEM14, ITEMS14,
                                         ITEM32, ITEMS32
        IF STAT-WORD1 <> 0
           MOVE STAT-WORD1       TO EDIT-STAT
           DISPLAY 'INTRINSIC HPVOLINFO FAILED'
           DISPLAY 'ERROR CODE = ' EDIT-STAT ' ' VOL-SPEC
           DISPLAY 'LOCATION 6'
           STOP RUN
        END-IF

        MOVE TOTAL-SYSTEM        TO EDIT-LNUM
        DISPLAY ' ' EDIT-LNUM ' ' NO ADVANCING
        MOVE TOTAL-PERM-USED     TO EDIT-LNUM
        DISPLAY EDIT-LNUM
        ADD 1 TO S2
     END-PERFORM.
 B1000-EXIT.  EXIT.
*
 C9000-EOJ.
     DISPLAY 'End of VOLINFO2 at ' TIME-OF-DAY.
     STOP RUN.

:RUN VOLINFO2.PROG

Begin run of VOLINFO2 at 07:22:07

There are          1 Volume Sets on this system
There are          3 disks on Volume Set %MPEXL_SYSTEM_VOLUME_SET%
LDEV Drive Type     Volume Member Name          Total Capacity    Space Used
----------------------------------------------------------------------------
  15 HP7937         MH7937D1                         2,232,204     1,295,625
   4 HP7937         MH7937D2                         2,232,204     1,348,326
  12 HP7937         MH7937D3                         2,232,204     1,494,724

End of Program
:

Using this intrinsic can be tricky, and not very intuitive. First I have to retrieve how many disk volumes there are, as noted in the code, this will normally be 1 unless you are using private volumns. Next we have to retrieve all the volume names into a table. Now we have to loop through the volume name table to see how many members there are for each volume. Then for each member of each volume we will retrieve the specific information that we are concerned with. And for some odd reason, the intrinsic on a classic requires that the volume set name be MPEXL_SYSTEM_VOLUME_SET.

I hope you found this month’s exercise interesting. While I was going through this it occurred to me that not a lot of people make use of the DBINFO intrinsic, or don’t really understand how it works. So next month I am going to provide a nifty little utility that will make extensive use of the DBINFO intrinsic in a COBOL program.