Obtains row format information about the result set of a prepared dynamic SQL statement and stores that information in a SQLDA structure.
exec sql describe [output] statement_name using descriptor sqlda_name end-exec
An optional keyword that has no effect on the describe output statement but provides conformance to the SQL standard.
The name (specified in a prepare statement) that represents the select statement to be executed.
Identifies descriptor_name as a SQLDA structure.
The name of a SQLDA structure that is to store the information returned by the describe output statement:
      EXEC SQL BEGIN DECLARE SECTION END-EXEC.
             01      QUERY          PIC X(100).
             01      CHARVAR        PIC X(100).
       EXEC SQL END DECLARE SECTION END-EXEC.
       01      dout.
                         05 SD-SQLN      PIC S9(4) COMP.
                         05 SD-SQLD      PIC S9(4) COMP.
                         05 SD-COLUMN OCCURS 3 TIMES.
                         10 SD-DATAFMT.
                            15 SQL--NM        PIC X(132).
                            15 SQL--NMLEN     PIC S9(9) COMP.
                            15 SQL--DATATYPE  PIC s9(9) COMP.
                            15 SQL--FORMAT     PIC S9(9) COMP.
                            15 SQL--MAXLENGTH  PIC S9(9) COMP.
                            15 SQL--SCALE      PIC S9(9) COMP.
                            15 SQL--PRECISION  PIC S9(9) COMP.
                            15 SQL--STTUS      PIC S9(9) COMP.
                            15 SQL--COUNT      PIC S9(9) COMP.
                            15 SQL--USERTYPE   PIC S9(9) COMP.
                            15 SQL--LOCALE     PIC S9(9) COMP.
                         10 SD-SQLDATA    PIC S9(9) COMP.
                         10 SD-SQLIND     PIC S9(9) COMP.
                         10 SD-SQLLEN     PIC S9(9) COMP.
                         10 SD-SQLMORE    PIC S9(9) COMP.
         01      TMP                 PIC Z(8)9.
         01      COLNUM              PIC S9(9) COMP.
         01      TMP1                PIC S9(9) COMP.
         01      TMP2                PIC S9(9) COMP.
         01      RETCODE             PIC S9(9) COMP.
             ...
       DISPLAY "ENTER QUERY :"
       ACCEPT QUERY.
       EXEC SQL ALLOCATE DESCRIPTOR dout WITH MAX 256 END-EXEC.
       EXEC SQL PREPARE dynstmt FROM :QUERY END-EXEC.
       EXEC SQL DECLARE selcursor CURSOR FOR dynstmt END-EXEC.
       EXEC SQL OPEN selcursor END-EXEC.
       EXEC SQL DESCRIBE OUTPUT dynstmt 
                     USING DESCRIPTOR dout END-EXEC.
       MOVE 1  TO COLNUM.
       MOVE 25 TO TMP1.
       MOVE 0  TO TMP2.
       CALL "SYBSETSQLDA" USING RETCODE dout COLNUM
             CHARVAR SYB-X-PIC TMP1 TMP2 SYB-NO-USAGE
                   SYB-NO-SIGN.
       EXEC SQL FETCH selcursor INTO DESCRIPTOR dout END-EXEC.
       DISPLAY "CHARVAR = ", CHARVAR.
       EXEC SQL CLOSE selcursor END-EXEC.
       EXEC SQL DEALLOCATE CURSOR selcursor END-EXEC.
       EXEC SQL DEALLOCATE PREPARE dynstmt END-EXEC.
       EXEC SQL DEALLOCATE DESCRIPTOR dout END-EXEC.
The information obtained is data held in the SQLDA fields, such as the type, name, length (or precision and scale, if a number), nullable status, and number of items in the result set.
The information is about the result columns from the select column list.
describe input, execute, prepare