MainframeMaster

COBOL Tutorial

COBOL CLOSE Statement

The CLOSE statement in COBOL is essential for proper file management and resource control, ensuring that files are properly closed, buffers are flushed, and system resources are released correctly. This statement is critical for maintaining data integrity, preventing resource leaks, and ensuring proper cleanup in enterprise applications where file handling operations must be robust, reliable, and compliant with system requirements for data persistence, transaction integrity, and resource management in high-volume processing environments where proper file closure is paramount for system stability and performance.

Understanding CLOSE Operations

The CLOSE statement terminates the processing of one or more files, ensuring that all pending I/O operations are completed, buffers are flushed to storage, and system resources are properly released. It's the counterpart to the OPEN statement and is essential for proper file lifecycle management.

Key Features:

  • File termination and resource cleanup with automatic buffer flushing
  • Multiple file closure in a single statement for batch operations
  • Optional positioning control for tape and sequential files
  • Error handling and status checking for failed close operations
  • Integration with transaction processing and commit operations
  • Support for different file types and access methods
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
*> Basic CLOSE statement usage for different file types DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE. 01 CUSTOMER-RECORD. 05 CUST-ID PIC 9(8). 05 CUST-NAME PIC X(30). 05 CUST-BALANCE PIC 9(7)V99. FD TRANSACTION-FILE. 01 TRANSACTION-RECORD. 05 TRANS-ID PIC 9(10). 05 TRANS-TYPE PIC X(2). 05 TRANS-AMOUNT PIC 9(7)V99. FD REPORT-FILE. 01 REPORT-RECORD PIC X(132). FD BACKUP-FILE. 01 BACKUP-RECORD PIC X(100). WORKING-STORAGE SECTION. 01 FILE-STATUS-CODES. 05 CUSTOMER-STATUS PIC X(2). 05 TRANSACTION-STATUS PIC X(2). 05 REPORT-STATUS PIC X(2). 05 BACKUP-STATUS PIC X(2). 01 PROCESSING-COUNTERS. 05 RECORDS-PROCESSED PIC 9(7) VALUE ZERO. 05 FILES-OPENED PIC 9(2) VALUE ZERO. 05 FILES-CLOSED PIC 9(2) VALUE ZERO. 05 CLOSE-ERRORS PIC 9(2) VALUE ZERO. 01 CLOSE-CONTROL-FLAGS. 05 SAFE-CLOSE-MODE PIC X VALUE 'Y'. 88 SAFE-CLOSE VALUE 'Y'. 05 FORCE-CLOSE-MODE PIC X VALUE 'N'. 88 FORCE-CLOSE VALUE 'Y'. 05 BATCH-CLOSE-MODE PIC X VALUE 'N'. 88 BATCH-CLOSE VALUE 'Y'. PROCEDURE DIVISION. BASIC-FILE-CLOSE-OPERATIONS. PERFORM INITIALIZE-FILE-PROCESSING PERFORM PROCESS-FILES PERFORM CLOSE-ALL-FILES PERFORM DISPLAY-CLOSE-SUMMARY. INITIALIZE-FILE-PROCESSING. MOVE ZERO TO RECORDS-PROCESSED FILES-OPENED FILES-CLOSED CLOSE-ERRORS *> Open files for processing OPEN INPUT CUSTOMER-FILE OPEN INPUT TRANSACTION-FILE OPEN OUTPUT REPORT-FILE OPEN OUTPUT BACKUP-FILE MOVE 4 TO FILES-OPENED. PROCESS-FILES. *> Simulate file processing PERFORM UNTIL CUSTOMER-STATUS = "10" READ CUSTOMER-FILE AT END MOVE "10" TO CUSTOMER-STATUS NOT AT END ADD 1 TO RECORDS-PROCESSED PERFORM PROCESS-CUSTOMER-RECORD END-READ END-PERFORM. PROCESS-CUSTOMER-RECORD. *> Write to report and backup files MOVE CUSTOMER-RECORD TO BACKUP-RECORD WRITE BACKUP-RECORD STRING "Customer: " CUST-ID " " CUST-NAME " Balance: " CUST-BALANCE DELIMITED BY SIZE INTO REPORT-RECORD END-STRING WRITE REPORT-RECORD. CLOSE-ALL-FILES. *> Individual file closing with error checking PERFORM CLOSE-CUSTOMER-FILE PERFORM CLOSE-TRANSACTION-FILE PERFORM CLOSE-REPORT-FILE PERFORM CLOSE-BACKUP-FILE. CLOSE-CUSTOMER-FILE. CLOSE CUSTOMER-FILE IF CUSTOMER-STATUS = "00" ADD 1 TO FILES-CLOSED DISPLAY "Customer file closed successfully" ELSE ADD 1 TO CLOSE-ERRORS DISPLAY "Error closing customer file: " CUSTOMER-STATUS END-IF. CLOSE-TRANSACTION-FILE. CLOSE TRANSACTION-FILE IF TRANSACTION-STATUS = "00" ADD 1 TO FILES-CLOSED DISPLAY "Transaction file closed successfully" ELSE ADD 1 TO CLOSE-ERRORS DISPLAY "Error closing transaction file: " TRANSACTION-STATUS END-IF. CLOSE-REPORT-FILE. CLOSE REPORT-FILE IF REPORT-STATUS = "00" ADD 1 TO FILES-CLOSED DISPLAY "Report file closed successfully" ELSE ADD 1 TO CLOSE-ERRORS DISPLAY "Error closing report file: " REPORT-STATUS END-IF. CLOSE-BACKUP-FILE. CLOSE BACKUP-FILE IF BACKUP-STATUS = "00" ADD 1 TO FILES-CLOSED DISPLAY "Backup file closed successfully" ELSE ADD 1 TO CLOSE-ERRORS DISPLAY "Error closing backup file: " BACKUP-STATUS END-IF. DISPLAY-CLOSE-SUMMARY. DISPLAY "=== File Close Summary ===" DISPLAY "Files Opened: " FILES-OPENED DISPLAY "Files Closed: " FILES-CLOSED DISPLAY "Close Errors: " CLOSE-ERRORS DISPLAY "Records Processed: " RECORDS-PROCESSED.

Advanced Close Operations and Error Handling

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
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
*> Advanced close operations with comprehensive error handling DATA DIVISION. WORKING-STORAGE SECTION. 01 ADVANCED-CLOSE-CONTROL. 05 CLOSE-OPERATION-LOG OCCURS 20 TIMES. 10 LOG-FILE-NAME PIC X(30). 10 LOG-CLOSE-TIME PIC X(26). 10 LOG-STATUS PIC X(2). 10 LOG-ERROR-MSG PIC X(50). 10 LOG-RETRY-COUNT PIC 9(2). 05 LOG-ENTRY-COUNT PIC 9(2) VALUE ZERO. 01 RETRY-CONTROL. 05 MAX-RETRY-ATTEMPTS PIC 9(2) VALUE 3. 05 RETRY-DELAY-SECONDS PIC 9(3) VALUE 5. 05 CURRENT-RETRY PIC 9(2) VALUE ZERO. 01 CLOSE-STRATEGIES. 05 NORMAL-CLOSE PIC X VALUE 'N'. 88 USE-NORMAL-CLOSE VALUE 'N'. 05 WITH-LOCK PIC X VALUE 'L'. 88 USE-LOCK-CLOSE VALUE 'L'. 05 WITH-NO-REWIND PIC X VALUE 'R'. 88 USE-NO-REWIND VALUE 'R'. 05 UNIT-CLOSE PIC X VALUE 'U'. 88 USE-UNIT-CLOSE VALUE 'U'. 01 TRANSACTION-CONTROL. 05 TRANSACTION-ACTIVE PIC X VALUE 'N'. 88 TRANS-ACTIVE VALUE 'Y'. 05 COMMIT-BEFORE-CLOSE PIC X VALUE 'Y'. 88 COMMIT-FIRST VALUE 'Y'. 05 ROLLBACK-ON-ERROR PIC X VALUE 'Y'. 88 ROLLBACK-ERROR VALUE 'Y'. 01 RESOURCE-MONITORING. 05 MEMORY-USAGE-BEFORE PIC 9(8) VALUE ZERO. 05 MEMORY-USAGE-AFTER PIC 9(8) VALUE ZERO. 05 MEMORY-FREED PIC 9(8) VALUE ZERO. 05 BUFFER-COUNT PIC 9(4) VALUE ZERO. 05 OPEN-FILE-COUNT PIC 9(3) VALUE ZERO. PROCEDURE DIVISION. ADVANCED-CLOSE-PROCESSING. PERFORM INITIALIZE-ADVANCED-CLOSE PERFORM MONITOR-RESOURCE-USAGE PERFORM EXECUTE-STRATEGIC-CLOSE PERFORM VERIFY-CLOSE-COMPLETION PERFORM GENERATE-CLOSE-REPORT. INITIALIZE-ADVANCED-CLOSE. MOVE ZERO TO LOG-ENTRY-COUNT CURRENT-RETRY MOVE FUNCTION CURRENT-DATE TO WS-CURRENT-TIMESTAMP *> Initialize monitoring PERFORM GET-SYSTEM-RESOURCE-USAGE MOVE WS-MEMORY-USAGE TO MEMORY-USAGE-BEFORE. MONITOR-RESOURCE-USAGE. *> Monitor system resources before closing PERFORM COUNT-OPEN-FILES PERFORM COUNT-ACTIVE-BUFFERS DISPLAY "Pre-close Resource Status:" DISPLAY "Open Files: " OPEN-FILE-COUNT DISPLAY "Active Buffers: " BUFFER-COUNT DISPLAY "Memory Usage: " MEMORY-USAGE-BEFORE " KB". EXECUTE-STRATEGIC-CLOSE. *> Close files using different strategies based on file type PERFORM CLOSE-INPUT-FILES-STRATEGY PERFORM CLOSE-OUTPUT-FILES-STRATEGY PERFORM CLOSE-UPDATE-FILES-STRATEGY PERFORM CLOSE-TEMPORARY-FILES-STRATEGY. CLOSE-INPUT-FILES-STRATEGY. *> Strategy for input files - normal close MOVE 'N' TO NORMAL-CLOSE PERFORM CLOSE-FILE-WITH-STRATEGY("CUSTOMER-FILE", NORMAL-CLOSE) PERFORM CLOSE-FILE-WITH-STRATEGY("TRANSACTION-FILE", NORMAL-CLOSE). CLOSE-OUTPUT-FILES-STRATEGY. *> Strategy for output files - ensure data is written MOVE 'N' TO NORMAL-CLOSE PERFORM CLOSE-FILE-WITH-STRATEGY("REPORT-FILE", NORMAL-CLOSE) PERFORM CLOSE-FILE-WITH-STRATEGY("BACKUP-FILE", NORMAL-CLOSE). CLOSE-UPDATE-FILES-STRATEGY. *> Strategy for update files - commit before close IF TRANS-ACTIVE AND COMMIT-FIRST PERFORM COMMIT-TRANSACTION END-IF MOVE 'L' TO WITH-LOCK PERFORM CLOSE-FILE-WITH-STRATEGY("UPDATE-FILE", WITH-LOCK). CLOSE-TEMPORARY-FILES-STRATEGY. *> Strategy for temporary files - quick close MOVE 'U' TO UNIT-CLOSE PERFORM CLOSE-FILE-WITH-STRATEGY("TEMP-FILE", UNIT-CLOSE). CLOSE-FILE-WITH-STRATEGY. *> Generic close routine with retry logic MOVE ZERO TO CURRENT-RETRY MOVE 'N' TO WS-CLOSE-SUCCESS PERFORM UNTIL WS-CLOSE-SUCCESS = 'Y' OR CURRENT-RETRY >= MAX-RETRY-ATTEMPTS ADD 1 TO CURRENT-RETRY PERFORM ATTEMPT-FILE-CLOSE IF WS-FILE-STATUS NOT = "00" PERFORM LOG-CLOSE-ATTEMPT IF CURRENT-RETRY < MAX-RETRY-ATTEMPTS PERFORM WAIT-BEFORE-RETRY END-IF ELSE MOVE 'Y' TO WS-CLOSE-SUCCESS PERFORM LOG-SUCCESSFUL-CLOSE END-IF END-PERFORM IF WS-CLOSE-SUCCESS = 'N' PERFORM HANDLE-CLOSE-FAILURE END-IF. ATTEMPT-FILE-CLOSE. *> Attempt to close file based on strategy EVALUATE WS-CLOSE-STRATEGY WHEN 'N' *> Normal close CLOSE WS-FILE-NAME WHEN 'L' *> Close with lock CLOSE WS-FILE-NAME WITH LOCK WHEN 'R' *> Close with no rewind (tape files) CLOSE WS-FILE-NAME WITH NO REWIND WHEN 'U' *> Unit close CLOSE WS-FILE-NAME UNIT END-EVALUATE. LOG-CLOSE-ATTEMPT. ADD 1 TO LOG-ENTRY-COUNT MOVE WS-FILE-NAME TO LOG-FILE-NAME(LOG-ENTRY-COUNT) MOVE WS-CURRENT-TIMESTAMP TO LOG-CLOSE-TIME(LOG-ENTRY-COUNT) MOVE WS-FILE-STATUS TO LOG-STATUS(LOG-ENTRY-COUNT) MOVE CURRENT-RETRY TO LOG-RETRY-COUNT(LOG-ENTRY-COUNT) EVALUATE WS-FILE-STATUS WHEN "30" MOVE "Permanent I/O error" TO LOG-ERROR-MSG(LOG-ENTRY-COUNT) WHEN "34" MOVE "Boundary violation" TO LOG-ERROR-MSG(LOG-ENTRY-COUNT) WHEN "35" MOVE "File not found" TO LOG-ERROR-MSG(LOG-ENTRY-COUNT) WHEN "37" MOVE "File not open" TO LOG-ERROR-MSG(LOG-ENTRY-COUNT) WHEN "38" MOVE "File already closed" TO LOG-ERROR-MSG(LOG-ENTRY-COUNT) WHEN "39" MOVE "File attribute conflict" TO LOG-ERROR-MSG(LOG-ENTRY-COUNT) WHEN OTHER STRING "Unknown error: " WS-FILE-STATUS DELIMITED BY SIZE INTO LOG-ERROR-MSG(LOG-ENTRY-COUNT) END-STRING END-EVALUATE. LOG-SUCCESSFUL-CLOSE. ADD 1 TO LOG-ENTRY-COUNT MOVE WS-FILE-NAME TO LOG-FILE-NAME(LOG-ENTRY-COUNT) MOVE WS-CURRENT-TIMESTAMP TO LOG-CLOSE-TIME(LOG-ENTRY-COUNT) MOVE "00" TO LOG-STATUS(LOG-ENTRY-COUNT) MOVE "File closed successfully" TO LOG-ERROR-MSG(LOG-ENTRY-COUNT) MOVE CURRENT-RETRY TO LOG-RETRY-COUNT(LOG-ENTRY-COUNT). WAIT-BEFORE-RETRY. *> Implement delay before retry (system-specific) DISPLAY "Waiting " RETRY-DELAY-SECONDS " seconds before retry..." *> CALL "SLEEP" USING RETRY-DELAY-SECONDS (system-specific) . HANDLE-CLOSE-FAILURE. DISPLAY "CRITICAL: Failed to close file " WS-FILE-NAME DISPLAY "Final status: " WS-FILE-STATUS IF ROLLBACK-ERROR AND TRANS-ACTIVE PERFORM ROLLBACK-TRANSACTION DISPLAY "Transaction rolled back due to close failure" END-IF *> Log critical error for system administrator PERFORM LOG-CRITICAL-ERROR. COMMIT-TRANSACTION. *> Commit any pending transactions *> EXEC SQL COMMIT END-EXEC (if using embedded SQL) MOVE 'N' TO TRANSACTION-ACTIVE DISPLAY "Transaction committed before file close". ROLLBACK-TRANSACTION. *> Rollback transactions on error *> EXEC SQL ROLLBACK END-EXEC (if using embedded SQL) MOVE 'N' TO TRANSACTION-ACTIVE DISPLAY "Transaction rolled back due to error". VERIFY-CLOSE-COMPLETION. *> Verify all files are properly closed PERFORM COUNT-OPEN-FILES IF OPEN-FILE-COUNT > 0 DISPLAY "WARNING: " OPEN-FILE-COUNT " files still open" PERFORM FORCE-CLOSE-REMAINING-FILES ELSE DISPLAY "All files closed successfully" END-IF. FORCE-CLOSE-REMAINING-FILES. *> Emergency close for any remaining open files DISPLAY "Attempting emergency close of remaining files..." *> Implementation would be system-specific . GET-SYSTEM-RESOURCE-USAGE. *> Get current system resource usage (system-specific) *> This would typically call system APIs MOVE 1024 TO WS-MEMORY-USAGE *> Placeholder . COUNT-OPEN-FILES. *> Count currently open files (system-specific) MOVE 0 TO OPEN-FILE-COUNT *> Placeholder . COUNT-ACTIVE-BUFFERS. *> Count active I/O buffers (system-specific) MOVE 0 TO BUFFER-COUNT *> Placeholder . LOG-CRITICAL-ERROR. *> Log critical errors to system log DISPLAY "CRITICAL ERROR logged to system" *> Implementation would write to system error log . GENERATE-CLOSE-REPORT. PERFORM GET-SYSTEM-RESOURCE-USAGE MOVE WS-MEMORY-USAGE TO MEMORY-USAGE-AFTER COMPUTE MEMORY-FREED = MEMORY-USAGE-BEFORE - MEMORY-USAGE-AFTER DISPLAY "=== Advanced Close Operation Report ===" DISPLAY "Total Close Operations: " LOG-ENTRY-COUNT DISPLAY "Memory Freed: " MEMORY-FREED " KB" DISPLAY "Final Open Files: " OPEN-FILE-COUNT DISPLAY "" DISPLAY "Close Operation Log:" PERFORM VARYING WS-I FROM 1 BY 1 UNTIL WS-I > LOG-ENTRY-COUNT DISPLAY "File: " LOG-FILE-NAME(WS-I) DISPLAY "Time: " LOG-CLOSE-TIME(WS-I) DISPLAY "Status: " LOG-STATUS(WS-I) DISPLAY "Message: " LOG-ERROR-MSG(WS-I) DISPLAY "Retries: " LOG-RETRY-COUNT(WS-I) DISPLAY "---" END-PERFORM.

Best Practices and Guidelines

CLOSE Statement Guidelines:

  • Always close files in the reverse order of opening to maintain proper resource cleanup
  • Check file status after each CLOSE operation to detect and handle errors appropriately
  • Use appropriate close options (WITH LOCK, WITH NO REWIND) based on file type and requirements
  • Implement retry logic for close operations in high-availability environments
  • Close files in exception handling routines to prevent resource leaks
  • Monitor system resources before and after close operations for performance tuning
  • Document close strategies and error handling procedures for maintenance teams
  • Test close operations under various failure scenarios to ensure robustness
  • Consider transaction boundaries when closing files involved in database operations
  • Use batch close operations where appropriate to improve performance

Comprehensive FAQ

Q: What happens if I don't close a file before program termination?

The system typically closes files automatically when a program terminates, but this may not flush all buffers properly. Explicitly closing files ensures data integrity, proper resource cleanup, and consistent behavior across different systems. Unclosed files can lead to data loss, resource leaks, and file corruption.

Q: When should I use CLOSE WITH LOCK?

Use CLOSE WITH LOCK for files that should not be reopened within the same program execution, typically for security or data integrity reasons. This is common with audit files, security logs, or files containing sensitive data that should only be accessed once per program run.

Q: How do I handle CLOSE errors in batch processing?

Implement comprehensive error handling with retry logic, logging, and fallback procedures. Consider the business impact of failed closes - some may require program termination, while others might allow continued processing with alerts. Always log close failures for audit and troubleshooting purposes.

Q: Can I close multiple files in a single CLOSE statement?

Yes, you can close multiple files in one CLOSE statement: CLOSE FILE1, FILE2, FILE3. However, if one file fails to close, it may affect the others. For better error control and logging, consider closing files individually, especially in critical applications where you need precise error handling.

Q: What's the difference between CLOSE and CLOSE WITH NO REWIND?

CLOSE WITH NO REWIND is primarily for tape files and prevents the tape from rewinding to the beginning. This allows the tape to be positioned for the next file or operation. For disk files, this option typically has no effect, but it's important for sequential tape processing in mainframe environments.

Q: How do I ensure data is written before closing?

The CLOSE statement automatically flushes buffers and ensures pending writes are completed. For database files or transaction processing, consider committing transactions before closing. Some systems provide explicit flush operations, but CLOSE typically handles this automatically.

Interactive Quiz

Test Your CLOSE Knowledge

1. What is the primary purpose of the CLOSE statement?

2. When should you use CLOSE WITH LOCK?

3. What happens if a CLOSE operation fails?

Answers: 1-B, 2-B, 3-B