Converting Image File into Binary Code in VC

I am trying to convert a .png file into binary code in Visual COBOL. Here is what I have 

IDENTIFICATION DIVISION.
PROGRAM-ID. ImageToBinary.

ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.

SELECT IMAGE-FILE ASSIGN TO 'image.jpg'
ORGANIZATION IS LINE SEQUENTIAL.

DATA DIVISION.
FILE SECTION.
FD IMAGE-FILE.
01 IMAGE-RECORD PIC X(1024).

WORKING-STORAGE SECTION.
01 WS-END-OF-FILE PIC X(1) VALUE 'N'.
01 WS-BINARY-DATA PIC X(1024).
01 WS-IMAGE-BUFFER PIC X(1024) OCCURS 100 TIMES.
01 WS-BUFFER-INDEX PIC 9(4) VALUE 1.
01 WS-IMAGE-SIZE PIC 9(9) VALUE 0.

PROCEDURE DIVISION.
BEGIN.

OPEN INPUT IMAGE-FILE.

PERFORM UNTIL WS-END-OF-FILE = 'Y'
      READ IMAGE-FILE INTO IMAGE-RECORD
          AT END
                 MOVE 'Y' TO WS-END-OF-FILE
          NOT AT END
                MOVE IMAGE-RECORD TO WS-BINARY-DATA
                MOVE WS-BINARY-DATA TO WS-IMAGE-BUFFER(WS-BUFFER-INDEX)
                ADD 1 TO WS-BUFFER-INDEX
               ADD 1024 TO WS-IMAGE-SIZE
       END-READ
END-PERFORM.

CLOSE IMAGE-FILE
DISPLAY "Image Size: " WS-IMAGE-SIZE " bytes"
DISPLAY "Binary data stored in WS-IMAGE-BUFFER."
STOP RUN.


This code, however, does not work. When I read the image file into IMAGE-RECORD, it is blank. I am using Visual COBOL v9 on a Windows 10 pro. Thanks in advance.

  • 0  

    A line sequential file is a set of records delimited by CRLF characters. This cannot be used to read in a binary file.

    I would recommend using the byte stream library routines, CBL_OPEN_FILE and CBL_READ_FILE to accomplish this.

    Chris Glazier
    Rocket Software - Principal Technical Support Specialist
    If you found this post useful, give it a “Like” or click on "Verify Answer" under the "More" button

  • 0  

    What do you want to do with this file?
    Chris give a correct answer!
    there are other programs to works/integrate  with grafic file, a example is irfanview

  • 0 in reply to   

    Chris,

     I have the following code:

     

    WORKING-STORAGE

    01 IMAGE-FILE PIC X(16) VALUE 'C:\image.PNG'.

     PROCEDURE DIVISION.

     

               CALL "CBL_OPEN_FILE" USING IMAGE-FILE

                                RETURNING STATUS-CODE

               END-CALL.

    However, it returns a strange status code that looks like a 'u'. The hex display for the status code is H"B5". The CALL statement is unable to read the image file.

  • 0 in reply to   

    Greiner,

    I am trying to print an image file using PCL language but in order to do that, I need to get the binary code for the image which I am trying to do with COBOL. 

  • 0   in reply to 

    It is not so simple, do you have read the help and See the example for this

    you must define more and read the Bytes you had define until eof!

  • 0   in reply to 

    Here is ab example:

           identification division.
           program-id. Program1.
    
           environment division.
           configuration section.
    
           data division.
           working-storage section.
           01 data-buffer    pic x(1000) value spaces.
           01 filename       pic x(30) value "myfile.jpg".
           01 access-mode    pic x comp-x value 67. *> read-write and > 4gb.
           01 deny-mode      pic x comp-x value 3.
           01 device         pic x comp-x value 0.
           01 file-handle    pic x(4) comp-5 value zeroes.
           01 file-offset    pic x(8) comp-x.
           01 byte-count     pic x(8) comp-x.
           01 flags          pic x comp-x.
           procedure division.
    
               call "CBL_OPEN_FILE"
                  using filename
                        access-mode
                        deny-mode
                        device
                        file-handle
               end-call
               if return-code not = 0
                   display "error on open = " return-code
                   stop run
               end-if
               move 128 to flags *> File-offset will contain the filesize
               call "CBL_READ_FILE"
                  using file-handle
                        file-offset
                        byte-count
                        flags
                        data-buffer
               end-call
               if return-code not = 0
                   display "error on get filesize = " return-code
                   stop run
               end-if
    
               move 0 to flags
               move file-offset to byte-count *> read the entire file
                                              *> buffer must be large enough
               move 1 to file-offset
               call "CBL_READ_FILE" using file-handle
                                          file-offset
                                          byte-count
                                          flags
                                          data-buffer
               end-call
               if return-code not = 0
                   display "error on get filesize = " return-code
                   stop run
               end-if
    
               goback.
    
           end program Program1.
    

    Chris Glazier
    Rocket Software - Principal Technical Support Specialist
    If you found this post useful, give it a “Like” or click on "Verify Answer" under the "More" button

  • 0 in reply to   

    Chris,

    The code you provided works as it does not return an error. But I am still trying to understand how to obtain the binary code of my image. Where does it store the binary code when the call "CBL_READ_FILE" executes?

  • 0   in reply to 

    It reads the number of bytes specified in byte-count into the data-buffer data-item. The first call to cbl_read_file with a flag value of 128 simply returns the size of the file into the file-offset data-item. So I move the size of the file from file-offset to byte-count and then the second call to cbl_read_file will read the contents of the file into data-buffer. This example is very simple and assumes that the file is not greater than 1000 bytes which is the size of data-buffer. 

    Are you sure that the PCL command requires the actual image to be embedded in the PCL stream and not just a filename of an image to load?

    Chris Glazier
    Rocket Software - Principal Technical Support Specialist
    If you found this post useful, give it a “Like” or click on "Verify Answer" under the "More" button

  • 0 in reply to   

    Chris,

    Thank you for the explanation. The image file is 14kb and I therefore increased the data-buffer to 14000.  However, the data-buffer is blank when I execute both CBL_READ_FILE commands. No, I am not sure if the PCL command requires the actual image to be embedded in the PCL stream. The PCL printer language protocol was developed by Hewlett-Packard and they have documentation on PCL commands. I am still parsing through their manual, but I am not having any luck with regards to printing image files with PCL commands. The resources I have encountered suggest that printing an image in PCL requires the binary data of the image to be printed.

  • 0   in reply to 

    Sorry, I had one of the data items defined incorrectly.

    Please change byte-count from pic x(8) comp-x to pic x(4) comp-x.

    01 byte-count     pic x(4) comp-x.

    Chris Glazier
    Rocket Software - Principal Technical Support Specialist
    If you found this post useful, give it a “Like” or click on "Verify Answer" under the "More" button