MainframeMaster

COBOL Tutorial

COBOL File Processing

Progress0 of 0 lessons

File Processing Fundamentals

File processing in COBOL involves a series of operations to read, write, update, and manage data files. Understanding the basic file processing cycle is essential for developing robust COBOL applications that work with external data sources.

The File Processing Cycle

Every file operation in COBOL follows a standard cycle:

  1. OPEN - Establish connection to the file
  2. READ/WRITE/REWRITE/DELETE - Perform data operations
  3. CLOSE - Terminate the file connection
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
IDENTIFICATION DIVISION. PROGRAM-ID. FILE-PROCESSING-EXAMPLE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS CUSTOMER-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 80 CHARACTERS. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(35). 05 CUSTOMER-STATUS PIC X. WORKING-STORAGE SECTION. 01 CUSTOMER-STATUS PIC XX. 01 EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM OPEN-FILE PERFORM PROCESS-RECORDS UNTIL END-OF-FILE PERFORM CLOSE-FILE STOP RUN. OPEN-FILE. OPEN INPUT CUSTOMER-FILE IF CUSTOMER-STATUS NOT = "00" DISPLAY "Error opening file: " CUSTOMER-STATUS STOP RUN END-IF. PROCESS-RECORDS. READ CUSTOMER-FILE AT END MOVE "Y" TO EOF-FLAG NOT AT END PERFORM PROCESS-CUSTOMER-RECORD END-READ. PROCESS-CUSTOMER-RECORD. DISPLAY "Processing customer: " CUSTOMER-ID * Add your processing logic here. CLOSE-FILE. CLOSE CUSTOMER-FILE IF CUSTOMER-STATUS NOT = "00" DISPLAY "Error closing file: " CUSTOMER-STATUS END-IF.

This example demonstrates the basic file processing cycle: OPEN, READ (in a loop), and CLOSE. Notice the error checking after each file operation using the FILE STATUS field.

File Access Modes

COBOL supports different access modes that determine how you can interact with files:

Access ModeDescriptionOperations Allowed
SEQUENTIALRecords are processed in orderREAD, WRITE (for output files)
RANDOMRecords are accessed by key or positionREAD, WRITE, REWRITE, DELETE
DYNAMICCombines sequential and random accessAll operations with START capability

File Opening Modes

The way you open a file determines what operations you can perform:

cobol
1
2
3
4
5
6
7
8
9
10
11
* Read-only access OPEN INPUT file-name * Write-only access (creates new file or overwrites existing) OPEN OUTPUT file-name * Read and write access (for updating existing files) OPEN I-O file-name * Append mode (adds records to existing file) OPEN EXTEND file-name

Choose the appropriate opening mode based on your processing requirements. I-O mode is commonly used for maintenance programs that need to update existing records.

READ Operations

The READ statement is used to retrieve records from files. COBOL provides several variations of the READ statement to handle different access patterns and file organizations. Understanding these variations is crucial for effective file processing.

Sequential READ

The most common form of READ is sequential reading, which processes records in the order they appear in the file:

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
* Basic sequential READ with AT END handling READ file-name AT END MOVE "Y" TO EOF-FLAG NOT AT END PERFORM PROCESS-RECORD END-READ * READ with INTO clause (copies record to working storage) READ file-name INTO working-storage-record AT END MOVE "Y" TO EOF-FLAG NOT AT END PERFORM PROCESS-RECORD END-READ * READ with file status checking READ file-name AT END MOVE "Y" TO EOF-FLAG NOT AT END IF file-status = "00" PERFORM PROCESS-RECORD ELSE DISPLAY "Read error: " file-status END-IF END-READ

The AT END clause is essential for sequential reading to detect when you've reached the end of the file. The NOT AT END clause contains the logic to process each record.

Random READ

For indexed and relative files, you can read specific records by key or position:

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
* READ by key (for indexed files) MOVE "12345" TO CUSTOMER-KEY READ CUSTOMER-FILE INVALID KEY DISPLAY "Customer not found: " CUSTOMER-KEY NOT INVALID KEY PERFORM PROCESS-CUSTOMER END-READ * READ by relative record number (for relative files) MOVE 100 TO RELATIVE-RECORD-NUMBER READ RELATIVE-FILE INVALID KEY DISPLAY "Record not found at position: " RELATIVE-RECORD-NUMBER NOT INVALID KEY PERFORM PROCESS-RECORD END-READ * READ with file status for random access MOVE "12345" TO CUSTOMER-KEY READ CUSTOMER-FILE INVALID KEY EVALUATE CUSTOMER-STATUS WHEN "23" DISPLAY "Record not found" WHEN "30" DISPLAY "Permanent error" WHEN OTHER DISPLAY "Unexpected error: " CUSTOMER-STATUS END-EVALUATE NOT INVALID KEY PERFORM PROCESS-CUSTOMER END-READ

Random READ uses the INVALID KEY clause instead of AT END. The INVALID KEY clause is executed when the specified key or position doesn't exist in the file.

READ NEXT (Dynamic Access)

For files opened with DYNAMIC access mode, you can combine random and sequential access:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
* First, position the file at a specific key MOVE "10000" TO CUSTOMER-KEY START CUSTOMER-FILE KEY IS GREATER THAN CUSTOMER-KEY INVALID KEY DISPLAY "Start position not found" NOT INVALID KEY * Now read sequentially from this position PERFORM READ-SEQUENTIAL-RECORDS END-START READ-SEQUENTIAL-RECORDS. PERFORM UNTIL END-OF-FILE READ CUSTOMER-FILE NEXT AT END MOVE "Y" TO EOF-FLAG NOT AT END PERFORM PROCESS-CUSTOMER END-READ END-PERFORM.

READ NEXT is used after a START statement to read records sequentially from the positioned location. This is useful for processing subsets of data or implementing range queries.

READ Statement Variations

VariationUse CaseFile OrganizationAccess Mode
READ file-nameBasic sequential readingAllSEQUENTIAL
READ file-name INTO ws-recordRead with automatic copyAllSEQUENTIAL
READ file-name (with key)Random access by keyINDEXEDRANDOM/DYNAMIC
READ file-name NEXTSequential after STARTINDEXEDDYNAMIC
READ file-name (with RRN)Random access by positionRELATIVERANDOM/DYNAMIC

WRITE Operations

The WRITE statement is used to add new records to files. Unlike READ operations, WRITE operations are generally simpler but require careful attention to file organization and access mode requirements.

Basic WRITE Statement

The most common form of WRITE adds a record to the end of a file:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
* Basic WRITE for sequential files MOVE "12345" TO CUSTOMER-ID MOVE "JOHN DOE" TO CUSTOMER-NAME MOVE "123 MAIN ST" TO CUSTOMER-ADDRESS MOVE "A" TO CUSTOMER-STATUS WRITE CUSTOMER-RECORD * WRITE with FROM clause (copies from working storage) MOVE "12345" TO WS-CUSTOMER-ID MOVE "JOHN DOE" TO WS-CUSTOMER-NAME MOVE "123 MAIN ST" TO WS-CUSTOMER-ADDRESS MOVE "A" TO WS-CUSTOMER-STATUS WRITE CUSTOMER-RECORD FROM WS-CUSTOMER-RECORD * WRITE with error handling WRITE CUSTOMER-RECORD INVALID KEY DISPLAY "Write error occurred" NOT INVALID KEY DISPLAY "Record written successfully" END-WRITE

The WRITE statement transfers data from the record description to the file. The FROM clause allows you to specify a different source for the data.

WRITE for Different File Organizations

The behavior of WRITE varies depending on the file organization:

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
* Sequential files - records are added at the end OPEN OUTPUT SEQUENTIAL-FILE MOVE "DATA1" TO RECORD-FIELD WRITE SEQUENTIAL-RECORD MOVE "DATA2" TO RECORD-FIELD WRITE SEQUENTIAL-RECORD CLOSE SEQUENTIAL-FILE * Indexed files - records are inserted in key order OPEN OUTPUT INDEXED-FILE MOVE "10001" TO CUSTOMER-KEY MOVE "ALICE SMITH" TO CUSTOMER-NAME WRITE CUSTOMER-RECORD MOVE "10000" TO CUSTOMER-KEY MOVE "BOB JONES" TO CUSTOMER-NAME WRITE CUSTOMER-RECORD * This will be inserted before Alice CLOSE INDEXED-FILE * Relative files - records are written at specified positions OPEN OUTPUT RELATIVE-FILE MOVE 1 TO RELATIVE-RECORD-NUMBER MOVE "FIRST RECORD" TO RECORD-DATA WRITE RELATIVE-RECORD MOVE 5 TO RELATIVE-RECORD-NUMBER MOVE "FIFTH RECORD" TO RECORD-DATA WRITE RELATIVE-RECORD CLOSE RELATIVE-FILE

Sequential files append records in the order written. Indexed files maintain key order automatically. Relative files allow you to specify the exact position for each record.

WRITE with ADVANCING

For line sequential files (text files), you can control line spacing:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
* WRITE with different advancing options OPEN OUTPUT REPORT-FILE * Write with single line advance (default) WRITE REPORT-LINE * Write with double spacing WRITE REPORT-LINE AFTER ADVANCING 2 LINES * Write with page advance WRITE REPORT-LINE AFTER ADVANCING PAGE * Write without advancing (overwrite current line) WRITE REPORT-LINE BEFORE ADVANCING 1 LINE * Write with specific line count WRITE REPORT-LINE AFTER ADVANCING 5 LINES CLOSE REPORT-FILE

The ADVANCING clause is primarily used for report generation and text file formatting. It controls how many lines to advance after writing each record.

WRITE Statement Requirements

File OrganizationRequired Opening ModeKey RequirementsCommon Errors
SEQUENTIALOUTPUT or EXTENDNoneOpening existing file with OUTPUT
INDEXEDOUTPUT or I-OUnique key valuesDuplicate keys
RELATIVEOUTPUT or I-OValid record numbersInvalid record numbers
LINE SEQUENTIALOUTPUT or EXTENDText dataBinary data in text files

REWRITE and DELETE Operations

REWRITE and DELETE operations are used to modify existing records in files. These operations require the file to be opened for I-O (Input-Output) mode and are typically used in maintenance programs.

REWRITE Statement

The REWRITE statement replaces an existing record that was previously read from the file:

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
* Basic REWRITE operation OPEN I-O CUSTOMER-FILE * First, read the record to be updated MOVE "12345" TO CUSTOMER-KEY READ CUSTOMER-FILE INVALID KEY DISPLAY "Customer not found" NOT INVALID KEY * Modify the record data MOVE "JANE DOE" TO CUSTOMER-NAME MOVE "456 OAK AVE" TO CUSTOMER-ADDRESS * Replace the record REWRITE CUSTOMER-RECORD INVALID KEY DISPLAY "Rewrite failed" NOT INVALID KEY DISPLAY "Record updated successfully" END-REWRITE END-READ CLOSE CUSTOMER-FILE * REWRITE with FROM clause READ CUSTOMER-FILE INVALID KEY DISPLAY "Customer not found" NOT INVALID KEY * Prepare updated data in working storage MOVE CUSTOMER-RECORD TO WS-UPDATED-RECORD MOVE "NEW ADDRESS" TO WS-CUSTOMER-ADDRESS * Rewrite using working storage data REWRITE CUSTOMER-RECORD FROM WS-UPDATED-RECORD END-READ

REWRITE can only be used after a successful READ operation. The record being rewritten must exist in the file, and the key values (for indexed files) cannot be changed.

DELETE Statement

The DELETE statement removes a record from the file:

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
* DELETE operation for indexed files OPEN I-O CUSTOMER-FILE * Read the record to be deleted MOVE "12345" TO CUSTOMER-KEY READ CUSTOMER-FILE INVALID KEY DISPLAY "Customer not found" NOT INVALID KEY * Delete the record DELETE CUSTOMER-FILE INVALID KEY DISPLAY "Delete failed" NOT INVALID KEY DISPLAY "Record deleted successfully" END-DELETE END-READ CLOSE CUSTOMER-FILE * DELETE for relative files OPEN I-O RELATIVE-FILE MOVE 100 TO RELATIVE-RECORD-NUMBER READ RELATIVE-FILE INVALID KEY DISPLAY "Record not found" NOT INVALID KEY DELETE RELATIVE-FILE DISPLAY "Record deleted" END-READ CLOSE RELATIVE-FILE

Like REWRITE, DELETE requires a previous READ operation. The record is permanently removed from the file and cannot be recovered through normal COBOL operations.

Maintenance Program Example

Here's a complete example of a customer maintenance program that demonstrates REWRITE and DELETE:

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
IDENTIFICATION DIVISION. PROGRAM-ID. CUSTOMER-MAINTENANCE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT" ORGANIZATION IS INDEXED ACCESS MODE IS RANDOM RECORD KEY IS CUSTOMER-ID FILE STATUS IS CUSTOMER-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 80 CHARACTERS. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(35). 05 CUSTOMER-STATUS PIC X. WORKING-STORAGE SECTION. 01 CUSTOMER-STATUS PIC XX. 01 ACTION-CODE PIC X. 01 SEARCH-ID PIC 9(5). PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM PROCESS-ACTIONS UNTIL ACTION-CODE = "X" PERFORM FINALIZATION STOP RUN. INITIALIZATION. OPEN I-O CUSTOMER-FILE IF CUSTOMER-STATUS NOT = "00" DISPLAY "Error opening file: " CUSTOMER-STATUS STOP RUN END-IF. PROCESS-ACTIONS. DISPLAY "Enter action (U=Update, D=Delete, X=Exit): " ACCEPT ACTION-CODE EVALUATE ACTION-CODE WHEN "U" PERFORM UPDATE-CUSTOMER WHEN "D" PERFORM DELETE-CUSTOMER WHEN "X" CONTINUE WHEN OTHER DISPLAY "Invalid action" END-EVALUATE. UPDATE-CUSTOMER. DISPLAY "Enter customer ID to update: " ACCEPT SEARCH-ID MOVE SEARCH-ID TO CUSTOMER-ID READ CUSTOMER-FILE INVALID KEY DISPLAY "Customer not found" NOT INVALID KEY DISPLAY "Current name: " CUSTOMER-NAME DISPLAY "Enter new name: " ACCEPT CUSTOMER-NAME DISPLAY "Enter new address: " ACCEPT CUSTOMER-ADDRESS REWRITE CUSTOMER-RECORD INVALID KEY DISPLAY "Update failed: " CUSTOMER-STATUS NOT INVALID KEY DISPLAY "Customer updated successfully" END-REWRITE END-READ. DELETE-CUSTOMER. DISPLAY "Enter customer ID to delete: " ACCEPT SEARCH-ID MOVE SEARCH-ID TO CUSTOMER-ID READ CUSTOMER-FILE INVALID KEY DISPLAY "Customer not found" NOT INVALID KEY DISPLAY "Deleting customer: " CUSTOMER-NAME DELETE CUSTOMER-FILE INVALID KEY DISPLAY "Delete failed: " CUSTOMER-STATUS NOT INVALID KEY DISPLAY "Customer deleted successfully" END-DELETE END-READ. FINALIZATION. CLOSE CUSTOMER-FILE DISPLAY "Maintenance completed.".

This maintenance program allows users to update or delete customer records. Notice that both REWRITE and DELETE operations are preceded by a READ operation to locate the target record.

REWRITE and DELETE Requirements

OperationFile ModePrerequisiteFile OrganizationsCommon Errors
REWRITEI-OSuccessful READAll except LINE SEQUENTIALKey changes, file not open I-O
DELETEI-OSuccessful READINDEXED, RELATIVERecord not found, file not open I-O

File Status and Error Handling

Proper error handling is crucial for robust file processing. COBOL provides file status codes that indicate the success or failure of file operations, allowing programs to respond appropriately to various error conditions.

Common File Status Codes

File status codes are two-character values that indicate the result of file operations:

Status CodeMeaningCommon CausesTypical Response
"00"Successful operationNormal completionContinue processing
"10"End of fileNo more records to readEnd processing loop
"23"Record not foundInvalid key or positionDisplay error message
"30"Permanent errorFile corruption, hardware failureLog error, terminate
"35"File not foundFile doesn't existCreate file or exit
"37"File already existsOPEN OUTPUT on existing fileUse EXTEND or different name
"39"File organization mismatchWrong organization specifiedCheck file definition
"41"File already openOPEN on already open fileClose file first
"42"File not openI/O operation on closed fileOpen file first
"43"File not open for inputREAD on OUTPUT fileOpen file for INPUT or I-O
"44"File not open for outputWRITE on INPUT fileOpen file for OUTPUT or I-O

Error Handling Patterns

Here are common patterns for handling file errors in COBOL:

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
* Pattern 1: Check status after each operation OPEN INPUT CUSTOMER-FILE IF CUSTOMER-STATUS NOT = "00" EVALUATE CUSTOMER-STATUS WHEN "35" DISPLAY "File not found - creating new file" OPEN OUTPUT CUSTOMER-FILE WHEN "41" DISPLAY "File already open" CLOSE CUSTOMER-FILE OPEN INPUT CUSTOMER-FILE WHEN OTHER DISPLAY "Unexpected error: " CUSTOMER-STATUS STOP RUN END-EVALUATE END-IF * Pattern 2: Use EVALUATE for comprehensive error handling READ CUSTOMER-FILE AT END MOVE "Y" TO EOF-FLAG NOT AT END EVALUATE CUSTOMER-STATUS WHEN "00" PERFORM PROCESS-CUSTOMER WHEN "10" MOVE "Y" TO EOF-FLAG WHEN "23" DISPLAY "Record not found" WHEN "30" DISPLAY "Permanent error - terminating" STOP RUN WHEN OTHER DISPLAY "Unexpected read error: " CUSTOMER-STATUS END-EVALUATE END-READ * Pattern 3: Centralized error handling routine PERFORM CHECK-FILE-STATUS USING CUSTOMER-STATUS "CUSTOMER-FILE" CHECK-FILE-STATUS SECTION. USING STATUS-CODE, FILE-NAME. IF STATUS-CODE NOT = "00" AND STATUS-CODE NOT = "10" DISPLAY "Error in " FILE-NAME ": " STATUS-CODE PERFORM LOG-ERROR USING STATUS-CODE, FILE-NAME IF STATUS-CODE = "30" OR STATUS-CODE = "39" STOP RUN END-IF END-IF.

These patterns help ensure that file errors are handled consistently and appropriately throughout your COBOL programs. Always check file status after operations that can fail.

Best Practices for Error Handling

  • Always check file status after OPEN, READ, WRITE, REWRITE, DELETE, and CLOSE operations
  • Use meaningful error messages that help identify the problem
  • Log errors for debugging and audit purposes
  • Handle expected errors (like end-of-file) gracefully
  • Terminate the program for critical errors that cannot be recovered
  • Consider implementing retry logic for transient errors
  • Use consistent error handling patterns throughout your program

Exercises

Exercise 1: File Copy Program

Write a COBOL program that copies records from one sequential file to another. The program should:

  • Open both input and output files
  • Read records from the input file
  • Write records to the output file
  • Handle end-of-file condition
  • Include proper error handling

Solution
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. FILE-COPY. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT INPUT-FILE ASSIGN TO "INPUT.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS INPUT-STATUS. SELECT OUTPUT-FILE ASSIGN TO "OUTPUT.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS OUTPUT-STATUS. DATA DIVISION. FILE SECTION. FD INPUT-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 80 CHARACTERS. 01 INPUT-RECORD PIC X(80). FD OUTPUT-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 80 CHARACTERS. 01 OUTPUT-RECORD PIC X(80). WORKING-STORAGE SECTION. 01 FILE-STATUSES. 05 INPUT-STATUS PIC XX. 05 OUTPUT-STATUS PIC XX. 01 EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. 01 RECORD-COUNT PIC 9(5) VALUE ZERO. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM COPY-RECORDS UNTIL END-OF-FILE PERFORM FINALIZATION STOP RUN. INITIALIZATION. OPEN INPUT INPUT-FILE IF INPUT-STATUS NOT = "00" DISPLAY "Error opening input file: " INPUT-STATUS STOP RUN END-IF OPEN OUTPUT OUTPUT-FILE IF OUTPUT-STATUS NOT = "00" DISPLAY "Error opening output file: " OUTPUT-STATUS CLOSE INPUT-FILE STOP RUN END-IF. COPY-RECORDS. READ INPUT-FILE AT END MOVE "Y" TO EOF-FLAG NOT AT END IF INPUT-STATUS = "00" MOVE INPUT-RECORD TO OUTPUT-RECORD WRITE OUTPUT-RECORD IF OUTPUT-STATUS = "00" ADD 1 TO RECORD-COUNT ELSE DISPLAY "Error writing record: " OUTPUT-STATUS MOVE "Y" TO EOF-FLAG END-IF ELSE DISPLAY "Error reading record: " INPUT-STATUS MOVE "Y" TO EOF-FLAG END-IF END-READ. FINALIZATION. CLOSE INPUT-FILE CLOSE OUTPUT-FILE DISPLAY "Copy completed. Records processed: " RECORD-COUNT.

This program demonstrates proper file handling with error checking at each step.

Exercise 2: Customer Search Program

Create a program that searches for customers in an indexed file by customer ID. The program should:

  • Accept a customer ID from the user
  • Search for the customer in an indexed file
  • Display customer information if found
  • Display an appropriate message if not found
  • Allow multiple searches until the user chooses to exit

Solution
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
IDENTIFICATION DIVISION. PROGRAM-ID. CUSTOMER-SEARCH. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT" ORGANIZATION IS INDEXED ACCESS MODE IS RANDOM RECORD KEY IS CUSTOMER-ID FILE STATUS IS CUSTOMER-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 80 CHARACTERS. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(35). 05 CUSTOMER-STATUS PIC X. WORKING-STORAGE SECTION. 01 CUSTOMER-STATUS PIC XX. 01 SEARCH-ID PIC 9(5). 01 CONTINUE-FLAG PIC X VALUE 'Y'. 88 CONTINUE-SEARCH VALUE 'Y'. 88 END-SEARCH VALUE 'N'. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM SEARCH-LOOP UNTIL END-SEARCH PERFORM FINALIZATION STOP RUN. INITIALIZATION. OPEN INPUT CUSTOMER-FILE IF CUSTOMER-STATUS NOT = "00" DISPLAY "Error opening customer file: " CUSTOMER-STATUS STOP RUN END-IF. SEARCH-LOOP. DISPLAY "Enter customer ID to search (or 00000 to exit): " ACCEPT SEARCH-ID IF SEARCH-ID = 00000 MOVE "N" TO CONTINUE-FLAG ELSE PERFORM SEARCH-CUSTOMER DISPLAY "Search another customer? (Y/N): " ACCEPT CONTINUE-FLAG END-IF. SEARCH-CUSTOMER. MOVE SEARCH-ID TO CUSTOMER-ID READ CUSTOMER-FILE INVALID KEY DISPLAY "Customer " SEARCH-ID " not found" NOT INVALID KEY IF CUSTOMER-STATUS = "00" DISPLAY "Customer found:" DISPLAY " ID: " CUSTOMER-ID DISPLAY " Name: " CUSTOMER-NAME DISPLAY " Address: " CUSTOMER-ADDRESS DISPLAY " Status: " CUSTOMER-STATUS ELSE DISPLAY "Error reading customer: " CUSTOMER-STATUS END-IF END-READ. FINALIZATION. CLOSE CUSTOMER-FILE DISPLAY "Search program completed.".

This program demonstrates random access to indexed files and proper error handling.

Exercise 3: File Update Program

Write a program that updates customer records in an indexed file. The program should:

  • Read a transaction file containing updates
  • For each transaction, find the customer in the master file
  • Update the customer record if found
  • Write unmatched transactions to an error file
  • Provide a summary of processing results

Solution
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
IDENTIFICATION DIVISION. PROGRAM-ID. CUSTOMER-UPDATE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT TRANSACTION-FILE ASSIGN TO "TRANS.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS TRANS-STATUS. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT" ORGANIZATION IS INDEXED ACCESS MODE IS RANDOM RECORD KEY IS CUSTOMER-ID FILE STATUS IS CUSTOMER-STATUS. SELECT ERROR-FILE ASSIGN TO "ERROR.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS ERROR-STATUS. DATA DIVISION. FILE SECTION. FD TRANSACTION-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 50 CHARACTERS. 01 TRANSACTION-RECORD. 05 TRANS-CUSTOMER-ID PIC 9(5). 05 TRANS-NAME PIC X(30). 05 TRANS-ADDRESS PIC X(15). FD CUSTOMER-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 80 CHARACTERS. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(35). 05 CUSTOMER-STATUS PIC X. FD ERROR-FILE LABEL RECORDS ARE STANDARD RECORD CONTAINS 50 CHARACTERS. 01 ERROR-RECORD PIC X(50). WORKING-STORAGE SECTION. 01 FILE-STATUSES. 05 TRANS-STATUS PIC XX. 05 CUSTOMER-STATUS PIC XX. 05 ERROR-STATUS PIC XX. 01 EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. 01 COUNTERS. 05 TRANS-COUNT PIC 9(5) VALUE ZERO. 05 UPDATE-COUNT PIC 9(5) VALUE ZERO. 05 ERROR-COUNT PIC 9(5) VALUE ZERO. PROCEDURE DIVISION. MAIN-PROCESS. PERFORM INITIALIZATION PERFORM PROCESS-TRANSACTIONS UNTIL END-OF-FILE PERFORM FINALIZATION STOP RUN. INITIALIZATION. OPEN INPUT TRANSACTION-FILE OPEN I-O CUSTOMER-FILE OPEN OUTPUT ERROR-FILE IF TRANS-STATUS NOT = "00" OR CUSTOMER-STATUS NOT = "00" OR ERROR-STATUS NOT = "00" DISPLAY "Error opening files" STOP RUN END-IF. PROCESS-TRANSACTIONS. READ TRANSACTION-FILE AT END MOVE "Y" TO EOF-FLAG NOT AT END ADD 1 TO TRANS-COUNT PERFORM UPDATE-CUSTOMER END-READ. UPDATE-CUSTOMER. MOVE TRANS-CUSTOMER-ID TO CUSTOMER-ID READ CUSTOMER-FILE INVALID KEY PERFORM WRITE-ERROR-RECORD NOT INVALID KEY IF CUSTOMER-STATUS = "00" MOVE TRANS-NAME TO CUSTOMER-NAME MOVE TRANS-ADDRESS TO CUSTOMER-ADDRESS REWRITE CUSTOMER-RECORD INVALID KEY PERFORM WRITE-ERROR-RECORD NOT INVALID KEY ADD 1 TO UPDATE-COUNT END-REWRITE ELSE PERFORM WRITE-ERROR-RECORD END-IF END-READ. WRITE-ERROR-RECORD. MOVE TRANSACTION-RECORD TO ERROR-RECORD WRITE ERROR-RECORD ADD 1 TO ERROR-COUNT. FINALIZATION. CLOSE TRANSACTION-FILE CLOSE CUSTOMER-FILE CLOSE ERROR-FILE DISPLAY "Processing Summary:" DISPLAY " Transactions processed: " TRANS-COUNT DISPLAY " Records updated: " UPDATE-COUNT DISPLAY " Errors: " ERROR-COUNT.

This program demonstrates file maintenance operations with comprehensive error handling and processing statistics.

Test Your Knowledge

1. What is the correct sequence of file operations in COBOL?

  • READ, OPEN, WRITE, CLOSE
  • OPEN, READ/WRITE, CLOSE
  • WRITE, OPEN, READ, CLOSE
  • CLOSE, OPEN, READ, WRITE

2. What does the AT END clause in a READ statement do?

  • It specifies what to do when a file is opened
  • It handles the end-of-file condition
  • It defines the file organization
  • It sets the file status

3. Which file organization allows both sequential and random access?

  • Sequential files only
  • Indexed files
  • Relative files only
  • Line sequential files

4. What is the purpose of the FILE STATUS clause?

  • To define the file organization
  • To specify the record format
  • To capture the result of file operations
  • To set the file permissions

5. When should you use the REWRITE statement?

  • To create a new file
  • To update an existing record in a file opened for I-O
  • To delete a file
  • To append records to a file

Frequently Asked Questions