COBOL Write Record into Fixed Length Indexed File Example
Scenario - Writing a record into the fixed length KSDS file.
Input file -
Browse           MATEPK.EMPL.KSDS
Command ===>
                            Type KSDS     RBA
Key                                          Col 1
<===>----10---+----2----+----3----+----4----+--
****  Top of data  ****
E0001EMPLOYEE1     DIR       LOC1 0000100000
E0002EMPLOYEE2     MGR  DEPT1LOC1 0000080000
E0003EMPLOYEE3     MGR  DEPT2LOC2 0000075000
E0004EMPLOYEE4     TL   DEPT1LOC1 0000050000
E0006EMPLOYEE6     SE   DEPT1LOC1 0000034000
E0007EMPLOYEE7     SSE  DEPT2LOC2 0000046000
****  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.
       FD EMPFILE
           RECORD CONTAINS 47  CHARACTERS
           BLOCK  CONTAINS 470 CHARACTERS
           DATA RECORD     IS EMPFILE-RECORD.
       01 EMPFILE-RECORD.
          05 EMP-ID        PIC X(05).
          05 EMP-NAME      PIC X(14).
          05 EMP-DESG      PIC X(05).
          05 EMP-DEPT      PIC X(05).
          05 EMP-LOC       PIC X(05).
          05 EMP-SALARY    PIC 9(10).
          05 FILLER        PIC X(03).
       WORKING-STORAGE SECTION.
       01 WS-FS1        PIC 9(02).
       PROCEDURE DIVISION.
      * Opening the file for writing
           OPEN I-O EMPFILE.
           INITIALIZE EMPFILE-RECORD
      * Receiving all the information of the record 
           ACCEPT EMP-ID.
           ACCEPT EMP-NAME.
           ACCEPT EMP-DESG.
           ACCEPT EMP-DEPT.
           ACCEPT EMP-LOC.
           ACCEPT EMP-SALARY.
      * Writing record into file and validation
           WRITE EMPFILE-RECORD.
           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=INDFILWR //STEPLIB DD DSN=MATEPK.COBOL.LOADLIB,DISP=SHR //INPUT01 DD DSN=MATEPK.EMPL.KSDS,DISP=SHR //SYSOUT DD SYSOUT=* //SYSIN DD * E0005 EMPLOYEE5 SSE DEPT2 LOC1 0000040000 /*
Output -
Record inserted successfully
File after record insert -
Browse           MATEPK.EMPL.KSDS              
Command ===>                                   
                            Type KSDS     RBA  
Key                                          Co
<===>----10---+----2----+----3----+----4----+--
****  Top of data  ****                        
E0001EMPLOYEE1     DIR       LOC1 0000100000   
E0002EMPLOYEE2     MGR  DEPT1LOC1 0000080000   
E0003EMPLOYEE3     MGR  DEPT2LOC2 0000075000   
E0004EMPLOYEE4     TL   DEPT1LOC1 0000050000   
E0005EMPLOYEE5     SSE  DEPT2LOC1 0000040000   
E0006EMPLOYEE6     SE   DEPT1LOC1 0000034000   
E0007EMPLOYEE7     SSE  DEPT2LOC2 0000040000   
****  End of data  ****                        
Explaining Example -
In the above example:
- Fixed 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.
