fetch

Description

Copies data values from the current cursor row into host variables or a dynamic descriptor.

Syntax

exec sql [at connection_name] fetch [rebind | norebind] cursor_name
into {:host_variable [[indicator]:indicator_variable]
 [,:host_variable 
 [[indicator]:indicator_variable]]… | 
 descriptor descriptor_name | 
 sql descriptor descriptor_name} end-exec

Parameters

rebind | norebind

Specifies whether host variables require rebinding for this fetch statement. The rebind clause overrides precompiler options that control rebinding.

cursor_name

The name of the cursor. The name is defined in a preceding declare cursor statement.

host_variable

A host language variable defined in a declare section.

indicator_variable

A 2-byte host variable declared in a previous declare section. If the value for the associated variable is null, fetch sets the indicator variable to -1. If truncation occurs, fetch sets the indicator variable to the actual length of the result column. Otherwise, it sets the indicator variable to 0.

descriptor

Identifies descriptor_name as a SQLDA structure.

sql descriptor

Identifies descriptor_name as a SQL descriptor.

descriptor_name

The name of the dynamic descriptor that is to hold a result set.

Examples

Example 1

     EXEC SQL BEGIN DECLARE SECTION END-EXEC.
           01     TITLE-ID   PIC X(6).
           01     BOOK-NAME  PIC X(80).
           01     BOOK-TYPE  PIC X(12).
           01     I-TITLE    PIC S9(9).
           01     I-TYPE     PIC S9(9).
      EXEC SQL END DECLARE SECTION END-EXEC.
 
           ...
 
      EXEC SQL DECLARE title_list CURSOR FOR
           SELECT type, title_id, title FROM titles 
           ORDER BY type END-EXEC.
 
      EXEC SQL OPEN title_list END-EXEC.
      PERFORM FETCH-LOOP UNTIL SQLCODE = 100.
      EXEC SQL CLOSE title_list END-EXEC.
 
           ...
 
      FETCH-LOOP.
           EXEC SQL FETCH title_list INTO 
                     :BOOK-TYPE :I-TYPE,
                     :TITLE-ID, 
                     :BOOK-NAME :I-TITLE END-EXEC
      * Check the indicator value - if not null display the value, else
      * display UNDECIDED.
           IF I-TYPE <> -1
                DISPLAY "TYPE : ", BOOK-TYPE
           ELSE
                DISPLAY "TYPE : UNDECIDED"
           END-IF
 
           DISPLAY "TITLE ID : ", TITLE-ID
 
           IF I-TITLE <> -1
                DISPLAY "TITLE : ", BOOK-NAME 
           ELSE
                DISPLAY "TITLE : UNDECIDED"
           END-IF.
      END-FETCH-LOOP.

Usage

See also

allocate descriptor, close, declare, delete (positioned cursor), open, prepare, update