Defining SQL descriptor areas in COBOL applications that use SQL

There are two types of SQL descriptor areas (SQLDAs). One is defined with the ALLOCATE DESCRIPTOR statement. The other is defined using the SQLDA structure. In this topic, only the SQLDA form is discussed.

The following statements can use an SQLDA:

  • EXECUTE…USING DESCRIPTOR descriptor-name
  • FETCH…USING DESCRIPTOR descriptor-name
  • OPEN…USING DESCRIPTOR descriptor-name
  • CALL…USING DESCRIPTOR descriptor-name
  • DESCRIBE statement-name INTO descriptor-name
  • DESCRIBE CURSOR cursor-name INTO descriptor-name
  • DESCRIBE INPUT statement-name INTO descriptor-name
  • DESCRIBE PROCEDURE procedure-name INTO descriptor-name
  • DESCRIBE TABLE host-variable INTO descriptor-name
  • PREPARE statement-name INTO descriptor-name

Unlike the SQLCA, there can be more than one SQLDA in a program. The SQLDA can have any valid name. An SQLDA can be coded in a COBOL program directly or added with the INCLUDE statement. Using the SQL INCLUDE statement requests the inclusion of a standard SQLDA declaration:

EXEC SQL INCLUDE SQLDA END-EXEC.

The COBOL declarations included for the SQLDA are:

Figure 1. INCLUDE SQLDA declarations for COBOL
1 SQLDA.
  05 SQLDAID     PIC X(8).
  05 SQLDABC     PIC S9(9) BINARY.
  05 SQLN        PIC S9(4) BINARY.
  05 SQLD        PIC S9(4) BINARY.
  05 SQLVAR OCCURS 0 TO 409 TIMES DEPENDING ON SQLD.
     10 SQLVAR1.
        15 SQLTYPE   PIC S9(4) BINARY.
        15 SQLLEN    PIC S9(4) BINARY.
        15 FILLER  REDEFINES SQLLEN.
           20 SQLPRECISION PIC X.
           20 SQLSCALE     PIC X.
        15 SQLRES    PIC X(12).
        15 SQLDATA   POINTER.
        15 SQL-RESULT-SET-LOCATOR-R REDEFINES SQLDATA.
           20 SQL-RESULT-SET-LOCATOR PIC S9(18) BINARY.
        15 SQLIND   POINTER.
        15 SQL-ROW-CHANGE-SQL-R REDEFINES SQLIND.
           20 SQLD-ROW-CHANGE FIC S9(9) BINARY.
        15 SQL-RESULT-SET-ROWS-R PIC REDEFINES SQLIND.
           20 SQLD-RESULT-SET-ROWS PIC S9(9) BINARY.
        15 SQLNAME.
           49 SQLNAMEL PIC S9(4) BINARY.
           49 SQLNAMEC PIC X(30).
     10 SQLVAR2 REDEFINES SQLVAR1.
        15 SQLVAR2-RESERVED-1 PIC S9(9) BINARY.
        15 SQLLONGLEN REDEFINEDS SQLVAR2-RESERVED-1
                                 PIC S9(9) BINARY.
        15 SQLVAR2-RESERVED-2 PIC X(28).
        15 SQLDATALEN POINTER.
        15 SQLDATATYPE-NAME.
           49 SQLDATATYPE_NAMEL PIC S9(4) BINARY.
           49 SQLDATATYPE_NAMEC PIC X(30).
            

SQLDA declarations must appear in the WORKING-STORAGE SECTION or LINKAGE SECTION of your program and can be placed wherever a record description entry can be specified in those sections. For ILE COBOL, the SQLDA is declared using the GLOBAL clause.

Dynamic SQL is an advanced programming technique. With dynamic SQL, your program can develop and then run SQL statements while the program is running. A SELECT statement with a variable SELECT list (that is, a list of the data to be returned as part of the query) that runs dynamically requires an SQL descriptor area (SQLDA). This is because you cannot know in advance how many or what type of variables to allocate in order to receive the results of the SELECT.