MainframeMaster

COBOL Tutorial

COBOL END-DELETE Statement

The END-DELETE statement represents a crucial component of structured file processing in COBOL, serving as an explicit scope terminator that clearly defines the boundaries of DELETE statement blocks. This statement embodies modern programming principles by providing unambiguous termination points for file record deletion operations, enabling sophisticated error handling for I/O conditions, and supporting the development of robust, maintainable enterprise applications that require precise control over data management operations and their associated error conditions.

Understanding END-DELETE

The END-DELETE statement implements sophisticated scope management for file record deletion operations. When used with conditional phrases like INVALID KEY and NOT INVALID KEY, END-DELETE creates a comprehensive framework for handling both successful deletions and error conditions that may arise during file operations.

This explicit termination is particularly important in data management applications where transaction integrity and error handling are paramount. END-DELETE enables developers to implement sophisticated deletion logic while maintaining code clarity and ensuring that file operations are properly bounded within defined scopes.

Basic END-DELETE 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
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
IDENTIFICATION DIVISION. PROGRAM-ID. END-DELETE-DEMO. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT EMPLOYEE-FILE ASSIGN TO 'EMPLOYEE.DAT' ORGANIZATION IS INDEXED ACCESS MODE IS DYNAMIC RECORD KEY IS EMPLOYEE-ID FILE STATUS IS EMPLOYEE-FILE-STATUS. DATA DIVISION. FILE SECTION. FD EMPLOYEE-FILE. 01 EMPLOYEE-RECORD. 05 EMPLOYEE-ID PIC X(10). 05 EMPLOYEE-NAME PIC X(30). 05 EMPLOYEE-SALARY PIC 9(7)V99. 05 EMPLOYEE-DEPARTMENT PIC X(10). WORKING-STORAGE SECTION. 01 EMPLOYEE-FILE-STATUS PIC XX. 01 DELETE-CONTROLS. 05 DELETE-COUNT PIC 9(5). 05 ERROR-COUNT PIC 9(5). 05 SUCCESSFUL-COUNT PIC 9(5). 01 EMPLOYEE-TO-DELETE PIC X(10). 01 DELETION-FLAG PIC X VALUE 'N'. 88 DELETION-SUCCESSFUL VALUE 'Y'. 88 DELETION-FAILED VALUE 'N'. PROCEDURE DIVISION. MAIN-PROCESSING. OPEN I-O EMPLOYEE-FILE MOVE 'EMP001' TO EMPLOYEE-TO-DELETE PERFORM DELETE-EMPLOYEE-RECORD MOVE 'EMP002' TO EMPLOYEE-TO-DELETE PERFORM DELETE-EMPLOYEE-RECORD CLOSE EMPLOYEE-FILE DISPLAY 'Deletion Summary:' DISPLAY 'Total Deletions Attempted: ' DELETE-COUNT DISPLAY 'Successful Deletions: ' SUCCESSFUL-COUNT DISPLAY 'Failed Deletions: ' ERROR-COUNT STOP RUN. DELETE-EMPLOYEE-RECORD. ADD 1 TO DELETE-COUNT MOVE EMPLOYEE-TO-DELETE TO EMPLOYEE-ID *> First read the record to ensure it exists READ EMPLOYEE-FILE KEY IS EMPLOYEE-ID INVALID KEY DISPLAY 'Employee not found: ' EMPLOYEE-TO-DELETE ADD 1 TO ERROR-COUNT SET DELETION-FAILED TO TRUE NOT INVALID KEY DISPLAY 'Employee found: ' EMPLOYEE-NAME PERFORM CONFIRM-AND-DELETE END-READ. CONFIRM-AND-DELETE. DISPLAY 'Deleting employee: ' EMPLOYEE-ID DELETE EMPLOYEE-FILE INVALID KEY DISPLAY 'Delete failed for employee: ' EMPLOYEE-ID DISPLAY 'File status: ' EMPLOYEE-FILE-STATUS ADD 1 TO ERROR-COUNT SET DELETION-FAILED TO TRUE NOT INVALID KEY DISPLAY 'Employee deleted successfully: ' EMPLOYEE-ID ADD 1 TO SUCCESSFUL-COUNT SET DELETION-SUCCESSFUL TO TRUE END-DELETE.

Advanced END-DELETE Patterns

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
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
IDENTIFICATION DIVISION. PROGRAM-ID. ADVANCED-END-DELETE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO 'CUSTOMER.DAT' ORGANIZATION IS INDEXED ACCESS MODE IS DYNAMIC RECORD KEY IS CUSTOMER-ID ALTERNATE RECORD KEY IS CUSTOMER-EMAIL WITH DUPLICATES FILE STATUS IS CUSTOMER-FILE-STATUS. SELECT AUDIT-FILE ASSIGN TO 'AUDIT.LOG' ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS AUDIT-FILE-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC X(15). 05 CUSTOMER-NAME PIC X(50). 05 CUSTOMER-EMAIL PIC X(100). 05 CUSTOMER-STATUS PIC X(10). 05 LAST-MODIFIED-DATE PIC X(10). FD AUDIT-FILE. 01 AUDIT-RECORD. 05 AUDIT-TIMESTAMP PIC X(26). 05 AUDIT-ACTION PIC X(20). 05 AUDIT-USER-ID PIC X(10). 05 AUDIT-RECORD-ID PIC X(15). 05 AUDIT-DETAILS PIC X(200). WORKING-STORAGE SECTION. 01 CUSTOMER-FILE-STATUS PIC XX. 01 AUDIT-FILE-STATUS PIC XX. 01 BATCH-DELETE-CONTROLS. 05 BATCH-SIZE PIC 9(5) VALUE 1000. 05 CURRENT-BATCH PIC 9(5). 05 RECORDS-PROCESSED PIC 9(7). 05 RECORDS-DELETED PIC 9(7). 05 RECORDS-FAILED PIC 9(7). 01 DELETE-CRITERIA. 05 DELETE-STATUS PIC X(10) VALUE 'INACTIVE'. 05 DELETE-BEFORE-DATE PIC X(10) VALUE '2020-01-01'. 05 CONFIRMATION-REQUIRED PIC X VALUE 'Y'. 01 TRANSACTION-CONTROLS. 05 TRANSACTION-ID PIC X(20). 05 ROLLBACK-REQUIRED PIC X VALUE 'N'. 88 ROLLBACK-NEEDED VALUE 'Y'. 05 COMMIT-INTERVAL PIC 9(5) VALUE 100. PROCEDURE DIVISION. MAIN-PROCESSING. PERFORM INITIALIZE-BATCH-DELETE PERFORM PROCESS-BATCH-DELETION PERFORM FINALIZE-BATCH-DELETE STOP RUN. INITIALIZE-BATCH-DELETE. OPEN I-O CUSTOMER-FILE OPEN OUTPUT AUDIT-FILE MOVE ZEROS TO CURRENT-BATCH, RECORDS-PROCESSED, RECORDS-DELETED, RECORDS-FAILED DISPLAY 'Batch deletion initialized' DISPLAY 'Delete criteria: Status = ' DELETE-STATUS DISPLAY 'Delete before date: ' DELETE-BEFORE-DATE. PROCESS-BATCH-DELETION. PERFORM UNTIL CURRENT-BATCH >= BATCH-SIZE PERFORM READ-NEXT-CANDIDATE IF CUSTOMER-FILE-STATUS = '10' EXIT PERFORM END-IF PERFORM EVALUATE-DELETE-CRITERIA PERFORM PROCESS-INDIVIDUAL-DELETE ADD 1 TO CURRENT-BATCH ADD 1 TO RECORDS-PROCESSED *> Commit transaction periodically IF FUNCTION MOD(RECORDS-PROCESSED, COMMIT-INTERVAL) = 0 PERFORM COMMIT-TRANSACTION END-IF END-PERFORM. READ-NEXT-CANDIDATE. READ CUSTOMER-FILE NEXT RECORD AT END DISPLAY 'End of file reached' NOT AT END CONTINUE END-READ. EVALUATE-DELETE-CRITERIA. IF CUSTOMER-STATUS = DELETE-STATUS IF LAST-MODIFIED-DATE < DELETE-BEFORE-DATE PERFORM CONFIRM-DELETION ELSE DISPLAY 'Record too recent for deletion: ' CUSTOMER-ID END-IF ELSE DISPLAY 'Record does not meet status criteria: ' CUSTOMER-ID END-IF. CONFIRM-DELETION. IF CONFIRMATION-REQUIRED = 'Y' DISPLAY 'Confirm deletion of customer: ' CUSTOMER-ID DISPLAY 'Name: ' CUSTOMER-NAME DISPLAY 'Email: ' CUSTOMER-EMAIL DISPLAY 'Status: ' CUSTOMER-STATUS DISPLAY 'Last Modified: ' LAST-MODIFIED-DATE *> In real application, would accept user confirmation END-IF PERFORM EXECUTE-DELETION. EXECUTE-DELETION. PERFORM LOG-DELETION-ATTEMPT DELETE CUSTOMER-FILE INVALID KEY DISPLAY 'Delete failed for customer: ' CUSTOMER-ID DISPLAY 'File status: ' CUSTOMER-FILE-STATUS ADD 1 TO RECORDS-FAILED PERFORM LOG-DELETION-FAILURE EVALUATE CUSTOMER-FILE-STATUS WHEN '23' DISPLAY 'Record not found' WHEN '24' DISPLAY 'Boundary violation' WHEN '30' DISPLAY 'Permanent I/O error' SET ROLLBACK-NEEDED TO TRUE WHEN OTHER DISPLAY 'Unknown error: ' CUSTOMER-FILE-STATUS SET ROLLBACK-NEEDED TO TRUE END-EVALUATE NOT INVALID KEY ADD 1 TO RECORDS-DELETED DISPLAY 'Customer deleted successfully: ' CUSTOMER-ID PERFORM LOG-DELETION-SUCCESS END-DELETE IF ROLLBACK-NEEDED PERFORM ROLLBACK-TRANSACTION END-IF. LOG-DELETION-ATTEMPT. MOVE FUNCTION CURRENT-DATE TO AUDIT-TIMESTAMP MOVE 'DELETE-ATTEMPT' TO AUDIT-ACTION MOVE 'SYSTEM' TO AUDIT-USER-ID MOVE CUSTOMER-ID TO AUDIT-RECORD-ID STRING 'Attempting to delete customer: ' DELIMITED BY SIZE CUSTOMER-NAME DELIMITED BY SIZE ' Status: ' DELIMITED BY SIZE CUSTOMER-STATUS DELIMITED BY SIZE INTO AUDIT-DETAILS END-STRING WRITE AUDIT-RECORD INVALID KEY DISPLAY 'Audit log write failed' END-WRITE. LOG-DELETION-SUCCESS. MOVE FUNCTION CURRENT-DATE TO AUDIT-TIMESTAMP MOVE 'DELETE-SUCCESS' TO AUDIT-ACTION MOVE 'SYSTEM' TO AUDIT-USER-ID MOVE CUSTOMER-ID TO AUDIT-RECORD-ID STRING 'Successfully deleted customer: ' DELIMITED BY SIZE CUSTOMER-NAME DELIMITED BY SIZE INTO AUDIT-DETAILS END-STRING WRITE AUDIT-RECORD INVALID KEY DISPLAY 'Audit log write failed' END-WRITE. LOG-DELETION-FAILURE. MOVE FUNCTION CURRENT-DATE TO AUDIT-TIMESTAMP MOVE 'DELETE-FAILURE' TO AUDIT-ACTION MOVE 'SYSTEM' TO AUDIT-USER-ID MOVE CUSTOMER-ID TO AUDIT-RECORD-ID STRING 'Failed to delete customer: ' DELIMITED BY SIZE CUSTOMER-NAME DELIMITED BY SIZE ' Error: ' DELIMITED BY SIZE CUSTOMER-FILE-STATUS DELIMITED BY SIZE INTO AUDIT-DETAILS END-STRING WRITE AUDIT-RECORD INVALID KEY DISPLAY 'Audit log write failed' END-WRITE. COMMIT-TRANSACTION. DISPLAY 'Committing transaction at record: ' RECORDS-PROCESSED. ROLLBACK-TRANSACTION. DISPLAY 'Rolling back transaction due to critical error' MOVE 'N' TO ROLLBACK-REQUIRED. FINALIZE-BATCH-DELETE. CLOSE CUSTOMER-FILE CLOSE AUDIT-FILE DISPLAY 'Batch deletion completed' DISPLAY 'Total records processed: ' RECORDS-PROCESSED DISPLAY 'Records deleted: ' RECORDS-DELETED DISPLAY 'Records failed: ' RECORDS-FAILED.

Best Practices

Recommended Practices

  • • Always use END-DELETE with error handling
  • • Implement comprehensive file status checking
  • • Use transaction control for batch deletions
  • • Maintain audit trails for deletion operations
  • • Validate records before deletion

Common Mistakes

  • • Omitting END-DELETE in nested structures
  • • Not handling INVALID KEY conditions
  • • Poor file status error handling
  • • Inconsistent use of END-DELETE
  • • Missing audit trail implementation

Frequently Asked Questions

Is END-DELETE required for all DELETE statements?

END-DELETE is not required for simple DELETE statements without conditional phrases. However, it becomes essential when using INVALID KEY or NOT INVALID KEY clauses, in nested structures, or when you want to explicitly define the scope of deletion operations for better code clarity.

How does END-DELETE handle file errors?

END-DELETE works with INVALID KEY and NOT INVALID KEY phrases to provide comprehensive handling of file operation errors. When an error occurs during deletion, the INVALID KEY clause is executed, allowing for error logging, recovery actions, or alternative processing paths.

Can END-DELETE be used with different file organizations?

Yes, END-DELETE can be used with various file organizations including sequential, indexed, and relative files. The error handling capabilities are particularly valuable with indexed files where key-based deletion operations may encounter various error conditions.