Created On:  13 July 2012

Problem:

There appears to be a problem when attempting to run an application that executes back to back SQL SELECT statements where arrays are being used when using OpenESQL and Oracle's 11g ODBC driver.

The same program runs fine when using Oracle's 10g ODBC driver.  The problem is that a Run-time error 114 occurs when executing the second SELECT.

Here is the program:

identification division.
program-id. Program1.
data division.
working-storage section.
EXEC SQL INCLUDE SQLCA END-EXEC.
EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 MY-ARRAY-FIELDS.
   05 ARRAY-FIELD1      PIC X(02) OCCURS 80.
   05 ARRAY-FIELD2      PIC X(02) OCCURS 80.
EXEC SQL END DECLARE SECTION END-EXEC.
procedure division.

   EXEC SQL CONNECT TO "oraconnect" USER "SCOTT/TIGER" END-EXEC.
   DISPLAY "SQLCODE IS " SQLCODE.
* First SQL statement
   EXEC SQL
      SELECT ARRAY1, ARRAY2
         INTO :ARRAY-FIELD1, :ARRAY-FIELD2
         FROM MYTABLE
         ORDER BY ARRAY1
   END-EXEC.
   DISPLAY "SQLCODE IS " SQLCODE.

* Second SQL statement 
   EXEC SQL
      SELECT ARRAY1, ARRAY2
         INTO :ARRAY-FIELD1, :ARRAY-FIELD2
         FROM MYTABLE
         ORDER BY ARRAY1
   END-EXEC.
   DISPLAY "SQLCODE IS " SQLCODE.
   
goback.

    

Resolution:

There is a bug in the Oracle 11g ODBC driver.  Development has confirmed this issue by putting together a C demo, and viewing the memory address containing the ODBC row status array before and after the fetch, both with the Oracle 10gR2 and 11gR2 ODBC drivers. The Oracle 11 driver is returning the row status array as 4 byte elements rather than 2, and is writing off the end of allocated memory.

They have submitted SR 3-5913626121 to Oracle and got the following response:

"This is Bug 13535622, which is fixed from 11.2.0.3 patch 6. 11.2.0.3 patch 7 can be downloaded from MyOracleSupport as Patches 10404530 and 14095819."

Development applied Patch 14095819 to their test machine and confirmed with both their C cut-down, and their COBOL cut-down, that the problem no longer occurs.

Incident #2580224