SQL$HELP72.HLB  —  INCLUDE  Examples
    Example 1: Including a host structure declaration

    This simple COBOL program uses the INCLUDE FROM DICTIONARY
    statement to declare a host structure that corresponds to the
    EMPLOYEES table in the sample personnel database. The repository
    path name specifies the RDB$RELATIONS repository directory
    between the database directory and the table name.

    IDENTIFICATION DIVISION.
    PROGRAM-ID. INCLUDE_FROM_CDD.
    *
    * Illustrate how to use the INCLUDE FROM DICTIONARY
    * statement to declare a host structure corresponding to
    * the EMPLOYEES table:
    *
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    EXEC SQL WHENEVER SQLERROR GOTO ERR END-EXEC.
    *
    * Include the SQLCA:
    EXEC SQL INCLUDE SQLCA END-EXEC.
    *
    * Declare the schema:
    * (Notice that declaring the alias with the
    * FILENAME qualifier would not have precluded
    * using the INCLUDE FROM DICTIONARY statement later.)
    EXEC SQL DECLARE PERS ALIAS FOR
            PATHNAME 'CDD$DEFAULT.PERSONNEL' END-EXEC.
    *
    * Create a host structure that corresponds to the
    * EMPLOYEES table with the INCLUDE FROM DICTIONARY
    * statement.  The path name in the INCLUDE statement
    * must specify the RDB$RELATIONS directory before
    * the table name:
    EXEC SQL INCLUDE FROM DICTIONARY
            'CDD$DEFAULT.PERSONNEL.RDB$RELATIONS.EMPLOYEES'
            END-EXEC.
    *
    * Declare an indicator structure for the host
    * structure created by the INCLUDE FROM DICTIONARY statement:
    01 EMPLOYEES-IND.
            02 EMP-IND OCCURS 12 TIMES PIC S9(4) COMP.
    EXEC SQL DECLARE E_CURSOR CURSOR
            FOR SELECT * FROM EMPLOYEES  END-EXEC.

    PROCEDURE DIVISION.
    0.
        DISPLAY "Display rows from EMPLOYEES:".
        EXEC SQL OPEN E_CURSOR END-EXEC.
        EXEC SQL FETCH E_CURSOR INTO :EMPLOYEES:EMP-IND  END-EXEC.
        PERFORM UNTIL SQLCODE NOT = 0
            DISPLAY EMPLOYEE_ID, FIRST_NAME, LAST_NAME
            EXEC SQL FETCH E_CURSOR INTO :EMPLOYEES:EMP-IND END-EXEC
        END-PERFORM.
        EXEC SQL CLOSE E_CURSOR END-EXEC.

        EXEC SQL ROLLBACK END-EXEC.
        EXIT PROGRAM.

    ERR.
        DISPLAY "unexpected error ", sqlcode with conversion.
        CALL "SQL$SIGNAL".

    Example 2: Including the SQLCA

    This fragment from a PL/I program shows the INCLUDE SQLCA
    statement and illustrates how an error-handling routine refers
    to the SQLCA.

    The program creates an intermediate result table, TMP, and copies
    the EMPLOYEES table from the personnel database into it. It then
    declares a cursor for TMP and displays the rows of the cursor on
    the terminal screen.

        /* Include the SQLCA: */
        EXEC SQL INCLUDE SQLCA;
        EXEC SQL WHENEVER SQLERROR GOTO ERROR_HANDLER;
        EXEC SQL DECLARE ALIAS FOR FILENAME personnel;
        DCL MANAGER_ID CHAR(5),
            LAST_NAME CHAR(20),
            DEPT_NAME CHAR(20);
        DCL COMMAND_STRING CHAR(256);

        EXEC SQL CREATE TABLE TMP
                (MANAGER_ID CHAR(5),
                 LAST_NAME CHAR(20),
                 DEPT_NAME CHAR(20));
        COMMAND_STRING =
            'INSERT INTO TMP
                    SELECT  E.LAST_NAME,
                            E.FIRST_NAME,
                            D.DEPARTMENT_NAME
                    FROM EMPLOYEES E, DEPARTMENTS D
                    WHERE E.EMPLOYEE_ID = D.MANAGER_ID';

        EXEC SQL EXECUTE IMMEDIATE :COMMAND_STRING;

        EXEC SQL DECLARE X CURSOR FOR SELECT * FROM TMP;
        EXEC SQL OPEN X;
        EXEC SQL FETCH X INTO MANAGER_ID, LAST_NAME, DEPT_NAME;
        DO WHILE (SQLCODE = 0);
            PUT SKIP EDIT
                    (MANAGER_ID, ' ', LAST_NAME, ' ', DEPT_NAME)
                    (A,A,A,A,A);
            EXEC SQL FETCH X INTO MANAGER_ID, LAST_NAME, DEPT_NAME;
        END;
        EXEC SQL ROLLBACK;
        PUT SKIP EDIT ('  ALL OK') (A);
        RETURN;

    ERROR_HANDLER:

        /* Display the value of the SQLCODE field in the SQLCA: */
        PUT SKIP EDIT ('UNEXPECTED SQLCODE VALUE ', SQLCODE) (A, F(9));
        EXEC SQL WHENEVER SQLERROR CONTINUE;
        EXEC SQL ROLLBACK;
Close Help