Progress0 of 0 lessons

COBOL System Integration

System integration is a critical aspect of mainframe COBOL development, enabling COBOL programs to interact with various enterprise systems and services. Modern mainframe applications rarely operate in isolation—they integrate with transaction processing systems like CICS, databases like DB2 and IMS, batch processing environments, web services, and other enterprise components. This guide covers the fundamental concepts, techniques, and best practices for integrating COBOL programs with mainframe systems.

What is COBOL System Integration?

COBOL system integration refers to the process of connecting COBOL applications with other mainframe systems, databases, and services to create comprehensive enterprise solutions. Integration enables COBOL programs to:

Integration with CICS (Customer Information Control System)

CICS is IBM's transaction processing system that enables COBOL programs to handle online, interactive transactions. CICS provides services for terminal I/O, file access, transaction management, and program communication.

Key Characteristics of CICS Programs

Basic CICS Command Structure

CICS commands are embedded in COBOL programs using the EXEC CICS format:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
IDENTIFICATION DIVISION. PROGRAM-ID. CICS-PROGRAM. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-MESSAGE PIC X(80). 01 WS-RESPONSE PIC S9(8) COMP. 01 WS-RESPONSE2 PIC S9(8) COMP. PROCEDURE DIVISION. *> Send a message to the terminal EXEC CICS SEND FROM(WS-MESSAGE) LENGTH(LENGTH OF WS-MESSAGE) END-EXEC. *> Receive data from the terminal EXEC CICS RECEIVE INTO(WS-MESSAGE) LENGTH(LENGTH OF WS-MESSAGE) END-EXEC. *> Read a record from a file EXEC CICS READ FILE('CUSTOMER') INTO(WS-MESSAGE) RIDFLD(WS-CUSTOMER-KEY) RESP(WS-RESPONSE) RESP2(WS-RESPONSE2) END-EXEC. *> Check if the read was successful IF WS-RESPONSE NOT = DFHRESP(NORMAL) EXEC CICS SEND FROM('ERROR: RECORD NOT FOUND') END-EXEC END-IF. *> Return control to CICS EXEC CICS RETURN END-EXEC. *> WS-MESSAGE: Contains the data to send or receive *> WS-RESPONSE: Contains the CICS response code *> DFHRESP(NORMAL): Indicates successful operation

Common CICS Commands

CICS Program Restrictions

When writing COBOL programs for CICS, you cannot use:

Integration with DB2 Database

DB2 is IBM's relational database management system. COBOL programs can access DB2 databases using embedded SQL statements, allowing direct database operations from within COBOL code.

Embedded SQL in COBOL

SQL statements are embedded in COBOL programs using the EXEC SQL format:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
IDENTIFICATION DIVISION. PROGRAM-ID. DB2-PROGRAM. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. *> SQL communication area - required for DB2 programs EXEC SQL INCLUDE SQLCA END-EXEC. *> Host variables for database operations 01 WS-CUSTOMER-ID PIC 9(5). 01 WS-CUSTOMER-NAME PIC X(30). 01 WS-CUSTOMER-ADDRESS PIC X(50). 01 WS-SALARY PIC S9(7)V99 COMP-3. *> SQLCODE and SQLSTATE for error checking 01 WS-SQLCODE PIC S9(9) COMP. 01 WS-SQLSTATE PIC X(5). PROCEDURE DIVISION. *> Declare a cursor for SELECT operations EXEC SQL DECLARE CUST_CURSOR CURSOR FOR SELECT CUSTOMER_ID, CUSTOMER_NAME, ADDRESS, SALARY FROM CUSTOMER_TABLE WHERE SALARY > :WS-SALARY END-EXEC. *> Open the cursor EXEC SQL OPEN CUST_CURSOR END-EXEC. *> Check for errors MOVE SQLCODE TO WS-SQLCODE IF WS-SQLCODE NOT = 0 DISPLAY 'ERROR OPENING CURSOR: ' WS-SQLCODE STOP RUN END-IF. *> Fetch rows from the cursor PERFORM UNTIL SQLCODE = 100 EXEC SQL FETCH CUST_CURSOR INTO :WS-CUSTOMER-ID, :WS-CUSTOMER-NAME, :WS-CUSTOMER-ADDRESS, :WS-SALARY END-EXEC IF SQLCODE = 0 DISPLAY 'CUSTOMER: ' WS-CUSTOMER-ID ' ' WS-CUSTOMER-NAME ELSE IF SQLCODE = 100 DISPLAY 'END OF DATA' ELSE DISPLAY 'FETCH ERROR: ' SQLCODE END-IF END-PERFORM. *> Close the cursor EXEC SQL CLOSE CUST_CURSOR END-EXEC. *> Insert a new record EXEC SQL INSERT INTO CUSTOMER_TABLE (CUSTOMER_ID, CUSTOMER_NAME, ADDRESS, SALARY) VALUES (:WS-CUSTOMER-ID, :WS-CUSTOMER-NAME, :WS-CUSTOMER-ADDRESS, :WS-SALARY) END-EXEC. *> Update a record EXEC SQL UPDATE CUSTOMER_TABLE SET SALARY = :WS-SALARY WHERE CUSTOMER_ID = :WS-CUSTOMER-ID END-EXEC. *> Delete a record EXEC SQL DELETE FROM CUSTOMER_TABLE WHERE CUSTOMER_ID = :WS-CUSTOMER-ID END-EXEC. *> Commit the transaction EXEC SQL COMMIT END-EXEC. *> :WS-CUSTOMER-ID: Host variable (prefixed with colon) *> SQLCA: SQL Communication Area for error handling *> SQLCODE: Contains return code (0 = success, 100 = no data, negative = error)

DB2 Host Variables

Host variables are COBOL data items used to pass data between COBOL and DB2:

DB2 Error Handling

Always check SQLCODE after SQL operations:

Integration with IMS (Information Management System)

IMS is IBM's hierarchical database and transaction management system. COBOL programs integrate with IMS using DL/I (Data Language/I) calls.

DL/I Call Structure

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
IDENTIFICATION DIVISION. PROGRAM-ID. IMS-PROGRAM. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. *> I/O PCB (Program Communication Block) 01 IO-PCB. 05 IO-PCB-TYPE PIC X(1). 05 IO-PCB-STATUS PIC X(2). 05 IO-PCB-DATE PIC X(8). 05 IO-PCB-TIME PIC X(8). 05 IO-PCB-SEQUENCE PIC X(4). *> Segment search arguments 01 SSA-CUSTOMER. 05 SSA-SEGMENT-NAME PIC X(8) VALUE 'CUSTOMER'. 05 SSA-BLANK PIC X(1) VALUE ' '. 05 SSA-OPERATOR PIC X(2) VALUE '= '. 05 SSA-CUSTOMER-ID PIC 9(5). *> Segment I/O area 01 CUSTOMER-SEGMENT. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(50). PROCEDURE DIVISION USING IO-PCB. *> Get unique (GU) - retrieve a specific segment CALL 'CBLTDLI' USING DLI-GU IO-PCB CUSTOMER-SEGMENT SSA-CUSTOMER. *> Check status IF IO-PCB-STATUS = ' ' DISPLAY 'CUSTOMER FOUND: ' CUSTOMER-NAME ELSE IF IO-PCB-STATUS = 'GE' DISPLAY 'CUSTOMER NOT FOUND' ELSE DISPLAY 'ERROR: ' IO-PCB-STATUS END-IF. *> Get next (GN) - retrieve next segment in sequence CALL 'CBLTDLI' USING DLI-GN IO-PCB CUSTOMER-SEGMENT SSA-CUSTOMER. *> Insert (ISRT) - add a new segment CALL 'CBLTDLI' USING DLI-ISRT IO-PCB CUSTOMER-SEGMENT SSA-CUSTOMER. *> Replace (REPL) - update an existing segment CALL 'CBLTDLI' USING DLI-REPL IO-PCB CUSTOMER-SEGMENT SSA-CUSTOMER. *> Delete (DLET) - remove a segment CALL 'CBLTDLI' USING DLI-DLET IO-PCB CUSTOMER-SEGMENT SSA-CUSTOMER. *> DLI-GU: Get Unique - retrieves a specific segment *> DLI-GN: Get Next - retrieves next segment in sequence *> DLI-ISRT: Insert - adds a new segment *> DLI-REPL: Replace - updates an existing segment *> DLI-DLET: Delete - removes a segment *> IO-PCB-STATUS: ' ' = success, 'GE' = not found, other = error

Common DL/I Call Types

Batch Processing Integration

Batch COBOL programs run as background jobs, typically scheduled to process large volumes of data. Batch programs use standard COBOL file I/O operations and can integrate with databases, call other programs, and participate in multi-step job workflows.

Batch Program Characteristics

Batch Program Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
IDENTIFICATION DIVISION. PROGRAM-ID. BATCH-PROGRAM. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT INPUT-FILE ASSIGN TO UT-S-INFILE. SELECT OUTPUT-FILE ASSIGN TO UT-S-OUTFILE. DATA DIVISION. FILE SECTION. FD INPUT-FILE RECORD CONTAINS 80 CHARACTERS. 01 INPUT-RECORD PIC X(80). FD OUTPUT-FILE RECORD CONTAINS 80 CHARACTERS. 01 OUTPUT-RECORD PIC X(80). WORKING-STORAGE SECTION. 01 WS-EOF-FLAG PIC X(1) VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. 01 WS-RECORD-COUNT PIC 9(6) VALUE ZERO. PROCEDURE DIVISION. MAIN-PROCESSING. OPEN INPUT INPUT-FILE OUTPUT OUTPUT-FILE PERFORM UNTIL END-OF-FILE READ INPUT-FILE AT END SET END-OF-FILE TO TRUE NOT AT END ADD 1 TO WS-RECORD-COUNT MOVE INPUT-RECORD TO OUTPUT-RECORD WRITE OUTPUT-RECORD END-READ END-PERFORM DISPLAY 'RECORDS PROCESSED: ' WS-RECORD-COUNT CLOSE INPUT-FILE OUTPUT-FILE STOP RUN. *> This batch program: *> 1. Opens input and output files *> 2. Reads records sequentially *> 3. Processes each record *> 4. Writes to output file *> 5. Closes files and terminates

Program-to-Program Communication

COBOL programs can call other programs (subroutines) using the CALL statement, enabling modular design and code reuse.

Calling Subroutines

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
IDENTIFICATION DIVISION. PROGRAM-ID. MAIN-PROGRAM. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-CUSTOMER-ID PIC 9(5) VALUE 12345. 01 WS-CUSTOMER-NAME PIC X(30). 01 WS-RETURN-CODE PIC 9(2). PROCEDURE DIVISION. MAIN-LOGIC. DISPLAY 'CALLING SUBROUTINE...' CALL 'SUBROUTINE-PROG' USING WS-CUSTOMER-ID WS-CUSTOMER-NAME WS-RETURN-CODE IF WS-RETURN-CODE = 0 DISPLAY 'SUCCESS: ' WS-CUSTOMER-NAME ELSE DISPLAY 'ERROR: RETURN CODE ' WS-RETURN-CODE END-IF STOP RUN. *> ============================================ *> Subroutine Program *> ============================================ IDENTIFICATION DIVISION. PROGRAM-ID. SUBROUTINE-PROG. DATA DIVISION. LINKAGE SECTION. 01 LK-CUSTOMER-ID PIC 9(5). 01 LK-CUSTOMER-NAME PIC X(30). 01 LK-RETURN-CODE PIC 9(2). PROCEDURE DIVISION USING LK-CUSTOMER-ID LK-CUSTOMER-NAME LK-RETURN-CODE. SUBROUTINE-LOGIC. *> Process the customer ID IF LK-CUSTOMER-ID > 0 MOVE 'CUSTOMER FOUND' TO LK-CUSTOMER-NAME MOVE 0 TO LK-RETURN-CODE ELSE MOVE 'INVALID ID' TO LK-CUSTOMER-NAME MOVE 1 TO LK-RETURN-CODE END-IF EXIT PROGRAM. *> CALL statement: Invokes another program *> USING clause: Passes parameters *> LINKAGE SECTION: Receives parameters in called program *> EXIT PROGRAM: Returns control to calling program

Web Services and Modern Integration

Modern COBOL programs can integrate with web services, REST APIs, and JSON/XML data formats, enabling connectivity with cloud-based and distributed systems.

JSON Processing in COBOL

Enterprise COBOL provides JSON parsing capabilities:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
IDENTIFICATION DIVISION. PROGRAM-ID. JSON-PROGRAM. DATA DIVISION. WORKING-STORAGE SECTION. *> JSON data structure 01 WS-JSON-STRING PIC X(200) VALUE '{"customerId":12345,"name":"John Doe","active":true}'. *> JSON parser result 01 WS-JSON-PARSED PIC X(200). PROCEDURE DIVISION. MAIN-LOGIC. *> Parse JSON string *> (Enterprise COBOL JSON functions would be used here) DISPLAY 'JSON INTEGRATION EXAMPLE' DISPLAY 'Original: ' WS-JSON-STRING STOP RUN. *> Modern COBOL can: *> - Parse JSON data *> - Generate JSON responses *> - Call REST APIs via HTTP *> - Process XML documents *> - Integrate with web services

Best Practices for System Integration

Error Handling

Always implement comprehensive error handling:

Performance Optimization

Security Considerations

Code Maintainability

Summary

COBOL system integration enables COBOL programs to participate in comprehensive enterprise solutions by connecting with:

Understanding these integration techniques is essential for developing robust, enterprise-grade COBOL applications that work seamlessly within the mainframe ecosystem and connect with modern distributed systems.

Test Your Knowledge

1. What is the primary purpose of COBOL system integration?

  • To make COBOL programs run faster
  • To enable COBOL programs to interact with other mainframe systems and services
  • To convert COBOL to other programming languages
  • To simplify COBOL syntax

2. What command format is used to execute CICS commands in COBOL?

  • CALL CICS command-name
  • EXEC CICS command-name END-EXEC
  • INVOKE CICS command-name
  • PERFORM CICS command-name

3. What is the purpose of the EXEC SQL statement in COBOL?

  • To execute system commands
  • To embed SQL statements for database access (DB2)
  • To perform string operations
  • To handle file I/O

4. What is a key difference between batch COBOL programs and CICS COBOL programs?

  • Batch programs are faster
  • CICS programs use EXEC CICS commands instead of standard COBOL file I/O statements
  • Batch programs cannot access databases
  • There is no difference

5. What is the purpose of the CALL statement in COBOL system integration?

  • To call external subroutines and programs
  • To make phone calls
  • To display messages
  • To read files

6. What is a transaction in CICS?

  • A database record
  • A unit of work that represents a complete business operation
  • A COBOL program
  • A file operation

Related Pages