Integrating SQL (Structured Query Language) into COBOL programs allows mainframe applications to interact with relational databases like DB2. This is primarily achieved through Embedded SQL, where SQL statements are placed directly within the COBOL source code.
SQL statements in a COBOL program must be clearly demarcated so that a special SQL precompiler (or preprocessor) can identify and process them before the standard COBOL compilation.
EXEC SQL
and END-EXEC
: All executable SQL statements are enclosed between these two delimiters.1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950IDENTIFICATION DIVISION. PROGRAM-ID. EMBEDDED-SQL-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-EMP-ID PIC X(6). 01 WS-EMP-NAME PIC X(30). 01 WS-EMP-DEPT PIC X(3). * Include SQL Communications Area (SQLCA) to check SQL status EXEC SQL INCLUDE SQLCA END-EXEC. * Include DCLGEN for the Employee table (Host Variables) * EXEC SQL * INCLUDE EMPDCLG *> Assuming EMPDCLG is the DCLGEN member * END-EXEC. * Or define host variables directly: 01 HV-EMP-ID PIC X(6). 01 HV-EMP-NAME PIC X(30). 01 HV-EMP-DEPT PIC X(3). 01 HV-EMP-SALARY PIC S9(7)V99 COMP-3. PROCEDURE DIVISION. MAIN-LOGIC. DISPLAY "Enter Employee ID to fetch: ". ACCEPT WS-EMP-ID. MOVE WS-EMP-ID TO HV-EMP-ID. EXEC SQL SELECT EMPNAME, EMPDEPT, SALARY INTO :HV-EMP-NAME, :HV-EMP-DEPT, :HV-EMP-SALARY FROM EMPLOYEE_TABLE WHERE EMPID = :HV-EMP-ID END-EXEC. IF SQLCODE = 0 DISPLAY "Employee Found:" DISPLAY "Name: " HV-EMP-NAME DISPLAY "Department: " HV-EMP-DEPT DISPLAY "Salary: " HV-EMP-SALARY ELSE IF SQLCODE = 100 DISPLAY "Employee Not Found." ELSE DISPLAY "SQL Error Occurred." DISPLAY "SQLCODE: " SQLCODE DISPLAY "SQLERRMC: " SQLERRMC OF SQLCA(1:SQLERRML OF SQLCA) *> Display error message tokens END-IF. STOP RUN.
The above example demonstrates a simple SELECT
statement. Notice the use of host variables (prefixed with a colon :
in the SQL statement) to pass data between COBOL and SQL.
EXEC SQL INCLUDE SQLCA END-EXEC.
) that the database system uses to communicate the status of SQL operations back to the COBOL program. The most important field is SQLCODE
(or SQLSTATE
for ANSI standard codes).DATA DIVISION
(usually WORKING-STORAGE SECTION
or LINKAGE SECTION
) used to pass data to SQL statements (e.g., in a WHERE
clause or VALUES
list) or to receive data from SQL statements (e.g., in an INTO
clause). They are prefixed with a colon (:
) within the SQL statements but not in COBOL procedural code.SQLCODE
after every EXEC SQL
statement is crucial. Common values: 0
(Successful), +100
(Not Found or end of data), negative values (Error).COMMIT
and ROLLBACK
are also embedded using EXEC SQL ... END-EXEC
to manage logical units of work.The EXEC SQL INCLUDE member-name END-EXEC
directive is a crucial part of writing maintainable and accurate COBOL SQL programs. It instructs the SQL precompiler to copy the contents of a specified member (like a COBOL copybook or a DCLGEN member) into the source program at that point.
INCLUDE
EXEC SQL INCLUDE SQLCA END-EXEC.
SQLCODE
, SQLSTATE
, and other diagnostic fields after an SQL operation.EXEC SQL INCLUDE DCLGEN_member_name END-EXEC.
EXEC SQL INCLUDE SQLDA END-EXEC.
12345678910111213141516171819202122232425262728293031323334353637383940WORKING-STORAGE SECTION. * Standard SQL Communication Area EXEC SQL INCLUDE SQLCA END-EXEC. * Declaration for the DEPARTMENTS table from DCLGEN member 'DEPTDCL' * Assume DEPTDCL contains something like: * 01 DCLDEPARTMENTS. * 05 DEPTNO PIC X(3). * 05 DEPTNAME PIC X(30). * 05 MGRNO PIC X(6). * 05 ADMRDEPT PIC X(3). * 01 DCLDEPARTMENTS-NULL-IND. * 05 DEPTNO-NI PIC S9(4) COMP. * 05 DEPTNAME-NI PIC S9(4) COMP. * 05 MGRNO-NI PIC S9(4) COMP. * 05 ADMRDEPT-NI PIC S9(4) COMP. EXEC SQL INCLUDE DEPTDCL END-EXEC. * Host variables based on the included DCLGEN 01 HV-TARGET-DEPTNO PIC X(3). PROCEDURE DIVISION. MOVE "A00" TO HV-TARGET-DEPTNO. EXEC SQL SELECT DEPTNAME, MGRNO INTO :DCLDEPARTMENTS.DEPTNAME, :DCLDEPARTMENTS.MGRNO FROM USERADM.DEPARTMENTS *> Example table name WHERE DEPTNO = :HV-TARGET-DEPTNO END-EXEC. IF SQLCODE = ZERO DISPLAY "Department Name: " DCLDEPARTMENTS.DEPTNAME DISPLAY "Manager No: " DCLDEPARTMENTS.MGRNO ELSE DISPLAY "SQL Error or Not Found. SQLCODE: " SQLCODE END-IF.
Using INCLUDE
promotes consistency by ensuring that all programs use the same, centrally defined structures for SQLCA and table layouts. This greatly simplifies maintenance and reduces errors.
The SQL precompiler resolves these INCLUDE
statements by literally inserting the content of the specified member into the COBOL source before translating the SQL. If the member is not found, or if there are issues within the included member, the precompilation step will fail.
The EXEC SQL WHENEVER END-EXEC
directive provides a way to specify automatic error or warning handling for subsequent embedded SQL statements. It allows you to define default actions based on common SQL conditions like errors, data not found, or warnings, without needing to code an explicit IF SQLCODE = ...
check after every SQL statement.
The general syntax is:
123EXEC SQL WHENEVER condition action END-EXEC.
Common Conditions:
SQLERROR
: Triggered when SQLCODE
is negative (indicating an error).SQLWARNING
: Triggered when SQLCODE
is positive but not +100 (indicating a warning, e.g., string truncation). Or when SQLWARN(0)
in SQLCA is 'W'.NOT FOUND
: Triggered when SQLCODE
is +100 (e.g., a SELECT
finds no rows, or a cursor reaches the end of data during a FETCH
).Common Actions:
CONTINUE
: Ignores the condition, and program execution continues with the next statement after the SQL call. This is often the default if no WHENEVER
is specified or to override a previous WHENEVER
.GO TO paragraph-name
(or GOTO paragraph-name
): Transfers control to the specified COBOL paragraph. This is commonly used to jump to an error-handling routine.STOP
: (Less common in production, more for debugging) Terminates the program. Some database systems might offer other actions like CALL
.WHENEVER
directive applies to all subsequent embedded SQL statements in the source code until another WHENEVER
directive for the same condition is encountered, or until the end of the program.WHENEVER
directives is critical. They are declarative and affect SQL statements that appear after them in the program's flow as processed by the precompiler.WHENEVER
directive. For example, you might have a general WHENEVER SQLERROR GOTO FATAL-ERROR-ROUTINE
, but for a specific SQL statement where an error is recoverable, you might precede it with WHENEVER SQLERROR CONTINUE
and then handle the error locally with an IF SQLCODE
check.123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354IDENTIFICATION DIVISION. PROGRAM-ID. WHENEVER-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 HV-EMP-ID PIC X(6). 01 HV-EMP-NAME PIC X(30). EXEC SQL INCLUDE SQLCA END-EXEC. PROCEDURE DIVISION. MAIN-PARA. * General error handling EXEC SQL WHENEVER SQLERROR GOTO SQL-ERROR-PARA END-EXEC. * Specific handling for NOT FOUND on FETCH EXEC SQL WHENEVER NOT FOUND GOTO END-OF-FETCH-PARA END-EXEC. DISPLAY "Processing employees...". MOVE "123456" TO HV-EMP-ID. EXEC SQL SELECT EMP_NAME INTO :HV-EMP-NAME FROM EMPLOYEES WHERE EMP_ID = :HV-EMP-ID END-EXEC. * If SQLCODE = 0 (found), control continues here. * If SQLCODE = 100 (not found), Jumps to END-OF-FETCH-PARA. * If SQLCODE < 0 (error), Jumps to SQL-ERROR-PARA. DISPLAY "Employee found: " HV-EMP-NAME. PERFORM SOME-OTHER-PROCESSING. GO TO END-PROGRAM-PARA. SQL-ERROR-PARA. DISPLAY "A serious SQL error occurred!". DISPLAY "SQLCODE: " SQLCODE. DISPLAY "SQLERRMC: " SQLERRMC OF SQLCA(1:SQLERRML OF SQLCA). MOVE 8 TO RETURN-CODE. *> Set error return code GOBACK. END-OF-FETCH-PARA. DISPLAY "Employee not found or end of data.". MOVE 0 TO RETURN-CODE. GO TO END-PROGRAM-PARA. SOME-OTHER-PROCESSING. DISPLAY "Performing other tasks...". EXEC SQL WHENEVER SQLERROR CONTINUE END-EXEC. *> Disable GOTO for next SQL EXEC SQL COMMIT END-EXEC. *> Try to commit IF SQLCODE NOT = ZERO DISPLAY "Commit failed, but we continue. SQLCODE: " SQLCODE END-IF. EXEC SQL WHENEVER SQLERROR GOTO SQL-ERROR-PARA END-EXEC. *> Restore general error handling END-PROGRAM-PARA. DISPLAY "End of program.". STOP RUN.
While WHENEVER
can simplify code by reducing repetitive IF SQLCODE
checks, it can also make program flow harder to follow if overused or not managed carefully. Modern practice sometimes favors explicit IF SQLCODE
checks for critical operations to improve clarity and maintainability, especially for complex error recovery logic.
Host variables are the bridge for data exchange between your COBOL program and the SQL database. Indicator variables work alongside host variables, primarily to handle NULL values and detect string truncation.
Host variables are standard COBOL data items defined in the WORKING-STORAGE SECTION
or LINKAGE SECTION
. They are used within embedded SQL statements to:
WHERE
clause), new data (INSERT
, UPDATE
), or parameters for stored procedures.SELECT ... INTO
, FETCH ... INTO
).Syntax:
EXEC SQL
and END-EXEC
), they are prefixed with a colon (:
). Example: :WS-EMPLOYEE-ID
.SELECT ... INTO :GROUP-ITEM
).123456789101112131415161718192021222324252627282930WORKING-STORAGE SECTION. 01 WS-DEPT-NUMBER PIC X(3). 01 WS-DEPT-NAME PIC X(30). 01 WS-MGR-ID PIC X(6). 01 WS-LOCATION PIC X(10). * DCLGEN for a table might look like: *01 DCL EMPLOYEE. * 05 EMPNO PIC X(6). * 05 FIRSTNME PIC X(12). * 05 LASTNAME PIC X(15). * 05 WORKDEPT PIC X(3). * 05 SALARY PIC S9(7)V99 COMP-3. PROCEDURE DIVISION. MOVE "A00" TO WS-DEPT-NUMBER. MOVE "SPIFFY COMPUTER SERVICE DIV." TO WS-DEPT-NAME. MOVE "000010" TO WS-MGR-ID. MOVE "NEW YORK" TO WS-LOCATION. EXEC SQL INSERT INTO DEPARTMENT (DEPTNO, DEPTNAME, MGRNO, LOCATION) VALUES (:WS-DEPT-NUMBER, :WS-DEPT-NAME, :WS-MGR-ID, :WS-LOCATION) END-EXEC. IF SQLCODE = 0 DISPLAY "Department Inserted Successfully." ELSE DISPLAY "Insert failed. SQLCODE: " SQLCODE. END-IF.
Indicator variables are two-byte signed binary integers (PIC S9(4) COMP
or PIC S9(5) COMP
depending on the system, usually S9(4) COMP
is safest for portability if it holds values like -1, 0, positive for length). They are used in conjunction with a host variable to:
-1
(or another negative value like -2
if the NULL is due to a numeric conversion error). The content of the main host variable is undefined in this case.-1
before executing the SQL statement.0
means the associated host variable contains a valid, non-NULL value, and no truncation (of the significant part) occurred.Syntax:
In SQL statements, the indicator variable immediately follows the host variable it's associated with, optionally separated by the keyword INDICATOR
(though often omitted for brevity if the database system allows it).
Example: :WS-MANAGER-ID INDICATOR :WS-MANAGER-ID-NI
or simply :WS-MANAGER-ID :WS-MANAGER-ID-NI
.
12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758WORKING-STORAGE SECTION. 01 WS-EMP-ID PIC X(6) VALUE "000120". 01 WS-EMP-COMM PIC S9(7)V99 COMP-3. 01 WS-EMP-COMM-NI PIC S9(4) COMP. *> Indicator for commission 01 WS-EMP-JOBTITLE PIC X(10). 01 WS-EMP-JOBTITLE-NI PIC S9(4) COMP. *> Indicator for job title length PROCEDURE DIVISION. * Example 1: Retrieving a potentially NULL value EXEC SQL SELECT COMM INTO :WS-EMP-COMM :WS-EMP-COMM-NI FROM EMPLOYEE WHERE EMPNO = :WS-EMP-ID END-EXEC. IF SQLCODE = 0 IF WS-EMP-COMM-NI = -1 DISPLAY "Commission is NULL." ELSE DISPLAY "Commission: " WS-EMP-COMM END-IF ELSE DISPLAY "Error fetching commission. SQLCODE: " SQLCODE END-IF. * Example 2: Inserting a NULL value MOVE "000130" TO WS-EMP-ID. MOVE -1 TO WS-EMP-COMM-NI. *> Indicate we want to insert NULL for commission EXEC SQL UPDATE EMPLOYEE SET COMM = :WS-EMP-COMM :WS-EMP-COMM-NI WHERE EMPNO = :WS-EMP-ID END-EXEC. IF SQLCODE = 0 DISPLAY "Update successful, commission potentially set to NULL." ELSE DISPLAY "Update failed. SQLCODE: " SQLCODE END-IF. * Example 3: Checking for string truncation (hypothetical) * Assume EMPLOYEE.JOBTITLE column is VARCHAR(20) EXEC SQL SELECT JOBTITLE INTO :WS-EMP-JOBTITLE :WS-EMP-JOBTITLE-NI FROM EMPLOYEE WHERE EMPNO = '000140' *> Assuming this employee has a job title > 10 chars END-EXEC. IF SQLCODE = 0 DISPLAY "Retrieved Job Title: " WS-EMP-JOBTITLE. IF WS-EMP-JOBTITLE-NI > 0 AND WS-EMP-JOBTITLE-NI > LENGTH OF WS-EMP-JOBTITLE DISPLAY "Warning: Job title was truncated. Original length: " WS-EMP-JOBTITLE-NI END-IF. END-IF.
It is good practice to always use indicator variables with host variables that map to nullable columns or where string truncation is possible.
While static SQL (where the SQL statement is fully known at precompile time) is common and efficient, dynamic SQL provides the flexibility to construct and execute SQL statements at runtime. This is useful when parts of the SQL query (like table names, column names, or complex WHERE conditions) are not known until the program is running.
Dynamic SQL is more complex than static SQL and generally has higher overhead. There are several forms, ranging from simple to very complex.
EXECUTE IMMEDIATE
This is the simplest form of dynamic SQL. It's used for SQL statements that do not produce a result set (e.g., INSERT
, UPDATE
, DELETE
, DDL statements) and do not contain parameter markers (placeholders for host variables).
123456789101112131415161718192021IDENTIFICATION DIVISION. PROGRAM-ID. EXEC-IMMEDIATE-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 SQL-STATEMENT-STRING PIC X(200). EXEC SQL INCLUDE SQLCA END-EXEC. PROCEDURE DIVISION. MOVE "DELETE FROM USERADM.TEMP_TABLE WHERE STATUS = 'OLD'" TO SQL-STATEMENT-STRING. EXEC SQL EXECUTE IMMEDIATE :SQL-STATEMENT-STRING END-EXEC. IF SQLCODE = 0 DISPLAY "EXECUTE IMMEDIATE successful." DISPLAY SQLERRD(3) OF SQLCA " rows affected." ELSE DISPLAY "EXECUTE IMMEDIATE failed. SQLCODE: " SQLCODE. END-IF. STOP RUN.
PREPARE
and EXECUTE
(Fixed List SELECT)This form is used when the SQL statement contains parameter markers (?
) for input host variables, or when you want to execute the same statement multiple times with different values. It's common for SELECT
statements where the number and types of selected columns are known at precompile time (fixed list SELECT).
PREPARE statement-name FROM :string-variable
: The SQL precompiler parses the SQL string and gives it a name.DECLARE cursor-name CURSOR FOR statement-name
: If it's a SELECT, a cursor is declared for the prepared statement.OPEN cursor-name USING :host-var1, :host-var2 ...
: Opens the cursor, substituting values for parameter markers.FETCH cursor-name INTO :host-varA, :host-varB ...
: Retrieves rows.EXECUTE statement-name USING :host-var1 ...
: For non-SELECT statements (INSERT, UPDATE, DELETE) with parameter markers.12345678910111213141516171819202122232425262728293031323334353637383940WORKING-STORAGE SECTION. 01 SQL-QUERY-STRING PIC X(200). 01 STMT-NAME PIC X(30) VALUE 'MYDYNAMICSQL'. 01 HV-DEPT-NO PIC X(3). 01 HV-EMP-NAME PIC X(30). 01 HV-EMP-SALARY PIC S9(7)V99 COMP-3. EXEC SQL INCLUDE SQLCA END-EXEC. PROCEDURE DIVISION. MOVE "SELECT EMPNAME, SALARY FROM EMPLOYEES WHERE WORKDEPT = ?" TO SQL-QUERY-STRING. EXEC SQL PREPARE :STMT-NAME FROM :SQL-QUERY-STRING END-EXEC. IF SQLCODE NOT = 0 DISPLAY "PREPARE failed: " SQLCODE STOP RUN END-IF. EXEC SQL DECLARE EMPCURSOR CURSOR FOR :STMT-NAME END-EXEC. MOVE "A01" TO HV-DEPT-NO. EXEC SQL OPEN EMPCURSOR USING :HV-DEPT-NO END-EXEC. IF SQLCODE NOT = 0 DISPLAY "OPEN CURSOR failed: " SQLCODE STOP RUN END-IF. PERFORM UNTIL SQLCODE NOT = 0 EXEC SQL FETCH EMPCURSOR INTO :HV-EMP-NAME, :HV-EMP-SALARY END-EXEC IF SQLCODE = 0 DISPLAY "Name: " HV-EMP-NAME " Salary: " HV-EMP-SALARY ELSE IF SQLCODE = 100 DISPLAY "End of data for department " HV-DEPT-NO ELSE DISPLAY "FETCH error: " SQLCODE END-IF END-PERFORM. EXEC SQL CLOSE EMPCURSOR END-EXEC. STOP RUN.
This is the most complex form. It's used when the number or data types of the columns in a SELECT
statement are not known until runtime. It requires using the SQL Descriptor Area (SQLDA).
EXEC SQL INCLUDE SQLDA END-EXEC.
PREPARE statement-name FROM :string-variable
DESCRIBE statement-name INTO :SQLDA-instance
: After preparing, DESCRIBE
populates the SQLDA with information about the result set columns (number of columns, data types, lengths, names).DECLARE
, OPEN
, FETCH ... USING DESCRIPTOR :SQLDA-instance
, CLOSE
.This is significantly more advanced and involves manipulating pointers and storage. It's less common in typical application programming but essential for generic query tools or highly flexible reporting systems.
123456789101112131415161718192021222324252627282930313233343536373839404142* Conceptual structure - actual implementation is complex WORKING-STORAGE SECTION. 01 SQL-SELECT-STR PIC X(256). 01 PREPARED-STMT-NAME PIC X(8) VALUE 'S1'. EXEC SQL INCLUDE SQLCA END-EXEC. EXEC SQL INCLUDE SQLDA END-EXEC. * SQLDA typically has a header and an array of SQLVAR structures. * 01 SQLDA. * 05 SQLDAID PIC X(8). * 05 SQLDABC PIC S9(9) COMP-5. * 05 SQLN PIC S9(4) COMP-5. *> Max SQLVAR entries * 05 SQLD PIC S9(4) COMP-5. *> Actual SQLVAR entries * 05 SQLVAR OCCURS 1 TO N TIMES DEPENDING ON SQLN. * 10 SQLTYPE PIC S9(4) COMP-5. * 10 SQLLEN PIC S9(4) COMP-5. * 10 SQLDATA POINTER. * 10 SQLIND POINTER. * 10 SQLNAME PIC X(30). PROCEDURE DIVISION. MOVE "SELECT LASTNAME, SALARY, HIREDATE FROM EMPLOYEES WHERE EMPNO = ?" TO SQL-SELECT-STR. EXEC SQL PREPARE :PREPARED-STMT-NAME FROM :SQL-SELECT-STR END-EXEC. * Check SQLCODE for PREPARE success EXEC SQL DESCRIBE :PREPARED-STMT-NAME INTO :SQLDA END-EXEC. * Check SQLCODE for DESCRIBE success * Now SQLDA.SQLD contains the number of columns in the result. * SQLDA.SQLVAR(i).SQLTYPE, SQLLEN, SQLNAME describe each column. * Program would then need to allocate memory for SQLDATA and SQLIND for each SQLVAR * and set the pointers in the SQLDA before OPEN/FETCH. * EXEC SQL DECLARE C1 CURSOR FOR :PREPARED-STMT-NAME END-EXEC. * EXEC SQL OPEN C1 USING ...:param-host-var ... END-EXEC. * EXEC SQL FETCH C1 USING DESCRIPTOR :SQLDA END-EXEC. * ... process data from allocated memory via SQLDATA pointers ... * EXEC SQL CLOSE C1 END-EXEC. DISPLAY "Varying list SELECT structure outlined (implementation detail omitted).". STOP RUN.
1. What is the primary purpose of EXEC SQL and END-EXEC delimiters in COBOL?
2. What does the SQL INCLUDE directive typically bring into a COBOL program?
3. What is the role of the WHENEVER directive in COBOL SQL programming?
4. In COBOL, variables used to pass data to or receive data from SQL statements are called:
5. Which technique allows SQL statements to be constructed and executed at runtime in a COBOL program?
Understanding tables, columns, primary keys, foreign keys, and basic SQL operations.