MainframeMaster

COBOL Tutorial

Progress0 of 0 lessons

COBOL TERMINATE Statement - Quick Reference

The TERMINATE statement in COBOL is used to end report processing and finalize report generation. It completes the report processing cycle by generating final output, processing any remaining report data, and ensuring proper report formatting.

Primary Use

End report processing and finalize report generation

Division

PROCEDURE DIVISION

Type

Report processing statement

Status

Required for report completion

Overview

The TERMINATE statement is a crucial part of COBOL report processing. It is used to finalize report generation after all data has been processed. When TERMINATE is executed, it processes any remaining report data, generates final summaries, formats the complete report, and ensures all report sections are properly closed. This statement is essential for completing the report processing cycle and producing the final report output.

Syntax

cobol
1
2
3
4
5
6
7
8
9
10
11
12
TERMINATE report-name. * Examples: TERMINATE SALES-REPORT. TERMINATE INVENTORY-REPORT. TERMINATE CUSTOMER-REPORT. * In a complete report processing sequence: INITIATE report-name * ... process data and generate report lines ... TERMINATE report-name CLOSE report-file.

Practical Examples

Basic TERMINATE Usage

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
* Basic TERMINATE example IDENTIFICATION DIVISION. PROGRAM-ID. BASIC-TERMINATE-EXAMPLE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT SALES-FILE ASSIGN TO "SALES.DAT" ORGANIZATION IS SEQUENTIAL. SELECT SALES-REPORT ASSIGN TO "SALES.RPT" ORGANIZATION IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD SALES-FILE. 01 SALES-RECORD. 05 SALE-DATE PIC 9(8). 05 SALE-AMOUNT PIC 9(7)V99. 05 SALE-PRODUCT PIC X(20). SD SALES-REPORT. 01 REPORT-LINE PIC X(80). WORKING-STORAGE SECTION. 01 WS-EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. PROCEDURE DIVISION. MAIN-LOGIC. * Initialize report INITIATE SALES-REPORT * Open input file OPEN INPUT SALES-FILE * Process sales records PERFORM UNTIL END-OF-FILE READ SALES-FILE AT END SET END-OF-FILE TO TRUE NOT AT END PERFORM PROCESS-SALES-RECORD END-READ END-PERFORM * Terminate report processing TERMINATE SALES-REPORT * Close files CLOSE SALES-FILE DISPLAY "Report processing completed" STOP RUN. PROCESS-SALES-RECORD. * Process individual sales record * Generate report lines as needed DISPLAY "Processing sale: " SALE-AMOUNT.

Explanation: This example demonstrates basic usage of the TERMINATE statement. The program initializes a sales report, processes sales records from an input file, and then terminates the report processing after all records have been processed. The TERMINATE statement finalizes the report generation, ensuring that all report data is properly formatted and output. This is the standard pattern for report processing in COBOL.

Multiple Report TERMINATE

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
* Multiple report TERMINATE example IDENTIFICATION DIVISION. PROGRAM-ID. MULTIPLE-REPORT-EXAMPLE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT INVENTORY-FILE ASSIGN TO "INVENTORY.DAT" ORGANIZATION IS SEQUENTIAL. SELECT SUMMARY-REPORT ASSIGN TO "SUMMARY.RPT" ORGANIZATION IS SEQUENTIAL. SELECT DETAIL-REPORT ASSIGN TO "DETAIL.RPT" ORGANIZATION IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD INVENTORY-FILE. 01 INVENTORY-RECORD. 05 ITEM-ID PIC 9(5). 05 ITEM-NAME PIC X(30). 05 ITEM-QUANTITY PIC 9(4). 05 ITEM-PRICE PIC 9(5)V99. SD SUMMARY-REPORT. 01 SUMMARY-LINE PIC X(80). SD DETAIL-REPORT. 01 DETAIL-LINE PIC X(80). WORKING-STORAGE SECTION. 01 WS-EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. 01 WS-TOTAL-VALUE PIC 9(9)V99 VALUE 0. PROCEDURE DIVISION. MAIN-LOGIC. * Initialize both reports INITIATE SUMMARY-REPORT INITIATE DETAIL-REPORT * Open input file OPEN INPUT INVENTORY-FILE * Process inventory records PERFORM UNTIL END-OF-FILE READ INVENTORY-FILE AT END SET END-OF-FILE TO TRUE NOT AT END PERFORM PROCESS-INVENTORY-RECORD END-READ END-PERFORM * Terminate both reports TERMINATE SUMMARY-REPORT TERMINATE DETAIL-REPORT * Close input file CLOSE INVENTORY-FILE DISPLAY "Both reports completed" DISPLAY "Total inventory value: " WS-TOTAL-VALUE STOP RUN. PROCESS-INVENTORY-RECORD. * Process individual inventory record * Generate detail report line * Update summary totals COMPUTE WS-TOTAL-VALUE = WS-TOTAL-VALUE + (ITEM-QUANTITY * ITEM-PRICE) DISPLAY "Processing item: " ITEM-NAME.

Explanation: This example shows how to use TERMINATE with multiple reports. The program generates both a summary report and a detail report from the same inventory data. After processing all records, both reports are terminated using separate TERMINATE statements. This ensures that each report is properly finalized and all report data is correctly formatted and output. The TERMINATE statements are executed after all data processing is complete.

Report with Final Summary

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
83
84
85
86
* Report with final summary TERMINATE example IDENTIFICATION DIVISION. PROGRAM-ID. SUMMARY-REPORT-EXAMPLE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT" ORGANIZATION IS SEQUENTIAL. SELECT CUSTOMER-REPORT ASSIGN TO "CUSTOMER.RPT" ORGANIZATION IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE. 01 CUSTOMER-RECORD. 05 CUST-ID PIC 9(5). 05 CUST-NAME PIC X(30). 05 CUST-BALANCE PIC 9(7)V99. 05 CUST-STATUS PIC X(1). SD CUSTOMER-REPORT. 01 REPORT-LINE PIC X(80). WORKING-STORAGE SECTION. 01 WS-EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. 01 WS-REPORT-STATS. 05 WS-TOTAL-CUSTOMERS PIC 9(4) VALUE 0. 05 WS-TOTAL-BALANCE PIC 9(9)V99 VALUE 0. 05 WS-ACTIVE-CUSTOMERS PIC 9(4) VALUE 0. PROCEDURE DIVISION. MAIN-LOGIC. * Initialize report INITIATE CUSTOMER-REPORT * Open input file OPEN INPUT CUSTOMER-FILE * Process customer records PERFORM UNTIL END-OF-FILE READ CUSTOMER-FILE AT END SET END-OF-FILE TO TRUE NOT AT END PERFORM PROCESS-CUSTOMER-RECORD END-READ END-PERFORM * Generate final summary before terminating PERFORM GENERATE-FINAL-SUMMARY * Terminate report processing TERMINATE CUSTOMER-REPORT * Close input file CLOSE CUSTOMER-FILE DISPLAY "Customer report completed" STOP RUN. PROCESS-CUSTOMER-RECORD. * Process individual customer record ADD 1 TO WS-TOTAL-CUSTOMERS ADD CUST-BALANCE TO WS-TOTAL-BALANCE IF CUST-STATUS = 'A' ADD 1 TO WS-ACTIVE-CUSTOMERS END-IF * Generate report line for customer DISPLAY "Processing customer: " CUST-NAME. GENERATE-FINAL-SUMMARY. * Generate final summary statistics DISPLAY "=== FINAL SUMMARY ===" DISPLAY "Total customers: " WS-TOTAL-CUSTOMERS DISPLAY "Active customers: " WS-ACTIVE-CUSTOMERS DISPLAY "Total balance: " WS-TOTAL-BALANCE * Calculate average balance IF WS-TOTAL-CUSTOMERS > 0 COMPUTE WS-AVG-BALANCE = WS-TOTAL-BALANCE / WS-TOTAL-CUSTOMERS DISPLAY "Average balance: " WS-AVG-BALANCE END-IF.

Explanation: This example demonstrates using TERMINATE with a report that includes final summary statistics. The program processes customer records, accumulates statistics, and then generates a final summary before terminating the report. The TERMINATE statement ensures that the final summary is properly included in the report output and that all report processing is completed correctly. This pattern is common for reports that need to include summary information at the end.

Error Handling with TERMINATE

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
83
84
85
86
87
88
89
90
91
92
93
94
* Error handling with TERMINATE example IDENTIFICATION DIVISION. PROGRAM-ID. ERROR-HANDLING-TERMINATE-EXAMPLE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT TRANSACTION-FILE ASSIGN TO "TRANS.DAT" ORGANIZATION IS SEQUENTIAL. SELECT TRANSACTION-REPORT ASSIGN TO "TRANS.RPT" ORGANIZATION IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD TRANSACTION-FILE. 01 TRANSACTION-RECORD. 05 TRANS-ID PIC 9(6). 05 TRANS-AMOUNT PIC 9(7)V99. 05 TRANS-TYPE PIC X(1). SD TRANSACTION-REPORT. 01 REPORT-LINE PIC X(80). WORKING-STORAGE SECTION. 01 WS-EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. 01 WS-ERROR-COUNT PIC 9(3) VALUE 0. 01 WS-PROCESS-COUNT PIC 9(4) VALUE 0. PROCEDURE DIVISION. MAIN-LOGIC. * Initialize report INITIATE TRANSACTION-REPORT * Open input file OPEN INPUT TRANSACTION-FILE IF WS-FILE-STATUS NOT = "00" DISPLAY "Error opening transaction file" STOP RUN END-IF * Process transaction records PERFORM UNTIL END-OF-FILE READ TRANSACTION-FILE AT END SET END-OF-FILE TO TRUE NOT AT END IF WS-FILE-STATUS = "00" PERFORM PROCESS-TRANSACTION-RECORD ELSE ADD 1 TO WS-ERROR-COUNT DISPLAY "Error reading record" END-IF END-READ END-PERFORM * Generate error summary PERFORM GENERATE-ERROR-SUMMARY * Terminate report even if errors occurred TERMINATE TRANSACTION-REPORT * Close input file CLOSE TRANSACTION-FILE DISPLAY "Report processing completed" DISPLAY "Records processed: " WS-PROCESS-COUNT DISPLAY "Errors encountered: " WS-ERROR-COUNT STOP RUN. PROCESS-TRANSACTION-RECORD. * Process individual transaction record ADD 1 TO WS-PROCESS-COUNT * Validate transaction data IF TRANS-AMOUNT <= 0 ADD 1 TO WS-ERROR-COUNT DISPLAY "Invalid amount for transaction: " TRANS-ID ELSE * Process valid transaction DISPLAY "Processing transaction: " TRANS-ID END-IF. GENERATE-ERROR-SUMMARY. * Generate summary of processing results DISPLAY "=== PROCESSING SUMMARY ===" DISPLAY "Total records processed: " WS-PROCESS-COUNT DISPLAY "Total errors encountered: " WS-ERROR-COUNT IF WS-ERROR-COUNT > 0 DISPLAY "WARNING: Errors were encountered during processing" ELSE DISPLAY "SUCCESS: All records processed without errors" END-IF.

Explanation: This example shows how to use TERMINATE in an error handling scenario. The program processes transaction records and tracks both successful processing and errors. Even when errors occur, the TERMINATE statement is still executed to ensure that the report is properly finalized and any valid data is included in the report output. This demonstrates that TERMINATE should be called regardless of whether errors occurred during processing, as it completes the report generation process.

Best Practices and Considerations

Important Considerations

  • TERMINATE must be called after all data processing
  • Use TERMINATE even if errors occur during processing
  • Generate final summaries before TERMINATE
  • Ensure all report data is processed before termination
  • Close files after TERMINATE execution

Advantages

  • Ensures proper report completion
  • Generates final report output
  • Processes remaining report data
  • Provides structured report processing
  • Handles report formatting automatically

Limitations

  • Must be used in correct sequence
  • Cannot be used without INITIATE
  • May not handle all error conditions
  • Requires proper report setup
  • May not be available in all COBOL implementations

Best Practices

  • • Always call TERMINATE after processing all data
  • • Generate final summaries before TERMINATE
  • • Use TERMINATE even when errors occur
  • • Close files after TERMINATE execution
  • • Ensure proper INITIATE-TERMINATE pairing

Test Your Knowledge

1. What is the primary purpose of the TERMINATE statement in COBOL?

  • To stop program execution
  • To end report processing and finalize report generation
  • To terminate file operations
  • To end database connections

2. In which COBOL division is the TERMINATE statement typically used?

  • IDENTIFICATION DIVISION
  • ENVIRONMENT DIVISION
  • DATA DIVISION
  • PROCEDURE DIVISION

3. What is the relationship between TERMINATE and report processing?

  • They are unrelated
  • TERMINATE is used to end report processing
  • TERMINATE starts report processing
  • TERMINATE is optional for reports

4. When should you use the TERMINATE statement?

  • At the beginning of report processing
  • After all report data has been processed
  • Only for error conditions
  • Before opening report files

5. What happens when a TERMINATE statement is executed?

  • The program stops immediately
  • Report processing is finalized and final output is generated
  • All files are closed
  • The program restarts