Was this helpful?
Variable Usage
COBOL variables (that is, data items) declared in an embedded SQL declaration section can substitute for most elements of embedded SQL statements that are not keywords. Of course, the variable and its data type must make sense in the context of the element. When you use a COBOL variable in an embedded SQL statement, you must precede it with a colon. As an example, the following select statement uses the data items NAMEVAR and NUMVAR to receive data and the data item IDNO as an expression in the where clause.
Example: Variable declarations
EXEC SQL SELECT ename, eno
    INTO :NAMEVAR, :NUMVAR
    FROM employee
    WHERE eno = :IDNO END-EXEC.
Various rules and restrictions apply to the use of COBOL variables in embedded SQL statements. The following sections describe the usage syntax of different categories of variables and provide examples of such use.
To distinguish the minus sign used as a subtraction operator in an embedded SQL statement from the hyphen used as a character in a data item name, you must delimit the minus sign by blanks. For example, the statement:
EXEC SQL INSERT INTO employee (ename, eno)
    VALUES ('Jones', :ENO-2)
    END EXEC.
indicates that the data item ENO-2 is to be inserted into the database column. To insert a value two less than the value in the data item ENO, you must instead use the following statement:
EXEC SQL INSERT INTO employee (ename, eno)
    VALUES ('Jones', :ENO - 2)
    END EXEC.
Note the spaces surrounding the minus sign.
Elementary Data Items
To refer to a simple scalar-valued data item (numeric, alphanumeric, or alphabetic), use the following syntax:
:simplename
The following program fragment demonstrates a typical error handling paragraph. The data items BUFFER and SECONDS are scalar-valued variables.
Example: Elementary data items usage
DATA DIVISION.
WORKING-STORAGE SECTION.

EXEC SQL BEGIN DECLARE SECTION END-EXEC.

01 SECONDS PIC S9(4) USAGE COMP.
01 BUFFER PIC X(100).
EXEC SQL END DECLARE SECTION END-EXEC.

* Program code

ERROR-HANDLE.

EXEC FRS MESSAGE :BUFFER END-EXEC.
EXEC FRS SLEEP :SECONDS END-EXEC.

*More error code.
COBOL Tables
To refer to a COBOL table, use the following syntax:
:tablename(subscript{,subscript})
Syntax Notes:
You must subscript the tablename because only elementary data items are legal SQL values.
When you declare a COBOL table, the preprocessor notes from the OCCURS clause that it is a table and not some other data item. When the table is later referenced in an ESQL statement, the preprocessor confirms that a subscript is present but does not check the legality of the subscript inside the parentheses. Consequently, you must ensure that the subscript is legal and that the correct number of subscripts is used.
If you use COBOL tables as null indicator arrays with COBOL record assignments, do not include subscripts.
The following example uses the variable SUB1 as a subscript that does not need to be declared in the embedded SQL declaration section because the preprocessor ignores it.
Example: COBOL table usage
EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 FORMNAMES.
  02 FORM-TABLE PIC X(8) OCCURS 3 TIMES.

EXEC SQL END DECLARE SECTION END-EXEC.

01 SUB1 PIC S9(4) USAGE COMP VALUE ZEROES.

PROCEDURE DIVISION.
BEGIN.
* Program code

PERFORM VARYING SUB1 FROM 1 BY 1
   UNTIL SUB1 > 3

EXEC FRS FORMINIT :FORM-TABLE(SUB1) END-EXEC

END-PERFORM.

* More program code.
Record Data Items
You can use a record data item (also known as a structure variable) in two different ways. First, you can use the record or a group item in the record as a simple variable, implying that all its elementary items (also known as structure members) are used. This is appropriate in the embedded SQL select, fetch, and insert statements. Second, you can refer to an elementary data item in the record alone.
Use the following syntax to refer to a record or group item:
:{groupname IN | OF }recordname
Alternatively, you can use the following "dot" notation, in which the record or group item is specified from the outer level inwards:
:recordname{.groupname}
Syntax Notes:
The recordname can refer to either a record or a group item. It can be an element of a table of group items. Any reference that yields a record or group item is acceptable. For example:
   * A record or unambiguous group item reference
         :EMPREC
   * A group item in a table of group items
         :EMPREC-TABLE(SUB1)
   * A group item subordinate to two group items
         :GROUP3 IN GROUP2 IN REC
         :REC.GROUP2.GROUP3
To be used as a collection of variables, the record (or group item) referenced must have no subordinate groups or tables. The preprocessor enumerates all the elements of the record, which must be elementary items. The preprocessor generates code as though the program had listed each elementary item of the record in the order in which it was declared.
The qualification of a record item can be elliptical; that is, you do not need to specify all the names in the hierarchy in order to reference the item. You must not, however, use an ambiguous reference that does not clearly qualify an item. For example, assume the following declaration:
01 PERSON.
  02 NAME.
      03 LAST PIC X(18).
      03 FIRST PIC X(12).
  02 AGE PIC S9(4) USAGE COMP.
  02 ADDR PIC X(50).
If the variable NAME was referenced, the preprocessor would assume the reference was to the group item NAME IN PERSON. However, if there also existed the declaration:
01 CHILD.
  02 NAME.
     03 LAST PIC X(18).
     03 FIRST PIC X(12).
  02 PARENT PIC X(30).
the reference to NAME would be ambiguous, because it could refer to either NAME IN PERSON or NAME IN CHILD.
The following example uses the employee.dcl file, generated by DCLGEN, to retrieve values into a record.
EXEC SQL BEGIN DECLARE SECTION END-EXEC.

* See above for description.
EXEC SQL INCLUDE 'employee.dcl' END-EXEC.

EXEC SQL END DECLARE SECTION END-EXEC.

EXEC SQL SELECT *
INTO :EMPREC
FROM employee
WHERE eno = 123
END-EXEC.
The example above generates code as though the following statement had been issued instead:
EXEC SQL SELECT *
 INTO :ENO IN EMPREC, :ENAME IN EMPREC, :AGE IN EMPREC,
     :JOB IN EMPREC, :SAL IN EMPREC, :DEPT IN EMPREC
 FROM employee
 WHERE eno = 123
 END-EXEC.
The following example fetches the values associated with all the columns of a cursor into a record:
EXEC SQL BEGIN DECLARE SECTION END-EXEC.

* See above for description.
EXEC SQL INCLUDE 'employee.dcl' END-EXEC.

EXEC SQL END DECLARE SECTION END-EXEC.

EXEC SQL DECLARE empcsr CURSOR FOR
SELECT *
FROM employee
ORDER BY ename
END-EXEC.
...
EXEC SQL FETCH empcsr INTO :EMPREC END-EXEC.
The following example inserts values by looping through a locally declared table of records whose items have been initialized:
DATA DIVISION.
WORKING-STORAGE SECTION.

EXEC SQL INCLUDE SQLCA END-EXEC.

EXEC SQL BEGIN DECLARE SECTION END-EXEC.

EXEC SQL DECLARE person TABLE
(pname char(30),
 page integer1,
 paddr varchar(50)) END-EXEC.

01 PERSON-REC.
 02 PERSON OCCURS 10 TIMES.
      03 NAME PIC X(30).
      03 AGE PIC S9(4) USAGE COMP.
      03 ADDR PIC X(50).

EXEC SQL END DECLARE SECTION END-EXEC.

01 SUB1 PIC S9(4) USAGE COMP.

PROCEDURE DIVISION.
BEGIN.

* Initialization code.

PERFORM VARYING SUB1 FROM 1 TO 10
    UNTIL SUB1 > 10

EXEC SQL INSERT INTO person
    VALUES (:PERSON(SUB1))
    END-EXEC
END-PERFORM.
The insert statement in the example just shown generates code as though the following statement had been issued instead:
EXEC SQL INSERT INTO person
VALUES (:NAME IN PERSON(SUB1), :AGE IN PERSON(SUB1),  :ADDR IN PERSON(SUB1))
 END-EXEC
Elementary Items from a Record
The syntax embedded SQL uses to refer to an elementary item record is the same as in COBOL:
:elementary-item-name IN | OF{ groupname IN | OF} recordname
Alternatively, you can use the following "dot" notation, in which the elementary item is specified from the outer level inwards:
:recordname{.groupname}.elementary-item-name
Syntax Notes:
The referenced item must be a scalar value (numeric, alphanumeric, or alphabetic). There can be any combination of tables and records, but the last referenced item must be a scalar value. Thus, the following references are all legal:
  * Element of a record
    :SAL IN EMPLOYEE
    :SAL OF EMPLOYEE
    :EMPLOYEE.SAL
  * Element of a record as an item of a table
    :NAME IN PERSON(3)
    :PERSON(3).NAME
  * Deeply nested element
    :ELEMENTARY-ITEM OF GROUP3 OF GROUP2 OF REC
    :REC.GROUP2.GROUP3.ELEMENTARY-ITEM
The qualification of an elementary item in a record can be elliptical; that is, you do not need to specify all the names in the hierarchy in order to reference the item. You must not, however, use an ambiguous reference that does not clearly qualify an item. For example, assume the following declaration:
01 PERSON.
   02 NAME PIC X(30).
   02 AGE PIC S9(4) USAGE COMP.
   02 ADDR PIC X(50).
If the variable NAME was referenced in your program, the preprocessor would assume the reference was to the elementary item NAME IN PERSON. However, if also there existed the declaration:
01 CHILD.
    02 NAME PIC X(30).
    02 PARENT PIC X(30).
the reference to NAME would be ambiguous because it could refer to either NAME IN PERSON or NAME IN CHILD.
Subscripts, if present, must qualify the data item declared with the OCCURS clause.
The following example uses the record EMPREC in the employee.dcl file generated by DCLGEN to put values into the empform form:
EXEC SQL BEGIN DECLARE SECTION END-EXEC.

* See above for description.
    EXEC SQL INCLUDE 'employee.dcl' END-EXEC.

EXEC SQL END DECLARE SECTION END-EXEC.

EXEC FRS PUTFORM empform
(eno = :ENO IN EMPREC, ename = :ENAME IN EMPREC,
 age = :AGE IN EMPREC, job = :JOB IN EMPREC,
 sal = :SAL IN EMPREC, dept = :DEPT IN EMPREC)
END-EXEC.
You could also write the putform statement without the EMPREC qualifications, assuming there are no ambiguous references to the item names:
EXEC FRS PUTFORM empform
     (eno = :ENO, ename = :ENAME, age = :AGE,
     job = :JOB, sal = :SAL, dept = :DEPT)
     END-EXEC.
Indicator Data Items
The syntax for referring to an indicator data item is the same as for an elementary data item, except that an indicator variable is always associated with another COBOL data item:
:data_item:indicator_item
or
:data_item indicator :indicator_item
Syntax Notes:
The indicator data item can be an elementary data item or an element of a table that yields a 2byte integer numeric data item. For example:
01 IND-1 PIC S9(4) USAGE COMP.
01 IND-TABLE.
  02 IND-2 PIC S9(4) USAGE COMP OCCURS 5 TIMES.
  :ITEM-1:IND-1
  :ITEM-2:IND-2(4)
If the data item associated with the indicator data item is a record, the indicator data item must be a table of indicators. In this case, do not subscript the table (see the following example).
When an indicator table is used, the first element of the table is associated with the first member of the record, the second element with the second member, and so on. Table elements begin at subscript 1.
The following example uses the employee.dcl file that DCLGEN generates, to retrieve values into a record and null values into the EMPIND table:
EXEC SQL BEGIN DECLARE SECTION END-EXEC.

* See above for description.

EXEC SQL INCLUDE 'employee.dcl' END-EXEC.
01 INDS.
 02 EMPIND PIC S9(4) USAGE COMP OCCURS 10 TIMES.
EXEC SQL END DECLARE SECTION END-EXEC.

EXEC SQL SELECT *
 INTO :EMPREC:EMPIND
 FROM employee
 END-EXEC
The example just shown generates code as though the following statement had been issued:
EXEC SQL SELECT *
INTO :ENO IN EMPREC:EMPIND(1),
     :ENAME IN EMPREC:EMPIND(2),
     :AGE IN EMPREC:EMPIND(3),
     :JOB IN EMPREC:EMPIND(4),
     :SAL IN EMPREC:EMPIND(5),
     :DEPT IN EMPREC:EMPIND(6),
  FROM employee
  END-EXEC
Last modified date: 04/03/2024