declare cursor (static)

Description

Declares a cursor for processing multiple rows returned by a select statement.

Syntax

exec sql declare cursor_name 
 cursor for select_statement 
 [for update [of col_name_1 [, col_name_n]…]|
 for read only] end-exec

Parameters

cursor_name

The cursor’s name, used to reference the cursor in open, fetch, and close statements. A cursor’s name must be unique on each connection and must have no more than 255 characters.

select_statement

The Transact-SQL select statement to be executed when the cursor is opened. See the description of the select statement in the Adaptive Server Enterprise Reference Manual for more information.

for update

Specifies that the cursor’s result list can be updated. (To update the result list, you use the update statement.

of col_name_n

The name of a column to be updated.

for read only

Specifies that the cursor’s result list cannot be updated.

Examples

Example 1

     EXEC SQL BEGIN DECLARE SECTION END-EXEC.
           01     TITLE-ID      PIC X(6).
           01     BOOK-NAME         PIC X(25).
           01     TYPE           PIC X(15).
      EXEC SQL END DECLARE SECTION END-EXEC.
 
           01      ANSWER           PIC X(1).
 
           ....
 
 
      DISPLAY "TYPE OF BOOKS TO RETRIEVE ? ".
      ACCEPT BOOK-TYPE.
      EXEC SQL DECLARE titlelist CURSOR FOR
           SELECT title_id, substring(title,1,25) FROM
                titles WHERE type = :BOOK-TYPE END-EXEC.
 
      EXEC SQL OPEN titlelist END-EXEC.
      PERFORM FETCH-PARA UNTIL SQLCODE = 100.
      EXEC SQL CLOSE titlelist END-EXEC.
      EXEC SQL DEALLOCATE CURSOR titlelist END-EXEC.
      EXEC SQL COMMIT WORK END-EXEC.
 
 
      FETCH-PARA.
           EXEC SQL FETCH titlelist INTO 
                     :TITLE-ID, :BOOK-NAME END-EXEC.
           DISPLAY "TITLE ID : ",TITLE-ID
           DISPLAY "TITLE    : ",BOOK-NAME
           IF SQLCODE = 100
                DISPLAY "NO RECORDS TO FETCH. END OF PROGRAM RUN."
           ELSE
           DISPLAY "UPDATE/DELETE THIS RECORD (U/D)? "
           ACCEPT ANSWER.
 
           IF ANSWER = "U"
                DISPLAY "ENTER NEW TITLE :"
                ACCEPT BOOK-NAME
                EXEC SQL UPDATE titles SET title = :BOOK-NAME
                      WHERE CURRENT OF titlelist END-EXEC
           ELSE
                IF ANSWER = "D"
                     EXEC SQL DELETE titles 
                     WHERE CURRENT OF titlelist  END-EXEC
                END-IF
           END-IF
           END-IF.
      END-FETCH-PARA.

Usage

See also

close, connect, deallocate cursor, declare cursor (stored procedure), declare cursor (dynamic), fetch, open, update