 |
» |
|
|
|
This appendix contains a group of sample programs illustrating
the use of File System features to perform Interprocess
Communication. Included are two simple COBOL programs
(Examples B-1 and B-2) that show the use of WAIT I/O for
interprocess communications. For sample programs showing
more complex forms of IPC, refer to Appendixes C and D. Example B-1.
001000*
001100* MSGWRTR
001200*
001300* Compiled with COBOLII.
001400*
001500* This program reads records from a terminal and writes
001600* the data to a message file, whose FILE STATUS is displayed.
001700* The message file must be built as follows:
001800*
001900* BUILD MSGFILE1;REC=-80,,F,ASCII;DISC=nnn;MSG
002000*
002100 IDENTIFICATION DIVISION.
002200 PROGRAM-ID. MSGWRTR.
002300*
002400 ENVIRONMENT DIVISION.
002500 INPUT-OUTPUT SECTION.
002600 FILE-CONTROL.
002700 SELECT WRITE-FILE ASSIGN TO "MSGFILE1"
002800 STATUS IS MSG-STAT.
002900*
003000 DATA DIVISION.
003100 FILE SECTION.
003200 FD WRITE-FILE.
003300 01 OUT-REC PIC X(80).
003400 WORKING-STORAGE SECTION.
003500 01 TERM-REC.
003600 02 END-REC PIC X(2).
003700 02 REST-REC PIC X(76).
003800 01 DONE PIC X.
003900 88 FINISHED VALUE IS "T".
004000 01 MSG-STAT PIC X(2).
004100*
004200 PROCEDURE DIVISION.
004300*
004400 100-START-OF-PROGRAM.
004500 OPEN OUTPUT WRITE-FILE.
004600 DISPLAY MSG-STAT.
004700 MOVE "F" TO DONE.
004800 PERFORM 200-GET-LINE UNTIL FINISHED.
004900 CLOSE WRITE-FILE.
005000 DISPLAY MSG-STAT.
005100 STOP RUN.
005200*
005300 200-GET-LINE.
005400 MOVE SPACES TO TERM-REC.
005500 ACCEPT TERM-REC.
005600 IF END-REC = "//" THEN
005700 MOVE "T" TO DONE
005800 ELSE
005900 WRITE OUT-REC FROM TERM-REC
006000 DISPLAY MSG-STAT
006100 IF MSG-STAT NOT = "00" THEN
006200* Error during write or file is full, stop writing.
006300 MOVE "T" TO DONE.
|
Example B-2.
001000*
001100* MSGREADR
001200*
001300* Compiled with COBOLII.
001400*
001500* This program reads records from the message file and processes them.
001600* It uses standard wait I/O because no other processing
001700* can be done while waiting for the record and wait I/O is simpler to
001800* use than no-wait I/O. Extended wait is used so this program
001900* will not get an (EOF) error if the file is empty and the program
002000* writing to it terminates. A 30-second timeout is used so that this
002100* program will not wait forever if the writer never comes back.
002200*
002300 IDENTIFICATION DIVISION.
002400 PROGRAM-ID. MSGREADR.
002500*
002600 ENVIRONMENT DIVISION.
002700 INPUT-OUTPUT SECTION.
002800 FILE-CONTROL.
002900 SELECT READ-FILE ASSIGN TO "MSGFILE1"
003000 STATUS IS MSG-STAT.
003100*
003200 DATA DIVISION.
003300 FILE SECTION.
003400 FD READ-FILE.
003500 01 IN-REC PIC X(80).
003600 WORKING-STORAGE SECTION.
003700 01 TERM-REC PIC X(78).
003800 01 DONE PIC X.
003900 88 FINISHED VALUE IS "T".
004000 88 NOTFINISHED VALUE IS "F".
004100 01 MSG-STAT PIC X(2).
004200 01 PARM PIC S9(4) COMP.
004300*
004400 PROCEDURE DIVISION.
004500*
004600 100-START-OF-PROGRAM.
004700 OPEN INPUT READ-FILE.
004800 DISPLAY MSG-STAT.
004900*
005000* Set up extended waits on read-file.
005100*
005200* The read will wait for a record to be written instead of
005300* returning an End-Of-File condition.
005400*
005500*
005600 MOVE 1 TO PARM.
005700 CALL INTRINSIC "FCONTROL" USING READ-FILE 45 PARM.
005800*
005900 MOVE "F" TO DONE.
006000 PERFORM 200-GET-LINE UNTIL FINISHED.
006100 CLOSE READ-FILE.
006200 DISPLAY MSG-STAT.
006300 STOP RUN.
006400*
006500 200-GET-LINE.
006600 MOVE SPACES TO TERM-REC.
006700*
006800* Set up 30-second timeout. We actually need to set the timeout only
006900* once for message files, but we set it here for each read in case
007000* message file timeouts are changed to work like terminal timeouts,
007100* which are valid only for the next I/O.
007200*
007300* Because extended waits were set up, we will wait forever on an
007400* empty message file. However, for esthetic reasons we don't want
007500* to wait forever. Neatness counts, so we set the read to fail
007600* if no data is in the message file after 30 seconds.
007700*
007800 MOVE 30 TO PARM.
007900 CALL INTRINSIC "FCONTROL" USING READ-FILE 4 PARM.
008000*
008100 READ READ-FILE INTO TERM-REC.
008200 IF MSG-STAT = "00" THEN
008300 PERFORM 300-WRITEREC
008400 ELSE
008500* Error or End-Of-File on the message file.
008600 DISPLAY MSG-STAT
008700 MOVE "T" TO DONE.
008800*
008900 300-WRITEREC.
009000*
009100* Process (in this case display) the record received from the
009200* message file.
009300*
009400 DISPLAY TERM-REC.
|
|