Skip to main content

Problem:

demonstration is attached.

It contains

I) ==================

firts a COBOL code, named pipeCob.cbl,

which uses UNIX primitives: pipe & write and read and close

To WRITE in a  pipe & READ from the pipe

II) ==================

A C code named pipeCob.c which

....creates a pipe

....calls COBOL ( CobolWrtPipe.cbl) ) passing to COBOL the pipe File descriptor

... .. .. the Cobol Function writes in the pipe

... Back in C code, the C code, thru the use of the read function, reads the content of the pipe filled by the COBOL function above

Resolution:

I) ==================

Sample Cobol code which uses UNIX primitives pipe & write & read & close to I-O on a pipes

Cob -x pipecob.cbl

pipeCob.cbl

       WORKING-STORAGE SECTION.

       01 int pic s9(9) comp-5 is typedef.

       01 fildes.

          02 fd0Read  int.

          02 fd1Write int.

       01 ret    int.

       78 ConstBufLen value 100.

       78 bufConst value "I-O_on_pipe".

       01 buf    pic x(ConstBufLen) value spaces.

       01 bufLen int value ConstBufLen.

       01 offset int value 0.

       01 i      pic 999 value 0.

       78 iMax   value 5.   

       PROCEDURE DIVISION.

         call "pipe" using fildes

                     returning ret

         display "*--> Result call  pipe: " ret

        perform varying i from 1 by 1 until i = Imax

         initialize buf

         string bufConst delimited by space

                i        delimited by size

            into buf     

         call "write" using by value     fd1Write

                            by reference buf

                            by value     bufLen

                      returning          ret     

         display "*--> Result call write: " ret

         if ret not = -1

         display "*--> Result call write: " buf

         end-if

        end-perform

       

         initialize buf

        perform varying i from 1 by 1 until i = Imax

         call "read" using by value      fd0Read

                           by reference  buf

                           by value      buflen

                           by value      offset

                     returning           ret

         display "*--> Result call  read: " ret  

         if ret not = -1

         display "*--> Result call  read: " offset "/" buf

         add ret to offset

         end-if

        end-perform

         call "close" using  by value    fd0Read

                      returning          ret

         display "*--> Result call close: " ret

         call "close" using  by value    fd1Write

                      returning          ret

         display "*--> Result call close: " ret

pipeCob.log = Trace of the execution of the code:

*--> Result call  pipe: 0000000000

*--> Result call write: 0000000100

*--> Result call write: I-O_on_pipe001                                                                                      

*--> Result call write: 0000000100

*--> Result call write: I-O_on_pipe002                                                                                      

*--> Result call write: 0000000100

*--> Result call write: I-O_on_pipe003                                                                                      

*--> Result call write: 0000000100

*--> Result call write: I-O_on_pipe004                                                                                      

*--> Result call  read: 0000000100

*--> Result call  read: 0000000000/I-O_on_pipe001                                                                                      

*--> Result call  read: 0000000100

*--> Result call  read: 0000000100/I-O_on_pipe002                                                                                      

*--> Result call  read: 0000000100

*--> Result call  read: 0000000200/I-O_on_pipe003                                                                                      

*--> Result call  read: 0000000100

*--> Result call  read: 0000000300/I-O_on_pipe004                                                                                      

*--> Result call close: 0000000000

*--> Result call close: 0000000000

II) ==================

C Creates pipe & call cobol which writes in pipe & C read content of the pipe filled by  COBOL

cob -x PipeCob.c  CobolWrtPipe.cbl

Pipecob.c

#include <unistd.h>

#include <stdio.h>

#define MSGSIZE  100

char *msg1 = "hello #1";

char *msg2 = "hello #2";

char *msg3 = "hello #3";

main()

{  char inbuf[MSGSIZE];

   int p[2], j, k;

   /* open pipe */

   if(pipe(p) == -1)

   {    perror("pipe call error");

        exit(1);

   }

  

   /* write down pipe */

   write(p[1], msg1, MSGSIZE);

   write(p[1], msg2, MSGSIZE);

   write(p[1], msg3, MSGSIZE);

   /* read pipe */

   for(j=0; j<3; j )

   {   read(p[0], inbuf, MSGSIZE);

       printf("%s\\n", inbuf);

   }

   k = CobolWrtPipe(&p);

   k--;

   for(j=0; j<k; j )

   {   read(p[0], inbuf, MSGSIZE);

       printf("%s\\n", inbuf);

   }

   exit(0);

}

CobolWrtPipe.cbl

       WORKING-STORAGE SECTION.

       01 int pic s9(9) comp-5 is typedef.

       01 ret    int.

       01 O-NODELAY int value 0.

       78 ConstBufLen value 100.

       78 bufConst value "I-O_on_pipe".

       01 buf    pic x(ConstBufLen) value spaces.

       01 bufLen int value ConstBufLen.

       01 offset int value 0.

       01 i      pic 999 value 0.

       78 iMax   value 5.   

       linkage section.

       01 fildes.

          02 fd0Read  int.

          02 fd1Write int.

       PROCEDURE DIVISION using by reference fildes.

        perform varying i from 1 by 1 until i = Imax

         initialize buf

         string bufConst delimited by space

                i        delimited by size

            into buf     

         move low-value to buf(buflen : 1)

         call "write" using by value     fd1Write

                            by reference buf

                            by value     bufLen

                      returning          ret     

         display "*--> Result call write: " ret

         if ret not = -1

         display "*--> Result call write: " buf

         end-if

        end-perform

       

        exit program returning Imax.        

CobolWrtPipe.log

See below that COBOL has written in the pipe and C has read the pipe

hello #1                                                          Begin  C printf

hello #2

hello #3                                                          End C printf

*--> Result call write: 0000000100             Begin COBOL DISPLAY

*--> Result call write: I-O_on_pipe001                                                                                      

*--> Result call write: 0000000100

*--> Result call write: I-O_on_pipe002                                                                                      

*--> Result call write: 0000000100

*--> Result call write: I-O_on_pipe003                                                                                      

*--> Result call write: 0000000100

*--> Result call write: I-O_on_pipe004          End COBOL DISPLAY                                               

I-O_on_pipe001                                             Begin  C printf

I-O_on_pipe002                                                                                    

I-O_on_pipe003                                                                                    

I-O_on_pipe004                                             End C printf

Attachments:

CpipeCobol.tar

Old KB# 2354