Inside COBOL #23
by
Shawn M. Gordon
President S.M.Gordon & Associates

Well I found some more code from the old days that illustrates a couple of handy examples of interacting with MPE from a program. I don’t think I wrote this originally, but I did enhance it a bit. Basically what we have here is a program that will do ABORTJOB’s against a whole bunch of users. It allows you to specify one inclusion, or one exclusion set of users, or all users. You will see in the code, but if you wanted to abort everyone in a particular account you would just specify +USER.ACCOUNT and away they go. You can also say abort everyone BUT the users specified by saying -USER.ACCOUNT. And finally you can abort everyone on the system by specifying @.

The program will always ignore device 20 (which is the console), because it would be the rare day that you would want to abort the console. There is also a little built in help facility to make it even easier to use.

  1     $CONTROL USLINIT,BOUNDS
  1.1    IDENTIFICATION DIVISION.
  1.2    PROGRAM-ID. JSABORT.
  1.3   *
  1.4   ****************************************************
  1.5   * This program will abort a user set off of the system
  1.6   ****************************************************
  1.7   *
  1.8    AUTHOR. Shawn M. Gordon.
  1.9    INSTALLATION. S.M.Gordon & Associates.
  2      DATE-WRITTEN. THU, AUG 10, 1995.
  2.1    DATE-COMPILED.
  2.2    ENVIRONMENT DIVISION.
  2.3    CONFIGURATION SECTION.
  2.4    SOURCE-COMPUTER. HP-3000.
  2.5    OBJECT-COMPUTER. HP-3000.
  2.6    INPUT-OUTPUT SECTION.
  2.7    FILE-CONTROL.
  2.8        SELECT SHOWJOB ASSIGN TO "SHOWWORK".
  2.9    DATA DIVISION.
  3      FILE SECTION.
  3.1    FD SHOWJOB
  3.2       RECORD CONTAINS 80 CHARACTERS.
  3.3    01 SH-REC.
  3.4       03 SJ-SESSION.
  3.5          05 SJ-1           PIC X.
  3.6          05                PIC X(05).
  3.7       03                   PIC X(14).
  3.8       03 SJ-DEV            PIC X(02).
  3.9       03                   PIC X(23).
  4         03 SJ-USER           PIC X(17).
  4.1       03                   PIC X(18).
  4.2   *
  4.3    WORKING-STORAGE SECTION.
  4.4
  4.5    01 WS-OPTION            PIC X(30)  VALUE SPACES.
  4.6    01 ERR-PARM             PIC S9(4)  COMP VALUE 0.
  4.7    01 MSG-LEVEL            PIC S9(4)  COMP VALUE 0.
  4.8
  4.9    01 HOME-N-CLEAR.
  5         03                   PIC X      VALUE %33.
  5.1       03                   PIC X      VALUE 'h'.
  5.2       03                   PIC X      VALUE %33.
  5.3       03                   PIC X      VALUE 'J'.
  5.4   *
  5.5    01 DIVERSE.
  5.6       03 USERTABLE.
  5.7          05 USERTAB OCCURS 999 INDEXED BY INX.
  5.8             07 PJOB        PIC X(06).
  5.9             07 PUSER       PIC X(17).
  6               07 PDEV        PIC X(02).
  6.1   *
  6.2    01 COM-IMAGE.
  6.3       03 COMMAND-IMAGE     PIC X(79)  VALUE SPACES.
  6.4       03                   PIC X      VALUE %15.
  6.5    01 COMMAND-ERROR        PIC S9(4)  COMP VALUE 0.
  6.6   *
  6.7    PROCEDURE DIVISION.
  6.8    A0000-MACROS.
  6.9   $DEFINE %COMIMAGE=
  7              MOVE SPACES                TO COMMAND-IMAGE.
  7.1            STRING !1
  7.2                   !2
  7.3                   DELIMITED BY SIZE INTO COMMAND-IMAGE
  7.4            CALL INTRINSIC 'HPCICOMMAND' USING COM-IMAGE,
  7.5                                               COMMAND-ERROR,
  7.6                                               ERR-PARM,
  7.7                                               MSG-LEVEL#
  7.8   *
  7.9    A1000-INIT.
  8          %COMIMAGE("BUILD SHOWWORK;REC=-80,,F,ASCII;DISC=1000;TEMP"#).
  8.1        %COMIMAGE("FILE SHOWWORK=SHOWWORK,OLDTEMP"#).
  8.2        PERFORM C1000-LOAD-SHOWJOB  THRU C1000-EXIT.
  8.3   *
  8.4    A1100-MENU.
  8.5        DISPLAY HOME-N-CLEAR NO ADVANCING.
  8.6        %COMIMAGE("SHOWJOB"#).
  8.7        DISPLAY SPACES.
  8.8        DISPLAY "Enter USER set or ? for help, E to End: "
  8.9                NO ADVANCING.
  9          ACCEPT WS-OPTION FREE.
  9.1        SET INX TO 1.
  9.2
  9.3        IF WS-OPTION(1:1) = "?"
  9.4           PERFORM H1000-HELP       THRU H1000-EXIT.
  9.5        IF WS-OPTION(1:1) = "-"
  9.6           PERFORM A2000-ABORT-EXC  THRU A2000-EXIT.
  9.7        IF WS-OPTION(1:1) = "+"
  9.8           PERFORM A3000-ABORT-INC  THRU A3000-EXIT.
  9.9        IF WS-OPTION(1:1) = "@"
 10             PERFORM A4000-ABORT-ALL  THRU A4000-EXIT.
 10.1        IF WS-OPTION = "E" OR "e" OR "EXIT" OR "QUIT" OR "Q"
 10.2           GO TO C9000-EOJ.
 10.3
 10.4        GO TO A1100-MENU.
 10.5    A1100-EXIT.  EXIT.
 10.6
 10.7    A2000-ABORT-EXC.
 10.8        IF PUSER(INX) = SPACES
 10.9           GO TO A2000-EXIT.
 11          IF PUSER(INX) <> WS-OPTION(2:17)
 11.1           PERFORM A5000-ABORT      THRU A5000-EXIT.
 11.2        SET INX UP BY 1.
 11.3        GO TO A2000-ABORT-EXC.
 11.4    A2000-EXIT.  EXIT.
 11.5   *
 11.6    A3000-ABORT-INC.
 11.7        IF PUSER(INX) = SPACES
 11.8           GO TO A3000-EXIT.
 11.9        IF PUSER(INX) = WS-OPTION(2:17)
 12             PERFORM A5000-ABORT      THRU A5000-EXIT.
 12.1        SET INX UP BY 1.
 12.2        GO TO A3000-ABORT-INC.
 12.3    A3000-EXIT.  EXIT.
 12.4   *
 12.5    A4000-ABORT-ALL.
 12.6        IF PUSER(INX) = SPACES
 12.7           GO TO A4000-EXIT.
 12.8        PERFORM A5000-ABORT         THRU A5000-EXIT.
 12.9        SET INX UP BY 1.
 13          GO TO A4000-ABORT-ALL.
 13.1    A4000-EXIT.  EXIT.
 13.2   *
 13.3    A5000-ABORT.
 13.4        IF PDEV(INX) = '20'
 13.5           GO TO A5000-EXIT.
 13.6        %COMIMAGE("ABORTJOB"#, PJOB(INX)#).
 13.7    A5000-EXIT.  EXIT.
 13.8   *
 13.9    C1000-LOAD-SHOWJOB.
 14          %COMIMAGE("SHOWJOB *SHOWWORK"#).
 14.1        OPEN INPUT SHOWJOB.
 14.2        SET INX TO 1.
 14.3        MOVE SPACES                   TO USERTABLE.
 14.4    C1000-LOOP.
 14.5        READ SHOWJOB
 14.6           AT END
 14.7          CLOSE SHOWJOB
 14.8          GO TO C1000-EXIT.
 14.9
 15          IF SJ-1 <> "#"
 15.1           GO TO C1000-LOOP.
 15.2        MOVE SJ-SESSION               TO PJOB(INX).
 15.3        MOVE SJ-DEV                   TO PDEV(INX).
 15.4        MOVE SJ-USER                  TO PUSER(INX).
 15.5        SET INX UP BY 1.
 15.6        GO TO C1000-LOOP.
 15.7    C1000-EXIT.  EXIT.
 15.8   *
 15.9    C9000-EOJ.
 16          %COMIMAGE("PURGE SHOWWORK,TEMP"#).
 16.1        STOP RUN.
 16.2   *
 16.3    H1000-HELP.
 16.4        DISPLAY HOME-N-CLEAR.
 16.5        DISPLAY "To abort generic groups of user's you may use "
 16.6                "1 inclusion or 1 exclusion set".
 16.7        DISPLAY "at a time.  "
 16.8                "To abort all sessions logged on as USER.PROD, "
 16.9                "you would type".
 17          DISPLAY "+USER.PROD the + sign is critical.".
 17.1        DISPLAY SPACES
 17.2        DISPLAY "To abort all sessions but those logged on as "
 17.3                "MGR.PROD, you would type -MGR.PROD".
 17.4        DISPLAY "the - sign is critical.".
 17.5        DISPLAY SPACES
 17.6        DISPLAY "To abort all sessions just type @, device 20 "
 17.7                "is always ignored.".
 17.8        DISPLAY SPACES.
 17.9        DISPLAY "? will display this help routine".
 18          DISPLAY "E will exit the program".
 18.1        DISPLAY " will redisplay the current job queue".
 18.2        DISPLAY SPACES.
 18.3        DISPLAY " to continue " NO ADVANCING.
 18.4        ACCEPT WS-OPTION FREE.
 18.5    H1000-EXIT.  EXIT.

Now some of the neat tricks in here is doing redirection of MPE commands into files, and then reading them. Also we are using the HPCICOMMAND intrinsic to execute the MPE commands. Basically we build a temp file that will hold our output, set a file equation, and then do a SHOWJOB redirecting the output into the temp file we just built. Using a macro for the HPCICOMMAND intrinsic makes it easy to specify the commands in your code and keep it readable.

Once we have the output of SHOWJOB in a file we then display the output to the user, and let them choose who to abort. We then use the file (which was parsed into a table) to find and abort the specified user set. Keep in mind that if
your current session is one of those that will get aborted then you could get dumped before the program gets a chance to finish aborting users. This will leave users still on the system that you may not have intended. It is probably
best to only run this program from the console anyway.

For those of you unfamiliar with the HPCICOMMAND intrinsic, it let’s execute almost any MPE command programmatically. You can see how this can be very useful. There are a couple of things to remember about using the intrinsic. First you need to make sure that the command buffer you are passing is terminated with a carriage return. That is why in the COM-IMAGE data structure you see an item with a value of %15, this is the octal representation of a carriage return.

The other parameters return information that let you determine if there was an error, and what the error was, and what message catalog the error is in. This brings up an interesting topic on how to access the system message catalog from your program, especially if you are using the COMMAND or HPCICOMMAND intrinsic. I believe that will be a good topic for next month. I suppose that I should mention that the HPCICOMMAND intrinsic is the Native Mode version of the old COMMAND intrinsic. It has some great new abilities though, like being able to issue a RUN command within your program without having to use the CREATEPROCESS or CREATE intrinsics, which can be rather bothersome as we have discussed in previous columns.

So next month is going to be dedicated to using the GENMESSAGE intrinsic for accessing the system message catalog. See you then.