A SQLDA consists of four variables (SQLDAID, SQLDABC, SQLN, and SQLD), followed by an arbitrary number of SQLVARs. A SQLVAR is a structure containing five fields.
The following table describes the SQLDA variables.
This SQLDA variable: |
Performs this function: |
---|---|
SQLDAID |
Contains an eye catcher of “SQLDA” for use in storage dumps |
SQLDABC |
Contains the length of the SQLDA, equal to SQLN*44+16 |
SQLN |
Contains the total number of occurrences of SQLVAR |
SQLD |
Indicates the number of columns described by occurrences of SQLVAR |
Each occurrence of SQLVAR describes one column of the result row the CSA is sending to the client application. The following table describes the five fields that each occurrence of SQLVAR contains.
This SQLDA field: |
Performs this function: |
---|---|
SQLTYPE |
Contains a 3-digit value that represents the datatype of the column and whether or not it allows null values. Table F-3 contains the valid data type values. |
SQLLEN |
Contains the external length of a value from the column. |
SQLDATA |
Contains the address of the data being transmitted. |
SQLIND |
Contains the address of an indicator, which tells whether the column is nullable. Uses a value less than zero if null. |
SQLNAME |
Contains the name or label of the column, or a string of length zero if the name or label does not exist. |
SQLNAMEL |
Contains the length of the column. |
Relating these standard SQLDA fields to the SQLDA template example from the LINKAGE SECTION of CLIENTC2 (see Appendix B, “CLIENTC2 Sample CSA”), you can see that one SQLVAR definition can be used six times for the six columns of data to be received from the SALES table:
01 SALES-SQLDA. 03 SALES-SQLDAID PIC X(08). 03 SALES-SQLDABC PIC S9(8) COMP. 03 SALES-SQLN PIC S9(4) COMP. 03 SALES-SQLD PIC S9(4) COMP. 03 SALES-SQLVAR OCCURS 6 TIMES. 05 SALES-SQLTYPE PIC S9(4) COMP. 05 SALES-SQLLEN PIC S9(4) COMP. 05 SALES-SQLDATA POINTER. 05 SALES-SQLIND POINTER. 05 SALES-SQLNAME PIC X(32).
The example assumes that all the expected data is the same datatype. If that were not true, you would need to define separate SQLVARs, with separate SQLIND fields for each of the datatypes in your SQLDA template.
In each of the six SQLVARs, a SALES-SQLDATA field points to a result data field that the CSA expects to receive. In CLIENTC2, the result data fields are defined in the LINKAGE SECTION following the SQLDA template:
01 STORE-ID PIC X(04).
01 ORDER-NUMBER. 03 ORD-NUM-LENGTH PIC S9(4) COMP. 03 ORD-NUM. 05 ORD-NUMCHAR PIC X(01) OCCURS 20 TIMES DEPENDING ON ORD-NUM-LENGTH.
01 ORDER-DATE PIC X(10).
01 QUANTITY PIC S9(4) COMP.
01 PAY-TERMS. 03 PAY-TERM-LEN PIC S9(4) COMP. 03 PAY-TERM. 05 PAY-TERM-CHAR PIC X(01) OCCURS 12 TIMES DEPENDING ON PAY-TERM-LEN.
01 TITLE-ID-ENT. 03 TITLE-ID-LEN PIC S9(4) COMP. 03 TITLE-ID. 05 TITLE-ID-CHAR PIC X(01) OCCURS 6 TIMES DEPENDING ON TITLE-ID-LEN.
After the input pipe is open and Open ClientConnect passes the actual SQLDA, the pointers to the result data are related to the data field definitions:
SET ADDRESS OF SALES-SQLDA TO SPSQLDA
SET ADDRESS OF STORE-ID TO SALES-SQLDATA(1) SET ADDRESS OF ORDER-NUMBER TO SALES-SQLDATA(2) SET ADDRESS OF ORDER-DATE TO SALES-SQLDATA(3) SET ADDRESS OF QUANTITY TO SALES-SQLDATA(4) SET ADDRESS OF PAY-TERMS TO SALES-SQLDATA(5) SET ADDRESS OF TITLE-ID-ENT TO SALES-SQLDATA(6)
CLIENTC2 illustrates the steps for reading a SQLDA definition:
Include a description of the SQLDA template.
The SQLDA template and the result data definitions go in the LINKAGE SECTION so they can be accessed by programs outside the CSA, such as Open ClientConnect.
Set the address of the SQLDA template to the address of the SQLDA that Open ClientConnect sends using the SPSQLDA field. Open ClientConnect places that address in the SPSQLDA field of the SPAREA.
Relate the pointers to the result data field definitions.
Copyright © 2005. Sybase Inc. All rights reserved. |
![]() |