File Processing
COBOL file processing refers to the operations carried out on data files, like reading, writing, updating, and deleting records.
When writing a COBOL program, it's important to choose the appropriate file processing method based on the nature of the data and the operations that will be performed on it.
Below are the file processing statements -
- OPEN File
- READ
- WRITE
- REWRITE
- DELETE
- START & READ NEXT
- CLOSE File
OPEN File
OPEN statement establishes a connection between the logical file and its associated physical file. It opens the file for subsequent processing (e.g., reading, writing, updating).
OPEN opening-mode file-name.
- opening-mode - Specifies the file opening mode. Mode is mandatory with OPEN statement.
- file-name - Specifies 8-character logical file name defined inside the program.
Opening Modes -
Mode | Description |
---|---|
INPUT | For reading operations only. |
OUTPUT | For writing operations only. If a file already exists, ts contents overwritten. |
I-O | For both reading and writing. Useful for updating files. |
EXTEND | For appending records to an existing file. It applies for sequential access files only. |
Example - Opening EMPFILE for reading.
OPEN INPUT EMPFILE.
READ Statement
READ statement is used to retrieve a record from the file. At a time, only one record is retrieved from the file. File should be opened in INPUT or I-O mode.
SEQUENTIAL Read (for sequential, indexed and relative files) -
READ logical-file-name
[INTO ws-record-name]
[AT END statements-set1]
[NOT AT END statements-set2]
[END-READ].
RANDOM Read (for indexed and relative files) -
READ logical-file-name
[INTO ws-record-name]
[KEY IS key-variable]
[INVALID KEY statements-set3]
[NOT INVALID KEY statements-set4]
[END-READ].
Example - Reading all the records from a PS file.
Input file -
BROWSE MATESY.EMPLOYEE.INPFILE Line 00000000 Col 001 080 Command ===> Scroll ===> CSR ----+----1----+----2----+----3----+----4----+----5----+----6----+----7----+----8 ********************************* Top of Data ********************************** E0001EMPLOYEE1 MANAGER 0000200000 E0002EMPLOYEE2 TL 0000150000 E0003EMPLOYEE3 SE 0000050000 E0004EMPLOYEE4 SSE 0000040000 E0005EMPLOYEE5 SE 0000045000 ******************************** Bottom of Data ********************************
Code -
----+----1----+----2----+----3----+----4----+
...
PROCEDURE DIVISION.
* Opens the file for reading
OPEN INPUT EMPFILE.
* Reading and displying the records until end of file
SET WS-NOT-EOF TO TRUE.
PERFORM UNTIL WS-EOF
READ EMPFILE
AT END SET WS-EOF TO TRUE
NOT AT END DISPLAY EMPFILE-RECORD
END-READ
END-PERFORM.
* Closing the file
CLOSE EMPFILE.
...
Run JCL -
//MATESYF JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID //* //STEP01 EXEC PGM=SEQFILE //STEPLIB DD DSN=MATESY.COBOL.LOADLIB,DISP=SHR //INPUT01 DD DSN=MATESY.EMPLOYEE.INPFILE,DISP=SHR //SYSOUT DD SYSOUT=*
Output -
E0001EMPLOYEE1 MANAGER 0000200000 E0002EMPLOYEE2 TL 0000150000 E0003EMPLOYEE3 SE 0000050000 E0004EMPLOYEE4 SSE 0000040000 E0005EMPLOYEE5 SE 0000045000
WRITE Statement
WRITE statement is used to add a record to the file. At a time, only one record is written to the file.
For Sequential files -
WRITE record-name
[FROM ws-record-name]
[END-WRITE].
For Index and Relative files -
WRITE record-name
[FROM ws-record-name]
[INVALID KEY statements-set1]
[NOT INVALID KEY statements-set2]
[END-WRITE].
Example - Below example describes how to write a new record into a new PS file.
Code -
----+----1----+----2----+----3----+----4----+
...
PROCEDURE DIVISION.
* Opening the file for writing
OPEN OUTPUT EMPFILE.
INITIALIZE EMPFILE-RECORD
* Receiving all the information of the record
ACCEPT EMP-ID.
ACCEPT EMP-NAME.
ACCEPT EMP-DESG.
ACCEPT EMP-SALARY.
* Writing record into file and validation
WRITE EMPFILE-RECORD.
IF WS-FS1 EQUAL ZERO
DISPLAY "RECORD WRITTEN"
ELSE
DISPLAY "RECORD WRITING FAILED"
END-IF.
* Closing file
CLOSE EMPFILE.
...
Run JCL -
//MATESYF JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID //* //STEP01 EXEC PGM=FILEWRIT //STEPLIB DD DSN=MATESY.COBOL.LOADLIB,DISP=SHR //INPUT01 DD DSN=MATESY.EMPLOYEE.INPFILE1, // DISP=(NEW,CATLG,DELETE), // SPACE=(TRK,(1,1),RLSE), // UNIT=SYSDA, // DCB=(DSORG=PS,RECFM=FB,LRECL=80,BLKSIZE=800) //SYSOUT DD SYSOUT=* //SYSIN DD * E0006 EMPLOYEE6 SE 0000040000 /*
Output -
RECORD WRITTEN
MATESY.EMPLOYEE.INPFILE1 -
E0006EMPLOYEE6 SE 0000040000
REWRITE Statement
REWRITE statement is used to replace the content of a previously read record with new data. At a time, only one record is replaced in the file.
REWRITE record-name
[FROM ws-record-name]
[INVALID KEY statements-set1]
[NOT INVALID KEY statements-set2]
[END-REWRITE].
Example - Rewriting a record by increasing the salary by 5000 for E0006 employee.
Input file (KSDS) -
Browse MATESY.EMPLOYEE.DETAILS Command ===> Type KSDS Key <===>----10---+----2----+----3----+----4 **** Top of data **** E0001EMPLOYEE1 MANAGER 0000200000 E0002EMPLOYEE2 TL 0000150000 E0003EMPLOYEE3 SE 0000050000 E0004EMPLOYEE4 SSE 0000040000 E0005EMPLOYEE5 SE 0000045000 E0006EMPLOYEE6 SE 0000040000 **** End of data ****
Code -
----+----1----+----2----+----3----+----4----+
...
PROCEDURE DIVISION.
* Opening file for rewrite
OPEN I-O EMPFILE.
* Reading the record that need to update
MOVE 'E0006' TO EMP-ID.
READ EMPFILE
KEY IS EMP-ID
INVALID KEY DISPLAY "RECORD NOT FOUND"
NOT INVALID KEY PERFORM 1000-REWRITE-REC
THRU 1000-EXIT
END-READ.
* Closing file
CLOSE EMPFILE.
STOP RUN.
1000-REWRITE-REC.
* Increased salary by 5000
COMPUTE EMP-SALARY = EMP-SALARY + 5000
* Rewriting the record
REWRITE EMPFILE-RECORD
INVALID KEY DISPLAY "RECORD NOT UPDATED"
NOT INVALID KEY DISPLAY "RECORD UPDATED"
END-REWRITE.
1000-EXIT.
EXIT.
Run JCL -
//MATESYF JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID //* //STEP01 EXEC PGM=FILERWRT //STEPLIB DD DSN=MATESY.COBOL.LOADLIB,DISP=SHR //INPUT01 DD DSN=MATESY.EMPLOYEE.DETAILS,DISP=SHR //SYSOUT DD SYSOUT=*
Output -
RECORD UPDATED
Output file (KSDS) -
Browse MATESY.EMPLOYEE.DETAILS Command ===> Type KSDS Key <===>----10---+----2----+----3----+----4 **** Top of data **** E0001EMPLOYEE1 MANAGER 0000200000 E0002EMPLOYEE2 TL 0000150000 E0003EMPLOYEE3 SE 0000050000 E0004EMPLOYEE4 SSE 0000040000 E0005EMPLOYEE5 SE 0000045000 E0006EMPLOYEE6 SE 0000045000 **** End of data ****
DELETE Statement
DELETE statement removes a record from an indexed or relative file. After the successful execution of a DELETE statement, the record is removed from the file and can no longer be available.
DELETE logical-file-name
[INVALID KEY statements-set1]
[NOT INVALID KEY statements-set2]
[END-DELETE].
Example - Deleting a record from KSDS file using key (E0006).
Input File (KSDS) -
Browse MATESY.EMPLOYEE.DETAILS Command ===> Type KSDS Key <===>----10---+----2----+----3----+----4 **** Top of data **** E0001EMPLOYEE1 MANAGER 0000200000 E0002EMPLOYEE2 TL 0000150000 E0003EMPLOYEE3 SE 0000050000 E0004EMPLOYEE4 SSE 0000040000 E0005EMPLOYEE5 SE 0000045000 E0006EMPLOYEE6 SE 0000045000 **** End of data ****
Code -
----+----1----+----2----+----3----+----4----+
...
PROCEDURE DIVISION.
* Opening file for DELETE
OPEN I-O EMPFILE.
* Deleting the record
MOVE 'E0006' TO EMP-ID.
DELETE EMPFILE
INVALID KEY DISPLAY "RECORD NOT FOUND"
NOT INVALID KEY DISPLAY "RECORD SUCCESSFULLY DELETED"
END-DELETE.
* Closing file
CLOSE EMPFILE.
...
Run JCL -
//MATESYF JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID //* //STEP01 EXEC PGM=FILEDEL //STEPLIB DD DSN=MATESY.COBOL.LOADLIB,DISP=SHR //INPUT01 DD DSN=MATESY.EMPLOYEE.DETAILS,DISP=SHR //SYSOUT DD SYSOUT=*
Output -
RECORD SUCCESSFULLY DELETED
File after deletion -
Browse MATESY.EMPLOYEE.DETAILS Command ===> Type KSDS Key <===>----10---+----2----+----3----+----4 **** Top of data **** E0001EMPLOYEE1 MANAGER 0000200000 E0002EMPLOYEE2 TL 0000150000 E0003EMPLOYEE3 SE 0000050000 E0004EMPLOYEE4 SSE 0000040000 E0005EMPLOYEE5 SE 0000045000 **** End of data ****
START & READ NEXT –
START -
START is used to set the file pointer to read the record. START won't retrieve any record and only sets the pointer before beginning a sequence of READ operations.
START logical-file-name
[KEY IS {EQUAL TO | GREATER THAN | LESS THAN | NOT ...} ws-key-value]
[INVALID KEY statements-set1]
[NOT INVALID KEY statements-set2]
[END-START].
READ NEXT
READ NEXT statement is used to read the next record from the current reading position of the file. At a time, only one record is retrieved from the file.
READ logical-file-name
[NEXT RECORD]
[INTO ws-record-name]
[AT END statements-set1]
[NOT AT END statements-set2]
[END-READ].
Example - Reading sequentially from record key 'E0003' in forward direction.
Input File (KSDS) -
Browse MATESY.EMPLOYEE.DETAILS Command ===> Type KSDS Key <===>----10---+----2----+----3----+----4 **** Top of data **** E0001EMPLOYEE1 MANAGER 0000200000 E0002EMPLOYEE2 TL 0000150000 E0003EMPLOYEE3 SE 0000050000 E0004EMPLOYEE4 SSE 0000040000 E0005EMPLOYEE5 SE 0000045000 E0006EMPLOYEE6 SE 0000045000 **** End of data ****
Code -
----+----1----+----2----+----3----+----4----+
...
PROCEDURE DIVISION.
* Opening file in INPUT mode
OPEN INPUT EMPFILE.
* Set the file pointer to read the record
MOVE 'E0003' TO EMP-ID.
START EMPFILE
KEY IS EQUAL TO EMP-ID
INVALID KEY DISPLAY "RECORD NOT FOUND"
NOT INVALID KEY PERFORM 1000-READ-EMPFILE
THRU 1000-EXIT
END-START.
* Closing file
CLOSE EMPFILE.
STOP RUN.
1000-READ-EMPFILE.
* Reading records sequentially using NEXT RECORD
* until end of the file
PERFORM UNTIL WS-EOF
READ EMPFILE
NEXT RECORD
AT END SET WS-EOF TO TRUE
NOT AT END DISPLAY EMPFILE-RECORD
END-READ
END-PERFORM.
1000-EXIT.
EXIT.
Run JCL -
//MATESYF JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID //* //STEP01 EXEC PGM=FILEBRFW //STEPLIB DD DSN=MATESY.COBOL.LOADLIB,DISP=SHR //INPUT01 DD DSN=MATESY.EMPLOYEE.INPFILE,DISP=SHR //SYSOUT DD SYSOUT=*
Output -
E0003EMPLOYEE3 SE 0000050000 E0004EMPLOYEE4 SSE 0000040000 E0005EMPLOYEE5 SE 0000045000 E0006EMPLOYEE6 SE 0000045000
CLOSE File
CLOSE statement is used to terminate the file processing and release the resources of the file.
CLOSE file-name.
Example - Closing EMPFILE.
CLOSE EMPFILE.