HP 3000 Manuals

Sample Programs: NOWAIT I O [ Interprocess Communication:Programmer's Guide ] MPE/iX 5.0 Documentation


Interprocess Communication:Programmer's Guide

Appendix C  Sample Programs:  NOWAIT I/O 

This appendix contains two programs (Example C-1 in COBOL, and Example
C-2 in FORTRAN) which illustrate the use of NOWAIT I/O in Interprocess
Communication.  Software interrupts are not used in these examples; see
Appendix D for sample programs illustrating their use.

Example C-1. 

     001000*
     001100*   NOWAITRD
     001200*
     001300*   Compiled with COBOLII.
     001400*
     001500*   This program has a background task that it does in a loop.  After
     001600*   each pass through the loop it checks a message file to see if a
     001700*   special request has been made.  The check for the special request
     001800*   is made only at the completion of a pass through the loop, for two
     001900*   reasons.  First, the time it takes to make a pass through the loop
     002000*   is not too long for the special request to wait to be read.  Second,
     002100*   the special request may require the use of some of data structures
     002200*   used by the background task, and those data structures may be in an
     002300*   inconsistent state part way into a pass through the loop.  The
     002400*   message file is checked for records containing the special requests
     002500*   using NOWAIT FREADs.  Standard (wait) FREADs were not used because
     002600*   they would have caused this program to wait if the message file did
     002700*   not contain any records (and there was another program with this
     002800*   file open for write access), when what we want is to continue doing
     002900*   the background task in the loop.  Software interrupts were not used
     003000*   because they would try to receive a special request anywhere in the
     003100*   loop, and would have added complexity to provide features that this
     003200*   program does not need.
     003300*

     003400 IDENTIFICATION DIVISION.
     003500 PROGRAM-ID.    NOWAITRD.
     003600*
     003700 ENVIRONMENT DIVISION.
     003800 CONFIGURATION SECTION.
     003900 SOURCE-COMPUTER.  HP-SYSTEM.
     004000 OBJECT-COMPUTER.  HP-SYSTEM.
     004100 SPECIAL-NAMES.
     004200   CONDITION-CODE IS CC.
     004300*
     004400 DATA DIVISION.
     004500 WORKING-STORAGE SECTION.
     004600 01   IN-REC            PIC X(80).
     004700 01   TERM-REC          PIC X(80).
     004800 01   BACK-GROUND-MSG   PIC X(17)      VALUE "BACKGROUND WORK  ".
     004900 01   ERROR-MSG         PIC X(17)      VALUE "UNEXPECTED ERROR ".
     005000 01   IN-FILE-NAME      PIC X(9)       VALUE "MSGFILE1 ".
     005100 01   DONE              PIC X.
     005200   88 FINISHED                         VALUE IS "T".
     005300   88 NOTFINISHED                      VALUE IS "F".
     005400 01   PARM              PIC S9(4) COMP.
     005500 01   LNGTH             PIC S9(4) COMP.
     005600 01   IN-FILE           PIC S9(4) COMP.
     005700 01   LOOP-COUNTER      PIC S9(4) COMP.
     005800 01   MSG-FLAG          PIC S9(4) COMP.
     005900*
     006000 PROCEDURE DIVISION.
     006100*
     006200 100-START-OF-PROGRAM.
     006300     MOVE 0 TO LOOP-COUNTER.
     006400     CALL INTRINSIC "FOPEN" USING IN-FILE-NAME %5 %4000
     006500                            GIVING IN-FILE.
     006600     IF CC NOT = 0 THEN
     006700       PERFORM 900-ERROR-CONDITION.
     006800*
     006900*    Set up extended waits on read-file.
     007000*
     007100*    This will cause IODONTWAIT to indicate that the record is still
     007200*    unavailable rather than returning an End-Of-File error if the
     007300*    writer program terminates.
     007400*
     007500     MOVE 1 TO PARM.
     007600     CALL INTRINSIC "FCONTROL" USING IN-FILE 45 PARM.
     007700     IF CC NOT = 0 THEN
     007800       PERFORM 900-ERROR-CONDITION.
     007900*
     008000*    Start the first read on the message file.
     008100*
     008200     PERFORM 600-START-NEXT-READ.
     008300*
     008400     MOVE "F" TO DONE.
     008500     PERFORM 200-PROCESSING-LOOP UNTIL FINISHED.
     008600*
     008700*    Abort the outstanding read (PARM is ignored) and close the msg file.
     008800*
     008900     CALL INTRINSIC "FCONTROL" USING IN-FILE 43 PARM.
     009000     IF CC NOT = 0 THEN
     009100       PERFORM 900-ERROR-CONDITION.
     009200     CALL INTRINSIC "FCLOSE" USING IN-FILE 0 0.
     009300     IF CC NOT = 0 THEN
     009400       PERFORM 900-ERROR-CONDITION.
     009500     STOP RUN.
     009600*
     009700 200-PROCESSING-LOOP.
     009800*
     009900*    Each pass through this loop we do one iteration of the "background
     010000*    task" and then we test to see if a message has come in.
     010100*
     010200     PERFORM 300-BACKGROUND-TASK.
     010300     PERFORM 400-CHECK-FOR-MSG.
     010400*
     010500 300-BACKGROUND-TASK.
     010600*
     010700*    This could be any background processing, but in our case it is
     010800*    just a display.
     010900*
     011000     PERFORM 700-CPU-WASTER 10000 TIMES.
     011100     ADD 1 TO LOOP-COUNTER.
     011200     IF LOOP-COUNTER = 100 THEN
     011300       MOVE "T" TO DONE.
     011400     DISPLAY BACK-GROUND-MSG.
     011500*

     011600 400-CHECK-FOR-MSG.
     011700*
     011800*    Call IODONTWAIT to see if a record has been written to the
     011900*    message file.  Whether or not a message is there, IODONTWAIT
     012000*    will always return immediately.
     012100*
     012200     CALL INTRINSIC "IODONTWAIT" USING IN-FILE IN-REC LNGTH
     012300                                 GIVING MSG-FLAG.
     012400     IF CC NOT = 0 THEN
     012500       PERFORM 900-ERROR-CONDITION.
     012600*
     012700*    MSG-FLAG will be non-zero (= file number) if a message was received.
     012800*    If a message was received, handle it and re-start the next read on
     012900*    the message file.
     013000*
     013100     IF MSG-FLAG NOT = 0 THEN
     013200       PERFORM 500-HANDLE-MSG
     013300       PERFORM 600-START-NEXT-READ.
     013400*
     013500 500-HANDLE-MSG.
     013600*
     013700*    Do any processing that is required to handle the incoming message.
     013800*
     013900     MOVE IN-REC TO TERM-REC.
     014000     DISPLAY TERM-REC.
     014100*
     014200 600-START-NEXT-READ.
     014300*
     014400*    Start the NOWAIT FREAD.  It will be completed by IODONTWAIT.  Note
     014500*    that NOWAIT FREADs on message files do not require Priv Mode.
     014600*
     014700     MOVE -80 TO LNGTH.
     014800     CALL INTRINSIC "FREAD" USING IN-FILE IN-REC LNGTH.
     014900     IF CC NOT = 0 THEN
     015000       PERFORM 900-ERROR-CONDITION.
     015100*
     015200 700-CPU-WASTER.
     015300*
     015400*    This is here just to burn up time.  Real work should be done here.
     015500*    DO NOT put a "CPU waster" like this in a real program.
     015600*
     015700     MOVE SPACES TO TERM-REC.
     015800*
     015900 900-ERROR-CONDITION.
     016000     DISPLAY ERROR-MSG.
     016100     CALL INTRINSIC "PRINTFILEINFO" USING IN-FILE.
     016200     STOP RUN.

Example C-2. 

     $CONTROL USLINIT
     $STANDARD_LEVEL SYSTEM
     C
            PROGRAM NOWAITREAD
     C
     C      Compiled with FORTRAN 77.
     C
     C      This program reads messages from both a terminal and a message
     C      file, and processes them.  When not processing a message, the
     C      program just waits for the next message.  This program uses
     C      NOWAIT I/O because it allows it to start FREADs on both the
     C      terminal and the message file, and then wait in a single
     C      "IOWAIT(0,... " statement for whichever FREAD is finished first.
     C
            INTEGER*2        fnum,fnumterm,fnuminfile,fnumoutfile
            INTEGER*2        tcount,length,condcode
            LOGICAL          buf(40)
            LOGICAL          eof
            SYSTEM INTRINSIC GETPRIVMODE,GETUSERMODE,FOPEN,FREAD,IOWAIT
            SYSTEM INTRINSIC FWRITE,FCLOSE,PRINTFILEINFO
     C
     C
     C      Priv Mode needed to open the terminal for NOWAIT I/O.  Must
     C      also PREP with PM.
     C      foption = $STDIN, ascii, old. aoption = no wait I/O, read access.
     C
            CALL GETPRIVMODE
            fnumterm = FOPEN(  , 45B, 4000B)
            IF (CCODE() .NE. 0) THEN
               CALL PRINTFILEINFO( fnumterm )
               STOP ' Error occured during terminal FOPEN '
            END IF
            CALL GETUSERMODE
     C
     C      Open the input message file.
     C      foption = ascii, old.   aoption = no wait I/O, read access.
     C
            fnuminfile = FOPEN( "MSGFILE1", 5B, 4000B)
            IF (CCODE() .NE. 0) THEN
               CALL PRINTFILEINFO( fnuminfile )
               STOP ' Error occured during input message file FOPEN '
            END IF
     C
     C      Open the output message file.
     C      foption = ascii, old.   aoption = write access.
     C

            fnumoutfile = FOPEN( "MSGFILE2", 5B, 1B)
            IF (CCODE() .NE. 0) THEN
               CALL PRINTFILEINFO( fnumoutfile )
               STOP ' Error occured during output message file FOPEN '
            END IF
     C
     C      Start the read on the terminal.  No Wait FREADs always return
     C      a length of 0.  The real data length is returned by IOWAIT.
     C
            tcount = -80
            length = FREAD( fnumterm, ibuf, tcount)
            IF (CCODE() .NE. 0) THEN
               CALL PRINTFILEINFO( fnumterm )
               STOP ' Error occured during the terminal FREAD '
            END IF
     C
     C      Start the read on the message file.  No Wait FREADs always return
     C      a length of 0.  The real data length is returned by IOWAIT.
     C
            tcount =  -80
            length = FREAD( fnuminfile, buf, tcount)
            IF (CCODE() .NE. 0) THEN
               CALL PRINTFILEINFO( fnuminfile )
               STOP ' Error occured during the message file FREAD '
            END IF
     C
            eof = .FALSE.
            DO WHILE (.NOT. eof)
     C
     C         An IOWAIT with file-number = 0 will complete whichever
     C         FREAD is ready to be finished first.
     C
               fnum = IOWAIT( 0, buf, tcount)
               condcode = CCODE()
               IF (condcode .EQ. -1) THEN    ! Error
                  CALL PRINTFILEINFO( fnum )
                  STOP ' Error occured during IOWAIT '
               END IF
               IF (condcode .EQ. 1) THEN     ! EOF
                  eof = .TRUE.
               END IF
               IF (condcode .EQ. 0) THEN
     C
     C            Process the message that came in;  in this case write it to
     C            "message file 2".  FREAD and FWRITE want byte lengths to be
     C            negative.  IOWAIT returns a positive byte length.  We have
     C            to change the sign.
     C
                  tcount = - tcount
                  CALL FWRITE( fnumoutfile, buf, tcount, 0)
                  IF (CCODE() .NE. 0) THEN
                     CALL PRINTFILEINFO( fnumoutfile )
                     STOP ' Error occured during FWRITE '
                  END IF

     C
     C            Re-start the FREAD that the IOWAIT just completed.
     C
                  tcount = -80
                  length = FREAD( fnum, buf, tcount)
                  IF (CCODE() .NE. 0) THEN
                     CALL PRINTFILEINFO( fnum )
                     STOP ' Error occured during FREAD '
                  END IF
               END IF
            ENDDO
     C
     C      Time to shut down.
     C      Call FCONTROL-43 to abort the no wait read that is pending
     C      against the terminal and the message file.  If CCG is returned,
     C      then the abort could not complete, and an IOWAIT must be called
     C      to clear the I/O.  CCE means aborted OK.  CCG means nothing to
     C      abort, which is OK here because the read is not restarted if
     C      there was an error.
     C
            CALL FCONTROL( fnumterm, 43, 0)
            IF (CCODE() .EQ. 1) THEN
               fnum = IOWAIT( fnumterm, buf, tcount)
               IF (CCODE() .NE. 0) THEN
                  CALL PRINTFILEINFO( fnumterm )
                  STOP ' Error occured during terminal FCONTROL/IOWAIT '
               END IF
            END IF
            CALL FCONTROL( fnuminfile, 43, 0)
            IF (CCODE() .EQ. 1) THEN
               fnum = IOWAIT( fnuminfile, buf, tcount)
               IF (CCODE() .NE. 0) THEN
                  CALL PRINTFILEINFO( fnuminfile )
                  STOP ' Error occured during message file FCONTROL/IOWAIT '
               END IF
            END IF
     C
            CALL FCLOSE( fnumterm, 0, 0)
            CALL FCLOSE( fnuminfile, 0, 0)
            CALL FCLOSE( fnumoutfile, 0, 0)
     C
            STOP 'Successful'
            END


MPE/iX 5.0 Documentation