TSO-ISPF JCL COBOL VSAM DB2 CICS Tools Articles Job Portal Forum Quiz Interview Q&A

CICS WRITE Command


WRITE command writes a new record to a file. The parameters used in WRITE command are same as the READ command.

Syntax:

Below is the syntax for WRITE command.

EXEC CICS WRITE
   FILE(filename)
   FROM(data-area)
   RIDFLD(data-area) [RBA|RRN]
   LENGTH(data-value)
   KEYLENGTH(data-value)
END-EXEC.

Let us see the parameters used in the WRITE command.

  • FILE(filename)

    Specifies the name of the file to be accessed.

  • FROM(data-area)

    Specifies the record that is to be written to the data set referred to by this file.

  • LENGTH

    Specifies the length, as a halfword binary value(PIC S9(4) COMP), of the data area from which the record is written.

  • RIDFLD(data-area)

    Specifies the key of the record to be written. If RBA or RRN is specified, this field is interpreted as a Relative Byte Address or Relative Record Number respectively.

  • RBA

    Specifies that the file is ESDS and the RIDFLD option should be interpreted as the Relative Byte Address.

  • RRN

    Specifies that the file is RRDS and the RIDFLD option should be interpreted as the Relative Record Number.

  • KEYLENGTH(data-value)

    specifies the length (halfword binary) of the key that has been specified in the RIDFLD option.


Example:

Let us see an example of CICS program for WRITE command.

IDENTIFICATION DIVISION.
PROGRAM-ID. IBMMF.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-REC-LEN    PIC S9(4) COMP.
01 WS-KEY-LEN    PIC S9(4) COMP.
01 WS-REC-KEY    PIC 9(3).
01 WS-REC-DATA   PIC X(80).
PROCEDURE DIVISION.
      MOVE +80           TO WS-REC-LEN.
      MOVE ‘502258’      TO WS-REC-KEY.
      MOVE 6             TO WS-KEY-LEN.
      MOVE '502258IBMMAINFRAMER TUTORIALS' TO WS-REC-DATA.
      EXEC CICS WRITE
        FILE('STDLST')
        FROM(WS-REC-DATA)
        LENGTH(WS-REC-LEN)
        RIDFLD(WS-REC-KEY)
        KEYLENGTH(WS-KEY-LEN)
      END-EXEC.

Description:

This program write the data in WS-REC-DATA into file 'STDLST'.

File name-'STDLST' is the name of the file which we want to write. This is the CICS symbolic file name which identifies the FCT(File control table) entry for the file. File names can be up to 8 characters long and should be enclosed in quotes if they are literals.

After execution, WS-REC-DATA will be written into file ‘STDLST’.


WRITE Command Exception conditions:


ExceptionDescription
DISABLEDA file is disabled
FILENOTFOUNDThe file name supplied in the FILE option is not defined to CICS.
NOTAUTHA resource security check has failed on FILE(filename).(i.e. User does not have enough permissions to access the file).
NOSPACENo space is available for new record.
LENGERRMismatch between the length specified in command and actual length of the record.
DUPKEYValue in RIDFLD is already exist in the file.


If you have any doubts or queries related to this chapter, get them clarified from our Mainframe experts on ibmmainframer Community!

Are you looking for Job Change? Job Portal