Multiple-row FETCH using a host structure array

To use the multiple-row FETCH statement with the host structure array, the application must define a host structure array that can be used by SQL.

Each language has its own conventions and rules for defining a host structure array. Host structure arrays can be defined by using variable declarations or by using compiler directives to retrieve External File Descriptions (such as the COBOL COPY directive).

The host structure array consists of an array of structures. Each structure corresponds to one row of the result table. The first structure in the array corresponds to the first row, the second structure in the array corresponds to the second row, and so on. SQL determines the attributes of elementary items in the host structure array based on the declaration of the host structure array. To maximize performance, the attributes of the items that make up the host structure array should match the attributes of the columns being retrieved.

Consider the following COBOL example:

Note: By using the code examples, you agree to the terms of the Code license and disclaimer information.
 
      EXEC SQL INCLUDE SQLCA
      END-EXEC.
 
...
 
      01 TABLE-1.
          02 DEPT  OCCURS 10 TIMES.
             05  EMPNO   PIC   X(6).
             05 LASTNAME.
                49 LASTNAME-LEN  PIC S9(4) BINARY.
                49 LASTNAME-TEXT PIC X(15).
             05  WORKDEPT PIC  X(3).
             05  JOB      PIC  X(8).
      01 TABLE-2.
         02 IND-ARRAY   OCCURS 10 TIMES.
            05 INDS PIC  S9(4) BINARY OCCURS 4 TIMES.
 
...
      EXEC SQL
      DECLARE D11 CURSOR FOR
      SELECT EMPNO, LASTNAME, WORKDEPT, JOB
       FROM CORPDATA.EMPLOYEE
        WHERE WORKDEPT = "D11"
      END-EXEC.
 
...
 
      EXEC SQL
       OPEN D11
      END-EXEC.
      PERFORM FETCH-PARA UNTIL SQLCODE NOT EQUAL TO ZERO.
  ALL-DONE.
        EXEC SQL CLOSE D11 END-EXEC.
 
...
 
      FETCH-PARA.
         EXEC SQL WHENEVER NOT FOUND GO TO ALL-DONE END-EXEC.
      EXEC SQL FETCH D11 FOR 10 ROWS INTO :DEPT :IND-ARRAY
      END-EXEC.
 
...
 

In this example, a cursor was defined for the CORPDATA.EMPLOYEE table to select all rows where the WORKDEPT column equals 'D11'. The result table contains eight rows. The DECLARE CURSOR and OPEN statements do not have any special syntax when they are used with a multiple-row FETCH statement. Another FETCH statement that returns a single row against the same cursor can be coded elsewhere in the program. The multiple-row FETCH statement is used to retrieve all of the rows in the result table. Following the FETCH, the cursor position remains on the last row retrieved.

The host structure array DEPT and the associated indicator array IND-ARRAY are defined in the application. Both arrays have a dimension of ten. The indicator array has an entry for each column in the result table.

The attributes of type and length of the DEPT host structure array elementary items match the columns that are being retrieved.

When the multiple-row FETCH statement has successfully completed, the host structure array contains the data for all eight rows. The indicator array, IND_ARRAY, contains zeros for every column in every row because no NULL values were returned.

The SQLCA that is returned to the application contains the following information:

  • SQLCODE contains 0
  • SQLSTATE contains '00000'
  • SQLERRD3 contains 8, the number of rows fetched
  • SQLERRD4 contains 34, the length of each row
  • SQLERRD5 contains +100, indicating the last row in the result table is in the block