In this section, we will explore how to perform various database operations using COBOL, particularly when working with DB2. This includes connecting to the database, executing SQL queries, and handling the results. By the end of this section, you should be able to perform basic CRUD (Create, Read, Update, Delete) operations in a COBOL program.
Key Concepts
- Connecting to the Database: Establishing a connection to the DB2 database.
- Executing SQL Statements: Running SQL commands from within a COBOL program.
- Handling Results: Processing the results returned by SQL queries.
- Error Handling: Managing errors that occur during database operations.
Connecting to the Database
To interact with a DB2 database, you need to establish a connection. This is typically done using the EXEC SQL statement in COBOL.
Example
IDENTIFICATION DIVISION.
PROGRAM-ID. DB-CONNECT.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 SQLCODE PIC S9(9) COMP-5.
01 SQLSTATE PIC X(5).
PROCEDURE DIVISION.
EXEC SQL
CONNECT TO 'DATABASE_NAME'
USER 'username'
USING 'password'
END-EXEC.
IF SQLCODE = 0
DISPLAY 'Connection successful.'
ELSE
DISPLAY 'Connection failed. SQLCODE: ' SQLCODE
' SQLSTATE: ' SQLSTATE
END-IF.
STOP RUN.Explanation
- IDENTIFICATION DIVISION: Defines the program's identity.
- WORKING-STORAGE SECTION: Declares variables to store SQL return codes.
- EXEC SQL CONNECT: Establishes a connection to the database using the provided credentials.
- SQLCODE: A variable that stores the return code of the SQL operation. A value of 0 indicates success.
- SQLSTATE: A variable that stores the SQL state code.
Executing SQL Statements
Once connected, you can execute SQL statements to interact with the database. This includes SELECT, INSERT, UPDATE, and DELETE operations.
Example: SELECT Statement
IDENTIFICATION DIVISION.
PROGRAM-ID. DB-SELECT.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 SQLCODE PIC S9(9) COMP-5.
01 SQLSTATE PIC X(5).
01 EMP-ID PIC 9(5).
01 EMP-NAME PIC X(20).
PROCEDURE DIVISION.
EXEC SQL
CONNECT TO 'DATABASE_NAME'
USER 'username'
USING 'password'
END-EXEC.
IF SQLCODE = 0
DISPLAY 'Connection successful.'
ELSE
DISPLAY 'Connection failed. SQLCODE: ' SQLCODE
' SQLSTATE: ' SQLSTATE
STOP RUN
END-IF.
EXEC SQL
SELECT EMP_ID, EMP_NAME
INTO :EMP-ID, :EMP-NAME
FROM EMPLOYEE
WHERE EMP_ID = 1001
END-EXEC.
IF SQLCODE = 0
DISPLAY 'Employee ID: ' EMP-ID
' Employee Name: ' EMP-NAME
ELSE
DISPLAY 'SELECT failed. SQLCODE: ' SQLCODE
' SQLSTATE: ' SQLSTATE
END-IF.
EXEC SQL
DISCONNECT CURRENT
END-EXEC.
STOP RUN.Explanation
- SELECT Statement: Retrieves data from the
EMPLOYEEtable whereEMP_IDis 1001. - INTO Clause: Maps the retrieved columns to COBOL variables
EMP-IDandEMP-NAME. - DISCONNECT Statement: Closes the database connection.
Handling Results
When executing SQL queries, it's important to handle the results appropriately. This includes checking the SQLCODE and processing the retrieved data.
Example: INSERT Statement
IDENTIFICATION DIVISION.
PROGRAM-ID. DB-INSERT.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 SQLCODE PIC S9(9) COMP-5.
01 SQLSTATE PIC X(5).
01 EMP-ID PIC 9(5) VALUE 1002.
01 EMP-NAME PIC X(20) VALUE 'John Doe'.
PROCEDURE DIVISION.
EXEC SQL
CONNECT TO 'DATABASE_NAME'
USER 'username'
USING 'password'
END-EXEC.
IF SQLCODE = 0
DISPLAY 'Connection successful.'
ELSE
DISPLAY 'Connection failed. SQLCODE: ' SQLCODE
' SQLSTATE: ' SQLSTATE
STOP RUN
END-IF.
EXEC SQL
INSERT INTO EMPLOYEE (EMP_ID, EMP_NAME)
VALUES (:EMP-ID, :EMP-NAME)
END-EXEC.
IF SQLCODE = 0
DISPLAY 'Insert successful.'
ELSE
DISPLAY 'Insert failed. SQLCODE: ' SQLCODE
' SQLSTATE: ' SQLSTATE
END-IF.
EXEC SQL
DISCONNECT CURRENT
END-EXEC.
STOP RUN.Explanation
- INSERT Statement: Adds a new record to the
EMPLOYEEtable withEMP_ID1002 andEMP_NAME'John Doe'. - VALUES Clause: Specifies the values to be inserted, mapped from COBOL variables.
Error Handling
Proper error handling is crucial for robust database operations. Always check the SQLCODE and SQLSTATE after executing SQL statements.
Common SQLCODE Values
| SQLCODE | Description |
|---|---|
| 0 | Operation successful |
| +100 | No more rows found (SELECT) |
| -911 | Deadlock or timeout |
| -803 | Duplicate key error (INSERT) |
Practical Exercise
Task
Write a COBOL program to update an employee's name in the EMPLOYEE table based on their EMP_ID.
Solution
IDENTIFICATION DIVISION.
PROGRAM-ID. DB-UPDATE.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 SQLCODE PIC S9(9) COMP-5.
01 SQLSTATE PIC X(5).
01 EMP-ID PIC 9(5) VALUE 1002.
01 NEW-EMP-NAME PIC X(20) VALUE 'Jane Smith'.
PROCEDURE DIVISION.
EXEC SQL
CONNECT TO 'DATABASE_NAME'
USER 'username'
USING 'password'
END-EXEC.
IF SQLCODE = 0
DISPLAY 'Connection successful.'
ELSE
DISPLAY 'Connection failed. SQLCODE: ' SQLCODE
' SQLSTATE: ' SQLSTATE
STOP RUN
END-IF.
EXEC SQL
UPDATE EMPLOYEE
SET EMP_NAME = :NEW-EMP-NAME
WHERE EMP_ID = :EMP-ID
END-EXEC.
IF SQLCODE = 0
DISPLAY 'Update successful.'
ELSE
DISPLAY 'Update failed. SQLCODE: ' SQLCODE
' SQLSTATE: ' SQLSTATE
END-IF.
EXEC SQL
DISCONNECT CURRENT
END-EXEC.
STOP RUN.Explanation
- UPDATE Statement: Modifies the
EMP_NAMEof the employee withEMP_ID1002 to 'Jane Smith'. - SET Clause: Specifies the new value for
EMP_NAME.
Conclusion
In this section, we covered the basics of performing database operations in COBOL, including connecting to a DB2 database, executing SQL statements, handling results, and managing errors. These skills are essential for interacting with databases in real-world COBOL applications. In the next section, we will delve into handling cursors for more complex data retrieval scenarios.
