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:
Walter Murray <[log in to unmask]>
Reply To:
Walter Murray <[log in to unmask]>
Date:
Fri, 27 Feb 1998 23:22:35 GMT
Content-Type:
text/plain
Parts/Attachments:
text/plain (85 lines)
Calling the PAUSE intrinsic from COBOL shouldn't be that
difficult!  Here's some code I wrote a few years ago.  Perhaps
somebody will find it useful.  It's also available as Response
Center Engineering Note A3043325.

Walter Murray
Hewlett-Packard
Support Technology Lab

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

PROBLEM TEXT

I need to call the PAUSE intrinsic from COBOL.  I would like sample code
that would work on both MPE V and MPE/iX.

RESOLUTION TEXT

The following sample code will work on both MPE V and MPE/iX, in both
Compatibility Mode and Native Mode.

Because COBOL II does not support real numbers, the key is to call
HPEXTIN to convert from "external" (COBOL DISPLAY) format to "internal"
(floating-point) format.  In this sample, the .LOC. pseudo-intrinsic is
used to capture the length of the field to be converted; moving 6 to
STRINGLEN would have worked as well.

Following is the COBOL subprogram.

     $CONTROL DYNAMIC
      IDENTIFICATION DIVISION.
      PROGRAM-ID. EZPAUSE.
     *
     *    This is a "universal" subroutine for calling the PAUSE
     *    intrinsic from COBOL.  This source file can be compiled
     *    in any of the following environments.
     *
     *    * ANSI74 or ANSI85.
     *    * COBOL II on MPE V systems.
     *    * Compatibility mode COBOL II on MPE/iX systems.
     *    * Native mode COBOL II/iX on MPE/iX systems.
     *
     *    The subroutine can reside in a USL, an RL, an SL,
     *    an NMOBJ file, or an XL.  Or use this as sample code
     *    showing how to call PAUSE directly from your program.
     *
      DATA DIVISION.
      WORKING-STORAGE SECTION.
      77  STRINGLEN        PIC S9(4)    COMP.
      77  REAL-NUMBER      PIC S9(9)    COMP.
      77  ERR-OR           PIC S9(4)    COMP.
      LINKAGE SECTION.
      77  PAUSE-SECONDS    PIC 9(6).
      PROCEDURE DIVISION USING PAUSE-SECONDS.
      BEGIN.
          CALL INTRINSIC ".LEN." USING PAUSE-SECONDS GIVING STRINGLEN.
          CALL "HPEXTIN" USING
                  @PAUSE-SECONDS, STRINGLEN,
                  \0\, \1\, \0\, \0\,
                  REAL-NUMBER,  ERR-OR.
          CALL INTRINSIC "PAUSE" USING REAL-NUMBER.
          EXIT PROGRAM.

Following is a test program that calls the subprogram shown above.

      IDENTIFICATION DIVISION.
      PROGRAM-ID. MURRAY.
     *
     *    This test program calls "EZPAUSE" twice, first to
     *    pause for 8 seconds, then for 3 seconds.
     *
      DATA DIVISION.
      WORKING-STORAGE SECTION.
      77  PAUSE-SECONDS    PIC 9(6).
      PROCEDURE DIVISION.
      BEGIN.
          DISPLAY "BEGIN".
          MOVE 8 TO PAUSE-SECONDS.  CALL "EZPAUSE" USING PAUSE-SECONDS.
          DISPLAY "THREE MORE SECONDS".
          MOVE 3 TO PAUSE-SECONDS.  CALL "EZPAUSE" USING PAUSE-SECONDS.
          DISPLAY "END".
          STOP RUN.

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

ATOM RSS1 RSS2