Examples of referencing a structure for output based on the earlier structure follow.
Assume the following table resides on the database:
CREATE TABLE TABLE1, NO FALLBACK, NO BEFORE JOURNAL, NO AFTER JOURNAL (FIELD1 CHAR(20), FIELD2 INTEGER, FIELD3 CHAR(6), FIELD4 DECIMAL(13,2)) UNIQUE PRIMARY INDEX (FIELD1)
Example: Single Row SELECT
EXEC SQL SELECT * INTO :STRUCTURE1 FROM TABLE1 WHERE FIELD3 = ’ABCDEF’ END-EXEC
Example: Multiple Row SELECT
EXEC SQL DECLARE C1 CURSOR FOR SELECT * FROM TABLE1 END-EXEC EXEC SQL OPEN C1 END-EXEC EXEC SQL FETCH C1 INTO :STRUCTURE1 (loop for FETCH) END-EXEC EXEC SQL CLOSE C1 END-EXEC
Example: Single Row SELECT That Returns Only Some Columns
EXEC SQL SELECT FIELD1, FIELD3 INTO :FIELD1, :FIELD3 FROM TABLE1 WHERE FIELD2 = 99 END-EXEC
Example: Single Row SELECT Using Qualified Variable References
EXEC SQL SELECT FIELD1, FIELD3 INTO :STRUCTURE1.FIELD1, :STRUCTURE1.FIELD3 FROM TABLE1 WHERE FIELD2 = 99 END-EXEC
Example: Single Row INSERT Using a Structure for Field Values
EXEC SQL INSERT INTO TABLE1 VALUES (:STRUCTURE1) END-EXEC
As a result, the field in the table receives these assignments:
TABLE1.FIELD1 <- FIELD1 of STRUCTURE1 TABLE1.FIELD2 <- FIELD2 of STRUCTURE1 TABLE1.FIELD3 <- FIELD3 of STRUCTURE1 TABLE1.FIELD4 <- FIELD4 of STRUCTURE1
The precompiler uses the elementary items as sending/receiving variables whenever using a host structure name.
If this structure is defined as:
01 STRUCTURE1.
02 FIELD1 PIC X(20).
02 FIELD2 PIC S9(9) <comp>.
02 FIELD3.
03 FIELD3A PIC X(2).
03 FIELD3B PIC X(2).
03 FIELD3C PIC X(2).
02 FIELD4 PIC S9(11)V99 COMP-3.
where <comp> is COMP-5 for MF COBOL and COMP for all other COBOL compilers), and specify the following single row SELECT statement:
EXEC SQL SELECT * INTO :STRUCTURE1 FROM TABLE1 WHERE FIELD3 = ’ABCDEF’ END-EXEC
the precompiler generates code so that COBOL attempts these assignments:
TABLE1.FIELD1 -> FIELD1 of STRUCTURE1 TABLE1.FIELD2 -> FIELD2 of STRUCTURE1 TABLE1.FIELD3 -> FIELD3A of STRUCTURE1 TABLE1.FIELD4 -> FIELD3B of STRUCTURE1
Data moved into FIELD3A is truncated; moving data into FIELD3B causes an error.