Reading Variable Length File Sequentially
Reading Variable Length File Sequentially Example
Scenario - Reading all the records sequentially from a variable length PS (Sequential) file.
Input file -
----+----1----+----2----+----3----+----4----+----5----+----6----+----7----+----8 E0001EMPLOYEE1 MANAGER 0000200000 EMPLOYEE RECORD 1 E0002EMPLOYEE2 TL 0000150000 EMP REC 2 E0003EMPLOYEE3 SE 0000050000 EMP 3 E0004EMPLOYEE4 SSE 0000040000 E0005EMPLOYEE5 SE 0000040000 EMP 5
Note!
Variable file record length should be actual record length + 4 bytes. For the above file, it should be 80 + 4 = 84 bytes.
Input file properties -
Data Set Name . . . . : MATEPK.EMPLOYEE.VINPFILE General Data Current Allocation Management class . . : **None** Allocated cylinders : 5 Storage class . . . : **None** Allocated extents . : 1 Volume serial . . . : DEVHD2 Device type . . . . : 3390 Data class . . . . . : **None** Organization . . . : PS Current Utilization Record format . . . : VB Used cylinders . . : 1 Record length . . . : 84 Used extents . . . : 1 Block size . . . . : 840 1st extent cylinders: 5 Secondary cylinders : 5 Dates Data set name type : Creation date . . . : 2024/05/16 SMS Compressible. . : NO Referenced date . . : 2024/05/16 Expiration date . . : ***None***
Code -
----+----1----+----2----+----3----+----4----+
IDENTIFICATION DIVISION.
PROGRAM-ID. SEQVFLRD.
AUTHOR. MTH.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
* EMPFILE Definition
SELECT EMPFILE ASSIGN TO INPUT01
ORGANIZATION IS SEQUENTIAL
ACCESS MODE IS SEQUENTIAL
FILE STATUS IS WS-FS1.
DATA DIVISION.
FILE SECTION.
* EMPFILE structure definition
FD EMPFILE
RECORD VARYING FROM 47 TO 80 CHARACTERS
DEPENDING ON EMPREC-LEN
RECORDING MODE IS V.
* EMPFILE record structure definition
01 EMP-RECORD80 PIC X(80).
WORKING-STORAGE SECTION.
01 WS-VAR.
05 EMPREC-LEN PIC 9(02).
05 WS-FS1 PIC 9(02).
05 WS-EOF-SW PIC X(01).
88 WS-EOF VALUE 'Y'.
88 WS-NOT-EOF VALUE 'N'.
PROCEDURE DIVISION.
* Opening EMPFILE for reading
OPEN INPUT EMPFILE.
* Loop for reading all records from EMPFILE
SET WS-NOT-EOF TO TRUE.
PERFORM UNTIL WS-EOF
READ EMPFILE
AT END SET WS-EOF TO TRUE
NOT AT END DISPLAY EMP-RECORD80(1:EMPREC-LEN)
END-READ
END-PERFORM.
* Closing EMPFILE
CLOSE EMPFILE.
STOP RUN.
Run JCL -
//MATEPKF JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID //* //STEP01 EXEC PGM=SEQVFLRD //STEPLIB DD DSN=MATEPK.COBOL.LOADLIB,DISP=SHR //INPUT01 DD DSN=MATEPK.EMPLOYEE.VINPFILE,DISP=SHR //SYSOUT DD SYSOUT=*
Output -
E0001EMPLOYEE1 MANAGER 0000200000 EMPLOYEE RECORD 1 E0002EMPLOYEE2 TL 0000150000 EMP REC 2 E0003EMPLOYEE3 SE 0000050000 EMP 3 E0004EMPLOYEE4 SSE 0000040000 E0005EMPLOYEE5 SE 0000040000 EMP 5
Explaining Example -
In the above example:
- Variable-length sequential file (PS file) is used as an input file and trying to read all the records sequentially.
- ORGANIZATION and ACCESS MODE should be sequential.
- File should declare with RECORD VARYING...DEPENDING clause to read the file record along with length.
- File reading starts from the first record and continue till the end of the file.