FILE REWRITE Statement


The 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.

Points to note -

  • The file should open in I-O mode to perform the REWRITE statement.
  • The REWRITE statement is used for all types of (sequential, indexed and relative) files.
  • A simple READ statement is used when the ACCESS MODE is SEQUENTIAL or RANDOM or DYNAMIC.

Syntax -

REWRITE record-name 
       [FROM ws-record-name]
           [INVALID KEY statements-set1]
       [NOT INVALID KEY statements-set2]
[END-REWRITE].
Note! All statements coded in [ ] are optional.

Parameters -

  • record-name - Refers to the record in the file that we wish to modify. It should have the data that has been read previously using the READ statement.
  • FROM ws-record-name - Specifies the working-storage record name from where the record should be replaced. If ignored, the data is directly taken from the record-name.
  • END-REWRITE - An optional phrase that marks the end of the REWRITE statement. END-REWRITE is not required when a REWRITE statement ends with a period.

Error Handling -

  • INVALID KEY - This phrase specifies the action to be taken if the record is not found (or if the key is invalid). The statements following INVALID KEY are executed in such cases. This is applicable to indexed or relative files.
  • NOT INVALID KEY - This phrase specifies the steps to be taken if the REWRITE is successful. This is applicable to indexed or relative files.
Note! If the FILE-STATUS clause is coded, the associated file status is updated when the REWRITE statement is executed.

Practical Example -


Scenario - Rewriting a record by increasing the salary by 5000 for E0006 employee.

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
E0006EMPLOYEE6      SE        0000040000
******************************** Bottom of Data ********************************

Code -

----+----1----+----2----+----3----+----4----+
       IDENTIFICATION DIVISION.
       PROGRAM-ID. FILERWRT.

       ENVIRONMENT DIVISION.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
           SELECT EMPFILE ASSIGN TO INPUT01  
           ORGANIZATION IS INDEXED
           ACCESS MODE  IS DYNAMIC
           RECORD KEY   IS EMP-ID
           FILE STATUS  IS WS-FS1.

       DATA DIVISION.
       FILE SECTION.
       FD EMPFILE
           RECORD CONTAINS 80  CHARACTERS
           BLOCK  CONTAINS 800 CHARACTERS
           DATA RECORD     IS EMPFILE-RECORD.

       01 EMPFILE-RECORD.
          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 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 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 -

 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
E0006EMPLOYEE6      SE        0000045000
******************************** Bottom of Data ********************************