Write Record into Variable Length Indexed File
Write Record into Variable Length Indexed File Example
Scenario - Writing a record into the variable length KSDS 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 0000035000 E0005EMPLOYEE5 SE 0000040000 EMP 5 **** End of data ****
Code -
----+----1----+----2----+----3----+----4----+----5----+
IDENTIFICATION DIVISION.
PROGRAM-ID. INDFILWR.
AUTHOR. MTH.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT EMPFILE ASSIGN TO INPUT01
ORGANIZATION IS INDEXED
ACCESS MODE IS RANDOM
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).
PROCEDURE DIVISION.
* Opening the file for writing
OPEN I-O EMPFILE.
INITIALIZE EMP-RECORD80
* 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
MOVE 40 TO EMPREC-LEN
WRITE EMP-RECORD80.
IF WS-FS1 EQUAL ZERO
DISPLAY "Record inserted successfully"
ELSE
DISPLAY "Record insertion failed"
END-IF.
* Closing file
CLOSE EMPFILE.
STOP RUN.
Run JCL -
//MATEPKF JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID //* //STEP01 EXEC PGM=INDVFLWR //STEPLIB DD DSN=MATEPK.COBOL.LOADLIB,DISP=SHR //INPUT01 DD DSN=MATEPK.EMPL.VKSDS,DISP=SHR //SYSOUT DD SYSOUT=* //SYSIN DD * E0006 EMPLOYEE6 SE 0000040000 /*
Output -
Record inserted successfully
File after record insert -
Browse MATEPK.EMPL.VKSDS Top of 6 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 0000035000 E0005EMPLOYEE5 SE 0000040000 EMP 5 E0006EMPLOYEE6 SE 0000040000 **** End of data ****
Explaining Example -
In the above example:
- Variable length KSDS (MATEPK.EMPL.KSDS) file is used as an input file and file should be opened in I-O mode.
- File organization is INDEXED and accessing mode should be DYNAMIC.
- Program receives the record information from input stream (SYSIN DD *) and writes it into the file.