HPlogo ALLBASE/SQL COBOL Application Programming Guide: HP 9000 Computer Systems > Chapter 4 Host Variables

Declaring Host Variables

» 

Technical documentation

Complete book in PDF
» Feedback

 » Table of Contents

 » Index

If your program uses host variables in the PROCEDURE DIVISION, you must declare the host variables in the DATA DIVISION:

  • If the host variable data is used only within a given program, declare host variables in the WORKING-STORAGE SECTION.

  • If the host variable data is used in a calling program, declare host variables in the program's WORKING-STORAGE SECTION.

  • Host variable data used in a called program or subprogram is declared in that program's LINKAGE SECTION.

  • If host variable values come from an HP-UX file or are written to an HP-UX file in the program, declare these host variables in the FILE SECTION.

Creating Declaration Sections

Host variables must be declared in what is known as a declare section. A declare section consists of the SQL command EXEC SQL BEGIN DECLARE SECTION END-EXEC., one or more variable declarations, and the SQL command EXEC SQL END DECLARE SECTION END-EXEC. (as shown in Figure 4-1).

More than one declare section may appear in the WORKING-STORAGE SECTION, the LINKAGE SECTION, and the FILE SECTION. Note that variables which are not host variables may also be declared within a declare section.

Each host variable is declared by using a COBOL data description entry. The declaration contains the same components as any COBOL data description entry:



   EXEC SQL BEGIN DECLARE SECTION END-EXEC.

   01  ORDERNUMBER    PIC S9(9) COMP.

   |   |              |

   |   |              |

   |   |              data clause

   |   |

   |   data name

   |

   level number

   EXEC SQL END DECLARE SECTION END-EXEC.


The level number can be from 01 to 49; single-level variables can have level numbers 01 or 77. The data name must be the same as the corresponding host variable name in the PROCEDURE DIVISION. The data clause must satisfy ALLBASE/SQL data type and COBOL preprocessor requirements.

Note, data clauses can also contain the optional constructs highlighted below:



PICTURE IS X(n) USAGE IS DISPLAY

PICTURE IS S9(4) USAGE IS COMPUTATIONAL


Figure 4-1 Host Variable Declarations in the DATA DIVISION



DATA DIVISION.

FILE SECTION.

.

.

EXEC SQL BEGIN DECLARE SECTION END-EXEC.

.

.  Declarations for host variables whose values

.  come from or go to an HP-UX file appear here.

.

EXEC SQL END DECLARE SECTION END-EXEC.

.

.

.

WORKING-STORAGE SECTION.

.

.

EXEC SQL BEGIN DECLARE SECTION END-EXEC.

.

.  Declarations for local host variables, including

.  those passed from a called program or subprogram, go here.

.

EXEC SQL END DECLARE SECTION END-EXEC.

.

.

LINKAGE SECTION.

.

.

EXEC SQL BEGIN DECLARE SECTION END-EXEC.

.

.  Declarations for host variables to be passed

.  to a calling program or subprogram go here.

.

EXEC SQL END DECLARE SECTION END-EXEC.

.

.

Declaring Variables for Data Types

Table 4-1 summarizes the syntax of the data description entries for host variables holding each type of ALLBASE/SQL data. Only the data descriptions shown in Table 4-1 are supported by the COBOL preprocessor.

CHAR Data

You can insert strings ranging from 1 to 3996 characters into a CHAR column.

When ALLBASE/SQL assigns data to a CHAR host variable from a CHAR host variable, it adds blanks if necessary on the right of the string to fill up the accepting variable.

VARCHAR Data

VARCHAR strings can range from 1 to 3996 characters. ALLBASE/SQL stores the actual length of the string in a four-byte field preceding the string itself.

In order to describe both the length and value of a VARCHAR string, you declare VARCHAR data as a group containing two 49-level items:

  • The length of the VARCHAR string is declared as PIC S9(9) COMP.

  • The VARCHAR string itself is declared as a GROUP-NAME of PIC X(n), where n is the maximum number of characters in the string.

Table 4-1 Host Variable Data Types

SQL DATA TYPESCOBOL DATA DESCRIPTION ENTRIES
CHAR(n)01DATA-NAMEPIC X(n).
VARCHAR(n)

01 GROUP-NAME. 49 LENGTH-NAME PIC S9(9) COMP. 49 VALUE-NAME PIC X(n).

BINARY01DATA-NAMEPIC X(n).
VARBINARY(n)

01 GROUP-NAME 49 LENGTH-NAME PIC S9(9) COMP. 49 VALUE-NAME PIC X(n).

SMALLINT01DATA-NAMEPIC S9(4) COMP.
INTEGER01DATA-NAMEPIC S9(9) COMP.
FLOAT (DECIMAL(p,s))01DATA-NAMEPIC S9(p-s)V9(s) COMP-3.
DATE01DATA-NAMEPIC X(10).[1]
TIME01DATA-NAMEPIC X(8).[1]
DATETIME01DATA-NAMEPIC X(23).[1]
INTERVAL01DATA-NAMEPIC X(20).[1]

[1] Applies to default format specification only.

 

The VENDORREMARKS column in the PURCHDB.VENDORS table is defined as VARCHAR(60). It is therefore declared as follows:



   01  VENDORREMARKS.

     49  REMARKSLENGTH        PIC S9(9) COMP.

     49  REMARKS              PIC X(60).


In the above example, VENDORREMARKS is the GROUP-NAME, REMARKSLENGTH is the LENGTH-NAME, and REMARKS is the VALUE-NAME. When using a VARCHAR host variable as an output variable, use the GROUP-NAME:



   EXEC SQL SELECT  VENDORREMARKS

              INTO :VENDORREMARKS

              FROM  PURCHDB.VENDORS

             WHERE  VENDORNUMBER = :VENDORNUMBER

   END-EXEC.


ALLBASE/SQL places the remarks into the item named REMARKS and the number of characters in the remarks string into the item named REMARKSLENGTH. When using the value in REMARKS, only use the number of characters specified in REMARKSLENGTH or move spaces to REMARKS before filling it.

When using a VARCHAR host variable as an input variable, you assign the actual length of the VARCHAR string to the string length variable and assign the value of the string to the string value variable:



   EXEC SQL UPDATE PURCHDB.VENDORS

               SET VENDORREMARKS = :VENDORREMARKS

             WHERE VENDORNUMBER  = :VENDORNUMBER

   END-EXEC.


When ALLBASE/SQL copies data from REMARKS, it copies as many characters as you have specified in REMARKSLENGTH and stores the value in REMARKSLENGTH in a four-byte field preceding the value in REMARKS. If the value in REMARKSLENGTH is an odd number, ALLBASE/SQL stores the number of characters specified, plus one space on the right; in this case, the value in REMARKSLENGTH is incremented by one and stored in the four-byte field preceding the REMARKS value.

SMALLINT Data

Declared as PIC S9(4) COMP, possible values range from -32768 to +32767.

INTEGER Data

Declared as PIC S9(9) COMP, possible values range from -2,147,483,648 to +2,147,483,647.

FLOAT Data

ALLBASE/SQL offers the option of specifying the precision of floating point data. In COBOL, ALLBASE/SQL FLOAT data is declared as DECIMAL. The first part of this discussion relates to the ALLBASE/SQL FLOAT data type. This is followed by a discussion of declaring ALLBASE/SQL FLOAT data as DECIMAL, in COBOL.

ALLBASE/SQL FLOAT Data

You have the choice of a 4-byte or an 8-byte floating point number. (This conforms to ANSI SQL86 level 2 specifications.) The keyword REAL, and FLOAT(1) through FLOAT(24), map to a 4-byte float. The FLOAT(25) through FLOAT(53) and DOUBLE PRECISION specifications map to an 8-byte float.

The REAL data type could be useful when the number you are dealing with is very small, and you do not require a great deal of precision. However, it is subject to overflow and underflow errors if the value goes outside its range. It is also subject to greater rounding errors than double precision. With the DOUBLE PRECISION (8-byte float) data type, you can achieve significantly higher precision and have available a larger range of values.

By using the CREATE TABLE or ALTER TABLE command, you can define a floating point column by using a keyword from Table 4-1. See the for complete syntax specifications.

Floating Point Data Compatibility

Floating point data types are compatible with each other and with other ALLBASE/SQL numeric data types (DECIMAL, INTEGER, and SMALLINT). All arithmetic operations and comparisons and aggregate functions are supported.

Table 4-2 ALLBASE/SQL Floating Point Column Specifications

Possible KeywordsRange of Possible ValuesStored In and Boundary Aligned On

REAL or FLOAT(n) where n = 1 through 24

-3.402823 E+38 through -1.175495 E-38 and 1.175495 E-38 through 3.402823 E+38 and 0

4 bytes

DOUBLE PRECISION or FLOAT or FLOAT(n) where n = 25 through 53

-1.79769313486231 E+308 through -2.22507385850721 E-308 and +2.22507385850721 E-308 through +1.79769313486231 E+308 and 0

8 bytes

 

COBOL DECIMAL Data

COBOL DECIMAL data for the ALLBASE/SQL FLOAT data type is defined in terms of a precision and a scale:

  • Precision is the maximum number of digits in the data, excluding sign and decimal point. ALLBASE/SQL DECIMAL data can have a precision as high as 15.

  • Scale is the number of digits to the right of the decimal point. ALLBASE/SQL DECIMAL data can have a scale as low as zero and as high as the precision value.

When you declare a host variable that will contain a DECIMAL value, the data clause defines the number of digits to the left and the right of the decimal point. The following declaration corresponds to an ALLBASE/SQL column defined as DECIMAL (10,2):



   PIC S9(8)V9(2) COMP-3

          |    |

          |    |

          |    The number of digits to the right of the decimal

          |    point, which is the same as the scale.

          |

          |

          The number of digits to the left of the decimal point,

          calculated by subtracting the scale from the precision.


When you use DECIMAL values in arithmetic operations and certain aggregate functions, the precision and scale of the result are functions of the precisions and scales of the values in the operation. Refer to the for a complete account of how to calculate the precision and scale.

BINARY Data

As with other data types, use the CREATE TABLE or ALTER TABLE command to define a binary or varbinary column. Up to 3996 bytes can be stored in such a column. Each byte contains two hexadecimal digits. For example, suppose you insert data via a host variable into a database column defined as binary. The host variable contains the digits, 1234. In the database, these four digits are stored in two bytes. Each nibble (half byte) contains one digit in hexadecimal format.

BINARY data is stored as a fixed length of left-justified bytes. It is zero padded up to the fixed length you have specified. VARBINARY data is stored as a variable length of left-justified bytes. You specify the maximum possible length. (Note that CHAR and VARCHAR data is stored in a similar manner except that CHAR data is blank padded.)

Binary Data Compatibility

BINARY and VARBINARY data types are compatible with each other and with CHAR and VARCHAR data types. They can be used with all comparison operators and the aggregate functions MIN and MAX; but arithmetic operations are not allowed.

Using the LONG Phrase with Binary Data Types

If the amount of data in a given column of a row can exceed 3996 bytes, it must be defined as a LONG column. Use the CREATE TABLE or ALTER TABLE command to specify the column as either LONG BINARY or LONG VARBINARY.

LONG BINARY and LONG VARBINARY data is stored in the database just as BINARY and VARBINARY data, except that its maximum possible length is practically unlimited.

When deciding on whether to use LONG BINARY versus LONG VARBINARY, and if space is your main consideration, you would choose LONG VARBINARY. However, LONG BINARY offers faster data access.

LONG BINARY and LONG VARBINARY data types are compatible with each other, but not with other data types. Also, the concept of inputting and accessing LONG column data differs from that of other data types. Refer to the for detailed syntax and to the chapter in this document titled "Defining and Using Long Columns" for information about using LONG column data.

DATE, TIME, DATETIME, and INTERVAL Data



    EXEC SQL BEGIN DECLARE SECTION END-EXEC.

   ** DATETIME DATA TYPE      **

    01 BATCHSTAMP       PIC X(23).

   ** DATE DATA TYPE          **

    01 TESTDATE         PIC X(10).

    01 TESTDATEIND      SQLIND.

   ** TIME DATA TYPE          **

    01 TESTSTART        PIC X(8).

    01 TESTSTARTIND     SQLIND.

   ** INTERVAL DATA TYPE      **

    01 LABTIME          PIC X(21).

    01 LABTIMEIND       SQLIND.

    EXEC SQL END DECLARE SECTION END-EXEC.



   *DECLARE and OPEN CURSOR C1 here.  Nulls not allowed for BatchStamp.*



    EXEC SQL FETCH C1

         INTO :BATCHSTAMP,

              :TESTDATE  :TESTDATEIND,

              :TESTSTART :TESTSTARTIND,

              :LABTIME   :LABTIMEIND

    END-EXEC.


Odd-Byte Columns

For BULK record operations, when the precision of a DECIMAL declaration is odd, the COBOL preprocessor generates a filler character. This character, known as a slack byte, ensures that the data is aligned on word boundaries. ALLBASE/SQL requires that data be on word boundaries for certain data manipulation operations.

DECIMAL values are padded by one byte on the left, and string values are padded by one byte on the right.

Most of the time, odd-byte padding has no effect on an application program. If, however, an odd-byte host variable in an array is used by a non-SQL subprogram, the subprogram needs to declare the variable for the passed value in a data description entry compatible with the way ALLBASE/SQL declares the host variable in the modified source file. Whenever the COBOL preprocessor generates a FILLER declaration in the modified source file, the event is flagged as follows in SQLMSG:



   Filler added to adjust for odd-byte field.  (DBWARN 10700)

The example in Figure 4-2 highlights the source file and resulting modified source file generated by the COBOL preprocessor for odd-byte columns.

Figure 4-2 Data Declarations Generated for Boundary Alignment



                                Source File

                  EXEC SQL BEGIN DECLARE SECTION END-EXEC.

                  01   ODDNUMBER       PIC S9(7)V99 COMP-3.

                  01   ODDCHAR         PIC X(15).

                  01   ODDVARCHAR.

                    49 ODDVARCHARLEN   PIC S9(9) COMP.

                    49 ODDVARCHARVAL   PIC X(15).

                  01   BUFFER.

                    05 BUFREC          OCCURS 2 TIMES.

                       10 ODDCHARB     PIC X(15).

                       10 ODDNUMBERB   PIC S9(7)V99 C0MP-3.

                       10 ODDVARCHAR.

                          49 ODDLEN    PIC S9(9) COMP.

                          49 ODDVAL    PIC X(15).

                  EXEC SQL END DECLARE SECTION END-EXEC.



                             Modified Source File

                  **** Start SQL Preprocessor ****

                  *EXEC SQL BEGIN DECLARE SECTION END EXEC.

                  **** End SQL Preprocessor ****



                   01   ODDNUMBER       PIC S9(7)V99 COMP-3.

                   01   ODDCHAR         PIC X(15).

                   01   ODDVARCHAR.

                     49 ODDVARCHARLEN   PIC S9(9) COMP.

                     49 ODDVARCHARVAL   PIC X(15).

                   01   BUFFER.

                     05 BUFREC          OCCURS 2 TIMES.

                        10 ODDCHARB     PIC X(15).

                        10 FILLER       PIC X.

                        10 ODDNUMBERB   PIC S9(7)V99 COMP-3.

                        10 ODDVARCHAR.

                           49 ODDLEN   PIC S9(9) COMP.

                           49 ODDVAL    PIC X(15).



                  **** Start SQL Preprocessor ****

                  *EXEC SQL END DECLARE SECTION END-EXEC.

                  **** End SQL Preprocessor ****


Using Default Data Values

You can choose a default value other than NULL when you create or alter a table by using the DEFAULT specification. Then when data is inserted, and a given column is not in the insert list, the specified default value is inserted. Or when you alter a table, adding a column to existing rows, every occurrence of the column is initialized to the default value. (This conforms to ANSI SQL1 level 2 with addendum-1 and FIPS 127 standards.)

When a table or column is defined with the DEFAULT specification, you will not get an error if a column defined as NOT NULL is not specified in the insert list of an INSERT command. Without the DEFAULT specification, if a column is defined as NOT NULL, it must have some value inserted into it. However, if the column is defined with the DEFAULT specification, it satisfies both the requirement that it be NOT NULL and have some value, in this case, the default value (unless the DEFAULT value is NULL). If a column not in an insert list does allow a NULL, then a NULL is inserted instead of the default value.

Your default specification options are as follows:

  • NULL.

  • USER (this indicates the current DBEUser ID).

  • A constant.

  • The result of the CURRENT_DATE function.

  • The result of the CURRENT_TIME function.

  • The result of the CURRENT_DATETIME function.

Complete syntax for the CREATE TABLE and ALTER TABLE commands as well as definitions of the above options are found in the .

In effect, by choosing any option other than NULL, you assure the column's value to be NOT NULL and of a particular format, unless and until you use the UPDATE command to enter another value.

In the following example, the OrderNumber column defaults to the constant 5, and it is possible to insert a NULL value into the column:



   CREATE PUBLIC TABLE PurchDB.Orders (

                       OrderNumber INTEGER DEFAULT 5,

                       VendorNumber INTEGER,

                       OrderDate    CHAR(8))

                    IN OrderFS


However, suppose you want to define a column default and specify that the column cannot be null. In the next example, the OrderNumber column defaults to the constant 5, and it is not possible to insert a NULL value into this column:



   CREATE PUBLIC TABLE PurchDB.Orders (

                       OrderNumber INTEGER DEFAULT 5 NOT NULL,

                       VendorNumber INTEGER,

                       OrderDate    CHAR(8))

                    IN OrderFS

Coding Considerations

Any default value must be compatible with the data type of its corresponding column. For example, when the default is an integer constant, the column for which it is the default must be created with an ALLBASE/SQL data type of INTEGER, REAL, or FLOAT.

In your application, you input or access data for which column defaults have been defined just as you would data for which defaults are not defined. In this chapter, refer to the section, "Declaring Variables for Data Types," for information on using the data types in your program. Also refer to the section "Declaring Variables for Compatibility" for information relating to compatibility.

When the DEFAULT Clause Cannot be Used

  • You can specify a default value for any ALLBASE/SQL column except those defined as LONG BINARY or LONG VARBINARY. For information on these data types, see the section in this document titled "Using the LONG Phrase with Binary Data Types."

  • With the CREATE TABLE command, you can use either a DEFAULT NULL specification or the NOT NULL specification. An error results if both are specified for a column as in the next example:

    
    
       CREATE PUBLIC TABLE PurchDB.Orders (
    
                           OrderNumber INTEGER {{DEFAULT NULL NOT NULL}},
    
                           VendorNumber INTEGER,
    
                           OrderDate    CHAR(8))
    
                        IN OrderFS
    

Declaring Variables for Compatibility

Under the following conditions, ALLBASE/SQL performs data type conversion when executing SQL commands containing host variables:

  • When the data types of values transferred between your program and a DBEnvironment do not match.

  • When data of one type is moved to a host variable. of a different type

  • When values of different types appear in the same expression.

Data types for which type conversion can be performed are called compatible data types. Table 4-3 “COBOL Data Type Equivalency and Compatibility” summarizes data type-host variable compatibility. It also points out which data type combinations are incompatible and which data type combinations are equivalent, i.e., require no type conversion. E describes an equivalent situation, C a compatible situation, and I an incompatible situation.

Table 4-3 COBOL Data Type Equivalency and Compatibility

ALLBASE/SQL DATA TYPES

PIC X(n)

PIC X(n) 49-level ITEM

PIC S9(4) COMP

PIC S9(9) COMP

PIC S9(p-s) V9(s) COMP-3

CHAR

E

C

I

I

I

VARCHAR

C

E

I

I

I

BINARY

C

C

I

I

I

VARBINARY

C

C

I

I

I

DATE

C

C

I

I

I

TIME

C

C

I

I

I

DATETIME

C

C

I

I

I

INTERVAL

C

C

I

I

I

SMALLINT

I

I

E

C

C

INTEGER

I

I

C

E

C

DECIMAL

I

I

C

C

E

 

As the following example illustrates, the ISQL INFO command provides the information you need to declare host variables compatible with or equivalent to ALLBASE/SQL data types. It also provides the information you need to determine whether an indicator variable is needed to handle null values:



   isql=> INFO PURCHDB.ORDERITEMS;



   Column Name         Data Type (length)                  Nulls Allowed

   ---------------------------------------------------------------------

   ORDERNUMBER         Integer                                   NO

   ITEMNUMBER          Integer                                   NO

   VENDPARTNUMBER      Char (16)                                 YES

   PURCHASEPRICE       Decimal (10,2)                            NO

   ORDERQTY            SmallInt                                  YES

   ITEMDUEDATE         Char (8)                                  YES

   RECEIVEDQTY         SmallInt                                  YES


The example identified as Figure 4-3 is a query that accesses the PURCHDB.ORDERITEMS table. The query produces a single-row query result that consists of two maximum values. The declare section illustrated contains data clauses equivalent to the data types in the PURCHDB.ORDERITEMS table:

  • ORDERNUMBER is an INTEGER variable because the column whose data it holds is INTEGER.

  • PURCHASEPRICE is declared as a DECIMAL variable because it holds the DECIMAL result of an aggregate function on a DECIMAL column.

  • DISCOUNT is declared as a DECIMAL variable because it is used in an arithmetic expression with a DECIMAL column, PurchasePrice.

  • ORDERQTY is declared as a SMALLINT variable because it holds the result of a SMALLINT column, ORDERQTY.

  • ORDERQTYIND is an indicator variable, necessary because the resulting ORDERQTY can contain null values. Note in the INFO example above that this column allows null values.

Figure 4-3 Declaring Host Variables for Single-Row Query Results



DATA DIVISION.

.

.

WORKING-STORAGE SECTION.

EXEC SQL BEGIN DECLARE SECTION END-EXEC.

.

.

01  ORDERNUMBER             PIC S9(9) COMP.

01  PURCHASEPRICE           PIC S9(8)V9(2) COMP-3.

01  DISCOUNT                PIC S9(8)V9(2) COMP-3.

01  ORDERQTY                PIC S9(4) COMP.

01  ORDERQTYIND             SQLIND.

.

.

EXEC SQL END DECLARE SECTION END-EXEC.

.

.

PROCEDURE DIVISION.

.

.

     EXEC SQL SELECT  PURCHASEPRICE * :DISCOUNT,

                      ORDERQTY,

                INTO :PURCHASEPRICE,

                     :ORDERQTY :ORDERQTYIND,

                FROM  PURCHDB.ORDERITEMS

               WHERE  ORDERNUMBER = :ORDERNUMBER

     END-EXEC.


The example in Figure 4-4 is similar to that in Figure 4-3. This query, however, is a BULK query, which may return a multiple-row query result. And it incorporates a HAVING clause.

  • ORDERSARRAY is the name of the array for storing the query result. It is large enough to hold as many as 25 rows. Each row in the array has the same format as that in the single-row query result just discussed.

  • FIRSTROW and TOTALROWS are declared as SMALLINT variables, since their maximum value is the size of the array, in this case, 25.

  • GROUPCRITERION is an INTEGER variable because its value is compared in the HAVING clause with the result of a COUNT function, which is always an INTEGER value.

Figure 4-4 Declaring Host Variables for Multiple-Row Query Results



DATA DIVISION.

.

.

.

WORKING-STORAGE SECTION.



EXEC SQL BEGIN DECLARE SECTION END-EXEC.

.

.

.

01  DISCOUNT                    PIC S9(8)V9(2) COMP-3.

01  ORDERSARRAY.

  05  EACH-ROW                OCCURS 25 TIMES.

    10  PURCHASEPRICE           PIC S9(8)V9(2) COMP-3.

    10  ORDERQTY                PIC S9(4) COMP.

    10  ORDERQTYIND             SQLIND.

    10  ORDERNUMBER             PIC S9(9) COMP.

01  FIRSTROW                    PIC S9(4) COMP.

01  TOTALROWS                   PIC S9(4) COMP.

01  LOWVALUE                    PIC S9(9) COMP.

01  HIGHVALUE                   PIC S9(9) COMP.

01  GROUPCRITERION              PIC S9(9) COMP.

EXEC SQL END DECLARE SECTION END-EXEC.

.

.

.

PROCEDURE DIVISION.

.

.

.

   EXEC SQL BULK SELECT  PURCHASEPRICE * :DISCOUNT,

                         ORDERQTY,

                         ORDERNUMBER

                   INTO :ORDERSARRAY,

                        :FIRSTROW,

                        :TOTALROWS

                   FROM  PURCHDB.ORDERITEMS

                  WHERE  ORDERNUMBER

                         BETWEEN :LOWVALUE AND :HIGHVALUE

               GROUP BY  ORDERQTY, ORDERNUMBER

                 HAVING  COUNT(ITEMNUMBER) > :GROUPCRITERION

   END-EXEC.


String Data Conversion

When ALLBASE/SQL moves string data of one type to a host variable declared as a compatible type, the following occurs:

  • When moving CHAR data to a VARCHAR variable, ALLBASE/SQL places the length of the string in the appropriate 49-level variable and pads the string on the right with spaces to fill up the VARCHAR string variable.

  • When moving VARCHAR data to a CHAR variable, ALLBASE/SQL pads the string on the right with spaces to fill up the CHAR string variable.

String Data Truncation

If the target host variable used in a SELECT or FETCH operation is too small to hold an entire string, the string is truncated. You can use an indicator variable to determine the actual length of the string in bytes before truncation:



   WORKING-STORAGE SECTION.

   EXEC SQL BEGIN DECLARE SECTION END-EXEC.

   .

   .

   .

   01  LITTLE-STRING              PIC X(40).

   01  LITTLE-STRING-IND          SQLIND.

   .

   .

   .

   EXEC SQL END DECLARE SECTION END-EXEC.

   .

   .

   .

   PROCEDURE DIVISION.

   .

   .

   .

       EXEC SQL SELECT  BIG_STRING

                  INTO :LITTLE-STRING :LITTLE-STRING-IND

                  .

                  .

                  .


When the string in column BIG_STRING is too long to fit in host variable LITTLE-STRING, ALLBASE/SQL puts the actual length of the string into indicator variable LITTLE-STRING-IND.

If a column is too small to hold a string in an INSERT or an UPDATE operation, the string is truncated and stored. ALLBASE/SQL gives no error or warning message, but SQLWARN1 will contain a W.

Numeric Data Conversion

When you use numeric data of different types in an expression or comparison operation, data types with less precision are converted into data types of greater precision. The result has the greater precision. ALLBASE/SQL numeric types available in COBOL have the following precedence, from highest to lowest:

  1. DECIMAL

  2. INTEGER

  3. SMALLINT

The following example illustrates numeric type conversion:



   WORKING-STORAGE SECTION.

   EXEC SQL BEGIN DECLARE SECTION END-EXEC.

   01  DISCOUNT           PIC S9(9) COMP.

   01  MAXPURCHASEPRICE   PIC S9(9) COMP.

   .

   .

   .

   EXEC SQL END DECLARE SECTION END-EXEC.

   .

   .

   .

   PROCEDURE DIVISION.

   .

   .

   .

       EXEC SQL SELECT  MAX(PURCHASEPRICE) * :DISCOUNT

                  INTO :MAXPURCHASEPRICE

                  FROM  PURCHDB.ORDERITEMS

       END-EXEC.


The query illustrated contains in the select list an aggregate function, MAX. The argument of the function is the PURCHASEPRICE column, defined in the PARTSDBE DBEnvironment as DECIMAL(10,2). Therefore the result of the function is DECIMAL. Since the host variable named DISCOUNT is declared as an INTEGER, a data type compatible with DECIMAL, ALLBASE/SQL converts the value in DISCOUNT to a DECIMAL quantity having a precision of 10 and a scale of 0.

After subtraction, data conversion occurs again before the DECIMAL result is stored in the INTEGER host variable MAXPURCHASEPRICE. In this case, the fractional part of the DECIMAL value is truncated. If the fractional part is zero, no error results. Otherwise, an error condition occurs.

Refer to the for additional information on how type conversion can cause truncation and overflow of numeric values.

Declaring Variables for Program Elements

The following section discusses how to declare elements specific to ALLBASE/SQL programs. In addition, Table 4-4 “Program Element Data Description Entries” provides the syntax of these special elements.

Table 4-4 Program Element Data Description Entries

PROGRAM ELEMENTCOBOL DATA DECLARATIONS

Indicator variable

01 IND-VAR-NAME SQLIND.

Array of n rows

01 ARRAY-NAME.

Data values

05 ROW-NAME OCCURS n TIMES. 10 COLUMN1-NAME valid data clause. 10 COLUMN2-NAME valid data clause.

Indicator variable

10 IND-VAR-NAME SQLIND.

StartIndex

01 START-INDEX-NAME PIC S9(4) COMP. or 01 START-INDEX-NAME PIC S9(9) COMP.

NumberOfRows

01 NUM-ROWS-NAME PIC S9(4) COMP. or 01 NUM-ROWS-NAME PIC S9(9) COMP.

Dynamic commands

01 COMMAND-NAME CHAR or VARCHAR data clause.

Savepoint numbers

01 SAVEPOINT-NAME PIC S9(9) COMP.

Message catalog messages

01 MESSAGE-NAME CHAR or VARCHAR data clause.

DBEnvironment name

01 DBE-NAME CHAR or VARCHAR data clause.

 

SQLCA Array

Every ALLBASE/SQL COBOL program must have the SQL Communications Area (SQLCA) declared in the working storage section of the DATA DIVISION. You can use the INCLUDE command to declare the SQLCA:



   EXEC SQL INCLUDE SQLCA END-EXEC.


Refer to the chapter, "Runtime Status Checking and the SQLCA," for further information regarding the SQLCA.

Bulk Processing Arrays

When you declare an array for holding the results of a BULK SELECT or BULK FETCH operation, ensure that you declare the fields in the same order as in the select list. (For single-row query results, however, the order of declaration does not have to match the select list order.) In addition, each indicator variable field must be declared immediately after the host variable field it describes. And if used, the bulk processing indicator variables (starting index and number of rows) are declared as 01 level data descriptions. They must be referenced in order (starting index followed by number of rows) immediately following your array reference. Refer back to Figure 4-4 again for an example.

Indicator Variables

Each indicator variable must be declared immediately following the host variable it describes, as shown in Figures 4-3 and 4-4. (The SQLIND data clause must be complete before column 64.) If a column allows nulls, a null indicator must be declared for it.

When the COBOL preprocessor encounters SQLIND, it generates the following declaration in its place in SQLOUT:



   PIC S9(4) COMP

Dynamic Commands

The maximum size for the host variable used to hold dynamic commands is 32,762 bytes. Such a host variable can be declared as a CHAR or VARCHAR data type. In Figure 4-5, one host variable is declared to hold a CHAR dynamic command of up to 2048 bytes. The second host variable is declared to hold a VARCHAR dynamic command of 80 bytes or less.

Figure 4-5 Declaring Host Variables for Dynamic Commands



DATA DIVISION.

.

.

.

WORKING-STORAGE SECTION.



EXEC SQL BEGIN DECLARE SECTION END-EXEC.

.

.

.

01  DYNAMIC-COMMAND           PIC X(2048).

.

.

.

01  DYNAMIC-COMMAND-2.

   49  LENGTH                PIC S9(9) COMP.

   49  VALUE                 PIC X(80).

.

.

.

EXEC SQL END DECLARE SECTION END-EXEC.

.

.

.

PROCEDURE DIVISION.

.

.

.

    EXEC SQL PREPARE  COMMAND-ON-THE-FLY

                 FROM :DYNAMIC-COMMAND

    END-EXEC.

.

.

.

    EXEC SQL PREPARE  COMMAND-ON-THE-FLY

                FROM :DYNAMIC-COMMAND-2

    END-EXEC.


Savepoint Numbers

Savepoint numbers are positive numbers ranging from 1 to 2,147,483,647. A host variable for holding a savepoint number should be declared as an integer.

Figure 4-6 Declaring Host Variables for Savepoint Numbers



DATA DIVISION.

.

.

.

WORKING-STORAGE SECTION.



EXEC SQL BEGIN DECLARE SECTION END-EXEC.

.

.

.

01  SAVEPOINT1           PIC S9(9) COMP.

.

.

.

EXEC SQL END DECLARE SECTION END-EXEC.

.

.

PROCEDURE DIVISION.

.

.

    EXEC SQL SAVEPOINT :SAVEPOINT1 END-EXEC.


Messages from the Message Catalog

The maximum size of a message catalog message is 256 bytes. Figure 4-7 illustrates how a host variable for holding a message might be declared.

Figure 4-7 Declaring Host Variables for Message Catalog Messages



DATA DIVISION.

.

.

.

WORKING-STORAGE SECTION.



EXEC SQL BEGIN DECLARE SECTION END-EXEC.

.

.

.

01  STATUSMESSAGE.

  49  MESSAGE-LENGTH            PIC S9(4) COMP.

  49  MESSAGE-TEXT              PIC X(256).

.

.

.

EXEC SQL END DECLARE SECTION END-EXEC.

.

.

.

PROCEDURE DIVISION.

.

.

.

EXEC SQL SQLEXPLAIN :STATUSMESSAGE END-EXEC.

DISPLAY MESSAGE-TEXT.


DBEnvironment Name

The DBEnvironment you specify in the preprocessor command line is the same as the DBECon file name. The maximum length of the complete pathname for a DBEnvironment is 128 bytes. When used in a host variable, the DBEnvironment name can be unquoted or enclosed in single quotation marks.

Figure 4-8 Declaring Host Variables for DBEnvironment Names



WORKING-STORAGE SECTION.

EXEC SQL BEGIN DECLARE SECTION END-EXEC.

.

.

.

01  SOMEDBE         PIC X(128).

.

.

.

EXEC SQL END DECLARE SECTION END-EXEC.

.

.

PROCEDURE DIVISION.

.

.

  DISPLAY "Enter DBEnvironment name> ".

  ACCEPT SOMEDBE.

  EXEC SQL CONNECT TO :SOMEDBE END-EXEC.


The host variable can be declared as a CHAR or VARCHAR variable. In this example, it is declared as CHAR.

Declaring Host Variables Passed Between Subprograms

Two instances require that you pass ALLBASE/SQL data structures between calling and called subprograms and/or programs.

  • When using the same DBEnvironment in both calling and called code, SQLCA data must be passed.

  • When using the same host variables in both calling and called code, both SQLCA data and host variable data must be passed.

For example, in Figure 4-9 the host variable passed is declared in the CallingProgram outside a declare section, because it is not used in an SQL command in that program. The passed host variable is declared in the INSERTsubpgm within a declare section in the LINKAGE SECTION. This is because it is used in an SQL command in the subprogram.

Note that USING clauses in both calling and called code name both the SQLCA and the passed host variable. The SQLCA must always be named in this clause in programs and subprograms that contain SQL commands to be executed from the same DBE session.

Figure 4-9 Declaring Host Variables Passed Between Subprograms



PROGRAM-ID.   CallingProgram.

.

.

.  

WORKING-STORAGE SECTION.

EXEC SQL INCLUDE SQLCA END-EXEC.

01  PARTNUMBER        PIC X(16).

  .

PROCEDURE DIVISION.

  .

    EXEC SQL CONNECT TO 'PARTSDBE.SOMEGRP.SOMEACCT' END-EXEC.

.

.

.



    IF RESPONSE-PREFIX = "1" THEN

    DISPLAY "INSERT rows into the Parts Table."

    CALL "INSERTsubpgm" USING SQLCA PARTNUMBER

 DISPLAY "Last row inserted had part number:  " PARTNUMBER.

                      |

                      |

                      V



PROGRAM-ID.   INSERTsubpgm.

.

.

.



WORKING-STORAGE SECTION.

EXEC SQL BEGIN DECLARE SECTION END-EXEC.

01  PARTNAME              PIC X(30).

01  SALESPRICE            PIC S9(10)V(2) COMP-3.

EXEC SQL END DECLARE SECTION END-EXEC.



LINKAGE SECTION.

EXEC SQL INCLUDE SQLCA END-EXEC.

EXEC SQL BEGIN DECLARE SECTION END-EXEC.

01  PARTNUMBER            PIC X(16).

EXEC SQL END DECLARE SECTION END-EXEC.

 .

PROCEDURE DIVISION USING SQLCA PARTNUMBER.

 .

    EXEC SQL INSERT INTO   PURCHDB.PARTS

                          (PARTNUMBER,

                           PARTNAME,

                           SALESPRICE)

                   VALUES (:PARTNUMBER,

                           :PARTNAME,

                           :SALESPRICE)

    END-EXEC.

.

.

. 

     GOBACK.


Feedback to webmaster