Skip to main content

We have a system that uses DB2 database. We need to have this system now use an Oracle Database for one particular customer. We thought the easiest way to achieve this would be to simply use ODBC so that (in theory) we should have minimum changes.


First test was to be able to access the existing DB2 database but via DB2 ODBC driver. First problem to arise was related to some strange (for historic reasons - no surprise) record layouts that we have. For example, we have the following code:

01  WS-DATA.

     03 WS-A        PIC X.

     03 WS-B        PIC  S9(4) COMP-5.

     03 WS-C        PIC X.

      
CREATE TABLE MYTABLE (MY_CODE SMALLINT NOT NULL, MY_DATA CHAR(254) FOR BIT DATA)

MOVE "A" TO WS-A

MOVE 1 TO WS-B.

MOVE "C" TO WS-C.

MOVE 1 TO WS-SQL-CODE

INSERT INTO MYTABLE VALUES(:WS-SQL-CODE,:WS-DATA)

COMMIT

SELECT MY_DATA INTO :WS-DATA FROM MYTABLE WHERE MY_CODE = 1

At this point, the WS-A field has "A", WS-B is 'corrupt' and WS-C has spaces.

The reason why WS-B is corrupt is that prior to performing the INSERT, this field had X"00" and X"01" in it. This represented zero in comp-5. When I read it back in, I had X"00" followed by x"20". It looks to me like it is not handling the 'FOR BIT DATA' clause correctly. I don't know if this is a DB2 ODBC driver issue or a COBOL issue (and therefore not something I should be bothering MF with).

In an attempt to find out, I tried to run the same program using a Oracle database source and Oracle ODBC driver. Unfortunately, the program experiences a 907 error on the CREATE TABLE statement. This is being caused by the 'FOR BIT DATA' clause.

Any ideas chaps?

We have a system that uses DB2 database. We need to have this system now use an Oracle Database for one particular customer. We thought the easiest way to achieve this would be to simply use ODBC so that (in theory) we should have minimum changes.


First test was to be able to access the existing DB2 database but via DB2 ODBC driver. First problem to arise was related to some strange (for historic reasons - no surprise) record layouts that we have. For example, we have the following code:

01  WS-DATA.

     03 WS-A        PIC X.

     03 WS-B        PIC  S9(4) COMP-5.

     03 WS-C        PIC X.

      
CREATE TABLE MYTABLE (MY_CODE SMALLINT NOT NULL, MY_DATA CHAR(254) FOR BIT DATA)

MOVE "A" TO WS-A

MOVE 1 TO WS-B.

MOVE "C" TO WS-C.

MOVE 1 TO WS-SQL-CODE

INSERT INTO MYTABLE VALUES(:WS-SQL-CODE,:WS-DATA)

COMMIT

SELECT MY_DATA INTO :WS-DATA FROM MYTABLE WHERE MY_CODE = 1

At this point, the WS-A field has "A", WS-B is 'corrupt' and WS-C has spaces.

The reason why WS-B is corrupt is that prior to performing the INSERT, this field had X"00" and X"01" in it. This represented zero in comp-5. When I read it back in, I had X"00" followed by x"20". It looks to me like it is not handling the 'FOR BIT DATA' clause correctly. I don't know if this is a DB2 ODBC driver issue or a COBOL issue (and therefore not something I should be bothering MF with).

In an attempt to find out, I tried to run the same program using a Oracle database source and Oracle ODBC driver. Unfortunately, the program experiences a 907 error on the CREATE TABLE statement. This is being caused by the 'FOR BIT DATA' clause.

Any ideas chaps?

ODBC uses a different set of data types and the types used in DCL statements like CREATE TABLE are specific to the ODBC driver being used.
It does not appear that FOR BIT DATA is supported for Oracle at least.

Try adding the directive SQL(ALLOWNULLCHAR)

This allows programs to use PIC X(n) host variables, and to select/insert/update hexadecimal characters in CHAR columns without changing source to use SQL TYPE BINARY host variables.

I got your example to work under Oracle using the Oracle ODBC driver but I had to make a few changes because the group item was not valid as a host variable.

The following worked for me:

      $set sql(dbman=odbc allownullchar)
       program-id.   oraodbc.
       working-storage section.
       exec sql include sqlca end-exec
       01 my-field        pic x(4).
       01 WS-DATA redefines my-field.
          03 WS-A        PIC X.
          03 WS-B        PIC  S9(4) COMP-5.
          03 WS-C        PIC X.
       01 ws-sql-code     pic s9(4) comp-5.
       procedure division.

          exec sql connect to "testora32"
             user "scott.tiger"
          end-exec
          display sqlcode
          exec sql drop table MYTABLE end-exec
          display sqlcode
          exec sql CREATE TABLE MYTABLE (MY_CODE SMALLINT NOT NULL,
             MY_DATA CHAR(254)) end-exec

          MOVE "A" TO WS-A
          MOVE 1 TO WS-B
          MOVE "C" TO WS-C
          MOVE 1 TO WS-SQL-CODE

          exec sql INSERT INTO MYTABLE (MY_CODE, MY_DATA)
             VALUES(:WS-SQL-CODE,:my-field)
          end-exec

          exec sql COMMIT end-exec
          move spaces to my-field
          exec sql
             SELECT MY_DATA INTO :my-field
                FROM MYTABLE WHERE MY_CODE = 1
          end-exec
          display sqlcode
          exec sql disconnect current end-exec
          stop run.


We have a system that uses DB2 database. We need to have this system now use an Oracle Database for one particular customer. We thought the easiest way to achieve this would be to simply use ODBC so that (in theory) we should have minimum changes.


First test was to be able to access the existing DB2 database but via DB2 ODBC driver. First problem to arise was related to some strange (for historic reasons - no surprise) record layouts that we have. For example, we have the following code:

01  WS-DATA.

     03 WS-A        PIC X.

     03 WS-B        PIC  S9(4) COMP-5.

     03 WS-C        PIC X.

      
CREATE TABLE MYTABLE (MY_CODE SMALLINT NOT NULL, MY_DATA CHAR(254) FOR BIT DATA)

MOVE "A" TO WS-A

MOVE 1 TO WS-B.

MOVE "C" TO WS-C.

MOVE 1 TO WS-SQL-CODE

INSERT INTO MYTABLE VALUES(:WS-SQL-CODE,:WS-DATA)

COMMIT

SELECT MY_DATA INTO :WS-DATA FROM MYTABLE WHERE MY_CODE = 1

At this point, the WS-A field has "A", WS-B is 'corrupt' and WS-C has spaces.

The reason why WS-B is corrupt is that prior to performing the INSERT, this field had X"00" and X"01" in it. This represented zero in comp-5. When I read it back in, I had X"00" followed by x"20". It looks to me like it is not handling the 'FOR BIT DATA' clause correctly. I don't know if this is a DB2 ODBC driver issue or a COBOL issue (and therefore not something I should be bothering MF with).

In an attempt to find out, I tried to run the same program using a Oracle database source and Oracle ODBC driver. Unfortunately, the program experiences a 907 error on the CREATE TABLE statement. This is being caused by the 'FOR BIT DATA' clause.

Any ideas chaps?

Can we clone you Chris?

Thanks


We have a system that uses DB2 database. We need to have this system now use an Oracle Database for one particular customer. We thought the easiest way to achieve this would be to simply use ODBC so that (in theory) we should have minimum changes.


First test was to be able to access the existing DB2 database but via DB2 ODBC driver. First problem to arise was related to some strange (for historic reasons - no surprise) record layouts that we have. For example, we have the following code:

01  WS-DATA.

     03 WS-A        PIC X.

     03 WS-B        PIC  S9(4) COMP-5.

     03 WS-C        PIC X.

      
CREATE TABLE MYTABLE (MY_CODE SMALLINT NOT NULL, MY_DATA CHAR(254) FOR BIT DATA)

MOVE "A" TO WS-A

MOVE 1 TO WS-B.

MOVE "C" TO WS-C.

MOVE 1 TO WS-SQL-CODE

INSERT INTO MYTABLE VALUES(:WS-SQL-CODE,:WS-DATA)

COMMIT

SELECT MY_DATA INTO :WS-DATA FROM MYTABLE WHERE MY_CODE = 1

At this point, the WS-A field has "A", WS-B is 'corrupt' and WS-C has spaces.

The reason why WS-B is corrupt is that prior to performing the INSERT, this field had X"00" and X"01" in it. This represented zero in comp-5. When I read it back in, I had X"00" followed by x"20". It looks to me like it is not handling the 'FOR BIT DATA' clause correctly. I don't know if this is a DB2 ODBC driver issue or a COBOL issue (and therefore not something I should be bothering MF with).

In an attempt to find out, I tried to run the same program using a Oracle database source and Oracle ODBC driver. Unfortunately, the program experiences a 907 error on the CREATE TABLE statement. This is being caused by the 'FOR BIT DATA' clause.

Any ideas chaps?

Also, the reason you had the issue regarding the group item is that I also have it, but gave you the simplified version of events. Our live programs actually move the record to a dummy data item.