| Front Page | News Headlines | Technical Headlines | Planning Features | Advanced Search |
LeeTech Sponsor Message

     

Calling MPEX from COBOL

By Shawn M. Gordon

This month I’d like to dust off the HP COBOL pseudo-intrinsics “.LEN.” and “.LOC.”. The “.LOC.” pseudo-intrinsic is necessary for certain uses of the CREATEPROCESS intrinsic. I’m not going to go into a lot of detail, but basically it allows you to pass an INFO parameter to a son process, as well as pass XL information and such. It casts a byte address to a string that you can use in your call to CREATEPROCESS, since you can’t do it directly in COBOL.

Keep in mind that much of what you once used CREATEPROCESS for isn’t needed anymore, as you can pass a fully formatted RUN command to the HPCICOMMAND intrinsic. The beauty of this process here — and it’s similar to what QEDIT does to work with MPEX — is that it keeps MPEX running and allows you to send commands to it perpetually.

Many moons ago (version 1.6 of MPEX), I hit upon an idea to have my programs call MPEX and do an ALTFILE if my writes to a file failed because it filled up, then re-open the file and keep writing to it. Now this is a one shot command to MPEX that will finish and then return to the program. What if you want to be in a command-driven program and be able to issue MPEX commands from your program? It is highly inefficient to do a new CREATEPROCESS for each and every command.

MPEX also makes use of the ‘SENDMAIL’ intrinsic for this type of communication. So now we have to be able to create MPEX as a son process, keep it alive after we come back to the father process, and then pass commands to MPEX that it will execute. So strap on your seat belts, here we go:


   01 MPEX-STUFF.
      03 MPEX-PIN               PIC S9(4)  COMP VALUE 0.
      03 MPEX-BUFF              PIC X(70)  VALUE SPACES.
      03 MPEX-FILE              PIC X(26)  VALUE "MPEX.PUB.VESOFT".
      03 MSG-LEN                PIC S9(4)  COMP VALUE 35.
      03 MAIL-STAT              PIC S9(4)  COMP VALUE 0.
      03 MS-I.
         05                     PIC S9(9)  COMP VALUE 0.
      03 MS-IN.
         05                     PIC S9(9)  COMP VALUE 0.
      03 MPEX-ERRORS            PIC S9(9)  COMP VALUE 0.
   01 COM-IMAGE.
      03 COMMAND-IMAGE          PIC X(60)  VALUE SPACES.
      03                        PIC X      VALUE %15.
   01 COMMAND-ERROR             PIC S9(4)  COMP VALUE 0.
  *
   PROCEDURE DIVISION.
   A0000-DEFINE-MACROS.
  *
  $DEFINE %COMIMAGE=
          MOVE !1
                  TO COMMAND-IMAGE
          CALL INTRINSIC 'COMMAND' USING COM-IMAGE,
                                         COMMAND-ERROR,
                                         ERR-PARM
          IF COMMAND-ERROR = 975
             DISPLAY "UNKNOWN COMMAND NAME"
          END-IF#
  *
  $DEFINE %UPSHIFT=
          INSPECT !1 CONVERTING
          "abcdefghijklmnopqrstuvwxyz" TO
          "ABCDEFGHIJKLMNOPQRSTUVWXYZ"#
  *
   A1100-PROMPT.
       MOVE SPACES                  TO READ-BUFF.
       ACCEPT READ-BUFF FREE.
       %UPSHIFT(READ-BUFF#).
       IF READ-BUFF(1:1) = ":"
          %COMIMAGE(READ-BUFF(2:76)#)
          GO TO A1100-PROMPT.
       IF READ-BUFF(1:1) = "%"
          MOVE READ-BUFF(2:76)      TO MPEX-BUFF
          PERFORM G2000-MPEX      THRU G2000-EXIT
          GO TO A1100-PROMPT.
  *
   G2000-MPEX.
       IF MPEX-PIN = 0
          CALL INTRINSIC "CREATEPROCESS" USING MPEX-ERRORS,
                                               MPEX-PIN,
                                               MPEX-FILE,
                                               MS-I, MS-IN
          IF MPEX-ERRORS <> 0
             DISPLAY "Failure in CREATEPROCESS: " MPEX-ERRORS
             GO TO G2000-EXIT.
       CALL INTRINSIC 'SENDMAIL' USING MPEX-PIN, MSG-LEN,
                                       MPEX-BUFF, 0
                                GIVING MAIL-STAT.
       IF CC <> 0
          DISPLAY "Failure in SENDMAIL: " MAIL-STAT
          GO TO G2000-EXIT.
       CALL INTRINSIC 'ACTIVATE' USING MPEX-PIN, 3
       IF CC <> 0
          DISPLAY "Failure in ACTIVATE".
   G2000-EXIT.  EXIT.
  *

The first thing you should notice is that I am allowing both MPE commands and MPEX commands to be executed. If a command is prefaced with a colon then I give it to the COMMAND intrinsic. If it is prefaced with a percent sign, then I pass it to MPEX.

In the G2000-MPEX paragraph, I first check the PIN for MPEX to see if it is zero. If it is, then we need to create MPEX as a child process and pass it the command through the SENDMAIL intrinsic. (We could pass it as an INFO string through CREATEPROCESS, but that wouldn’t let us just keep passing commands to it.) We then need to ‘ACTIVATE’ MPEX. Once we activate MPEX it will execute the command we passed it in SENDMAIL and then return control back to the parent process. It essentially goes to sleep until it gets another command through the SENDMAIL intrinsic.

That’s really all there is to it. There aren’t a lot of steps, but you need to know what those steps are, and hopefully I have laid them out for you here. Sometime you should just try going through the intrinsics manual looking for interesting things to use. That is how I learned these tricks.

Shawn Gordon, whose S.M. Gordon & Associates firm supplies HP 3000 utilities, has worked with 3000s since 1983.

 


Copyright The 3000 NewsWire. All rights reserved.