Created On:  27 March 2012

Problem:

Using Visual COBOL in 32-bit native application although problem also occurs in Net Express 5.1. After executing select into with array fields the fields appear to be populated corrected and no error occurs. But on the very next SQL statement a RTS 114 error will occur.

Here is a sample which uses the Oracle sample EMP table.  The 114 error occurs on the cursor open after the select into array.


      $SET SQL(DBMAN=ODBC)  sourceformat(variable)
       WORKING-STORAGE SECTION.

       EXEC SQL INCLUDE SQLCA  END-EXEC.
       *> -------------------------------------------
       *> DECLARE TABLE for EMP
       *> -------------------------------------------
          EXEC SQL DECLARE EMP TABLE
          ( EMPNO                 NUMBER(4)    NOT NULL
          , ENAME                 VARCHAR2(10)
          , JOB                        VARCHAR2(9)
          , MGR                      NUMBER(4)
          , HIREDATE             DATE
          , SAL                        NUMBER(7,2)
          , COMM                   NUMBER(7,2)
          , DEPTNO                NUMBER(2)
          ) END-EXEC.
       *> -------------------------------------------
       *> COBOL HOST VARIABLES FOR TABLE EMP
       *> -------------------------------------------
       01  DCLEMP.
           03 EMP-EMPNO                       PIC S9(4)  COMP-3.
           03 EMP-ENAME                       PIC X(10).
           03 EMP-JOB                              PIC X(9).
           03 EMP-MGR                            PIC S9(4)  COMP-3.
           03 EMP-HIREDATE                  PIC X(10).
           03 EMP-SAL                             PIC S9(5)V9(2)  COMP-3.
           03 EMP-COMM                        PIC S9(5)V9(2)  COMP-3.
           03 EMP-DEPTNO                      PIC S9(2)  COMP-3.
       *> -------------------------------------------
       *> COBOL INDICATOR VARIABLES FOR TABLE EMP
       *> -------------------------------------------
       01  DCLEMP-NULL.
           03 EMP-ENAME-NULL                  PIC S9(04)  COMP-5.
           03 EMP-JOB-NULL                         PIC S9(04)  COMP-5.
           03 EMP-MGR-NULL                       PIC S9(04)  COMP-5.
           03 EMP-HIREDATE-NULL             PIC S9(04)  COMP-5.
          03 EMP-SAL-NULL                         PIC S9(04)  COMP-5.
           03 EMP-COMM-NULL                   PIC S9(04)  COMP-5.
           03 EMP-DEPTNO-NULL                PIC S9(04)  COMP-5.

       01 MFSQLMESSAGETEXT  PIC X(250).
       01 IDX               PIC X(04)  COMP-5.

       EXEC SQL BEGIN DECLARE SECTION  END-EXEC
       01  ARRAY-VARS.
           03 EMP-EMPNO-A                      PIC S9(4)  COMP-3 OCCURS 80 TIMES.
           03 EMP-ENAME-A                      PIC X(10)  OCCURS 80 TIMES.
           03 EMP-JOB-A                             PIC X(9)   OCCURS 80 TIMES.
       EXEC SQL END DECLARE SECTION END-EXEC
       PROCEDURE DIVISION.

           EXEC SQL
              WHENEVER SQLERROR perform OpenESQL-Error
           END-EXEC
          
           EXEC SQL
             CONNECT TO 'testora' USER 'SCOTT.TIGER'
          END-EXEC
      
           move 0 to emp-empno
           EXEC SQL
               SELECT
                   A.EMPNO
                  ,A.ENAME
                  ,A.JOB
               INTO
               :EMP-EMPNO-a
              ,:EMP-ENAME-a
              ,:EMP-JOB-a
               FROM EMP A
                   WHERE (A.EMPNO > :EMP-EMPNO)
           END-EXEC    
             
           EXEC SQL
              DECLARE CSR2 CURSOR FOR SELECT
                  A.EMPNO
                 ,A.ENAME
                 ,A.JOB
              FROM EMP A
              WHERE (A.EMPNO > :EMP-EMPNO)
           END-EXEC

           EXEC SQL
              OPEN CSR2
           END-EXEC
           PERFORM UNTIL SQLSTATE >= "02000"
              EXEC SQL
              FETCH CSR2  INTO
                   :EMP-EMPNO
                  ,:EMP-ENAME:EMP-ENAME-NULL
                  ,:EMP-JOB:EMP-JOB-NULL
              END-EXEC
              *> Process data from the Fetch
              IF SQLSTATE < "02000"
                 DISPLAY 'ROW FOUND'
              END-IF
           END-PERFORM
           EXEC SQL
             CLOSE CSR2
           END-EXEC
         
           EXEC SQL DISCONNECT CURRENT END-EXEC
           STOP RUN.
       *> Default sql error routine / modify to stop program if needed
       OpenESQL-Error Section.

           display "SQL Error = " sqlstate " " sqlcode
           display MFSQLMESSAGETEXT
           *> stop run
           exit.

 

Resolution:

Micro Focus Development ran the test program with a debug version of the OpenESQL ODBC runtime.

Visual Studio reports a heap corruption on the OPEN following the singleton select. This happens with Oracle's 11.01 driver, but not with the 10.02 driver. We have searched the internet, and it seems that several others have run into this problem.


See https://forums.oracle.com/forums/thread.jspa?threadID=2295218 
 
We therefore doubt that this is a problem with the OpenESQL runtime. If OpenESQL itself was corrupting the heap we would expect this to be caught by the debug C runtime at the time the corruption occurred. 

This appears to be a bug in the Oracle 11g ODBC driver and the resolution is to move back to the Oracle 10g ODBC driver instead.