FILE WRITE Statement


WRITE statement is used to add a record to the file. At a time, only one record is written to the file.

Points to note -

  • The file should open in OUTPUT (for sequential, indexed and relative files when the files are empty) or I-O (indexed and relative files when the files are not empty) or EXTEND (for sequential files when the file is not empty) mode to perform the WRITE statement.
  • The WRITE 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 -

For Sequential files -

WRITE record-name 
     [FROM ws-record-name]
	 [BEFORE ADVANCING ws-variable|num LINES]
	 [AFTER  ADVANCING ws-variable|num LINES]
[END-WRITE].

For Index and Relative files -

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

Parameters -

  • record-name - This specifies the record in the data file where the information will be written.
  • FROM ws-record-name - This optional clause indicates the data source that will be written to the record. If this clause is ignored, the data will be taken from the record-name.
  • BEFORE ADVANCING - Specifies the number of lines to forward before writing a record.
  • AFTER ADVANCING - Specifies the number of lines to forward after writing a record.
  • END-WRITE - An optional phrase marking the end of the WRITE statement. END-WRITE is not required when a WRITE statement ends with a period.

Error Handling -

  • INVALID KEY - This phrase specifies the action to be taken if there's an error during the write operation, like attempting to add a record with a duplicate key in an indexed file. The statements following INVALID KEY are executed in such cases. This is applicable to indexed or relative files.
  • NOT INVALID KEY - This is executed if the WRITE operation is completed without errors. This is applicable to indexed or relative files.
Note! If the FILE-STATUS clause is coded, the associated file status is updated when the START statement is executed.

Practical Example -


Scenario - Below example describes how to write a new record into a new PS file.

Code -

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

       ENVIRONMENT DIVISION. 
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
           SELECT EMPFILE ASSIGN TO INPUT01
           ORGANIZATION IS SEQUENTIAL 
           ACCESS MODE  IS SEQUENTIAL 
           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) VALUE SPACES.

       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 the file for writing
           OPEN OUTPUT EMPFILE.

           INITIALIZE EMPFILE-RECORD
      * 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 
           WRITE EMPFILE-RECORD.
           IF WS-FS1 EQUAL ZERO
              DISPLAY "RECORD INSERTED"
           ELSE
              DISPLAY "RECORD INSERTION FAILED"
           END-IF.
      * Closing file
           CLOSE EMPFILE.
           STOP RUN.

Run JCL -

//MATESYF JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID
//*
//STEP01  EXEC PGM=FILEWRIT 
//STEPLIB  DD  DSN=MATESY.COBOL.LOADLIB,DISP=SHR
//INPUT01  DD  DSN=MATESY.EMPLOYEE.INPFILE1,
//             DISP=(NEW,CATLG,DELETE),
//             SPACE=(TRK,(1,1),RLSE),
//             UNIT=SYSDA,
//             DCB=(DSORG=PS,RECFM=FB,LRECL=80,BLKSIZE=800)
//SYSOUT   DD  SYSOUT=*
//SYSIN    DD  * 
E0006
EMPLOYEE6 
SE 
0000040000
/*

Output -

RECORD INSERTED   

MATESY.EMPLOYEE.INPFILE1 -

E0006EMPLOYEE6      SE        0000040000