$SET "esql.db2" "1" |
iscobol.compiler.esql.db2=1 |
***************************************************** * SQL DESCRIPTOR AREA * ***************************************************** 01 SQLDA. 02 SQLDAID PIC X(8) VALUE 'SQLDA '. 02 SQLDABC PIC S9(8) COMPUTATIONAL VALUE 33016. 02 SQLN PIC S9(4) COMPUTATIONAL VALUE 750. 02 SQLD PIC S9(4) COMPUTATIONAL VALUE 0. 02 SQLVAR OCCURS 1 TO 750 TIMES DEPENDING ON SQLN. 03 SQLTYPE PIC S9(4) COMPUTATIONAL. 03 SQLLEN PIC S9(4) COMPUTATIONAL. 03 SQLDATA POINTER. 03 SQLIND POINTER. 03 SQLNAME. 49 SQLNAMEL PIC S9(4) COMPUTATIONAL. 49 SQLNAMEC PIC X(30). |
SQLDAID | Contains the string 'SQLDA ' |
SQLDABC | Length of the SQLDA |
SQLN | Unchanged in this context |
SQLD | Number of columns described by occurrences of SQLVAR |
SQLTYPE | The data type of the column. See SQLTYPE values below for the list of possible values |
SQLLEN | The length attribute of the column |
SQLDATA | Not used |
SQLIND | Not used |
SQLNAME | The unqualified name of the column. This is a varchar field: SQLNAMEL contains the length of the value, while SQLNAMEC contains the value. |
SQLDAID | Contains the string 'SQLDA ' |
SQLDABC | Length of the SQLDA |
SQLN | Total number of occurrences of SQLVAR provided in the SQLDA |
SQLD | Number of occurrences of SQLVAR entries in the SQLDA that are used when executing the statement. It must be set to a value greater than or equal to zero and less than or equal to SQLN |
SQLTYPE | The data type of the host variable and whether an indicator variable is provided. See SQLTYPE values below for the list of possible values |
SQLLEN | The length attribute of the host variable |
SQLDATA | Contains the address of the host variable |
SQLIND | Contains the address of the indicator variable. It’s ignored if there is no indicator variable (as indicated by an even value of SQLTYPE) |
SQLNAME | Not used |
Value without indicator | Value with indicator | Type |
---|---|---|
384 | 385 | Date |
388 | 389 | Time |
392 | 393 | Timestamp |
396 | 397 | DataLink |
404 | 405 | BLOB |
408 | 409 | CLOB |
412 | 413 | DBCLOB |
448 | 449 | Varying-length character string |
452 | 453 | Fixed-length character string |
456 | 457 | Long varying-length character string |
480 | 481 | Floating point |
484 | 485 | Packed decimal |
488 | 489 | Zoned decimal |
492 | 493 | Big integer |
496 | 497 | Large integer |
500 | 501 | Small integer |
904 | 905 | ROWID |
908 | 909 | Varying-length binary string |
912 | 913 | Fixed-length binary string |
988 | 989 | XML |