Reading Variable Length Indexed File Sequentially
Reading Variable Length Indexed File Sequentially Example
Scenario - Reading all the records sequentially from a variable length indexed file.
Input file -
Browse MATEPK.EMPL.VKSDS Top of 5 Command ===> Scroll CSR Type KSDS RBA Format CHAR Key Col 1 <===>----10---+----2----+----3----+----4----+----5----+----6----+----7----+---- **** Top of data **** 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 **** End of data ****
Code -
----+----1----+----2----+----3----+----4----+
IDENTIFICATION DIVISION.
PROGRAM-ID. INDVFLSQ.
AUTHOR. MTH.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
* EMPFILE Definition
SELECT EMPFILE ASSIGN TO INPUT01
ORGANIZATION IS INDEXED
ACCESS MODE IS SEQUENTIAL
RECORD KEY IS EMP-ID
FILE STATUS IS WS-FS1.
DATA DIVISION.
FILE SECTION.
* EMPFILE structure definition
FD EMPFILE
RECORD VARYING FROM 40 TO 80 CHARACTERS
DEPENDING ON EMPREC-LEN.
* EMPFILE record structure definition
01 EMP-RECORD80.
05 EMP-ID PIC X(05).
05 EMP-NAME PIC X(15).
05 EMP-DESG PIC X(10).
05 EMP-SALARY PIC 9(10).
05 FILLER PIC X(40).
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 -
//MATEPKVR JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID //* //STEP01 EXEC PGM=INDVFLSQ //STEPLIB DD DSN=MATEPK.COBOL.LOADLIB,DISP=SHR //INPUT01 DD DSN=MATEPK.EMPL.VKSDS,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 indexed file (KSDS) is used as an input file and trying to read all the records sequentially.
- ORGANIZATION should be indexed 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.