FILE READ NEXT Statement


Note! The file pointer should set using START statement before using READ NEXT statement.

READ NEXT statement is used to read the next record from the current reading position of the file. At a time, only one record is retrieved from the file.

Points to note -

  • The file should open in INPUT or I-O mode to perform the READ NEXT statement.
  • The READ NEXT statement is used for indexed or relative files.
  • A READ NEXT statement is used when the ACCESS MODE is DYNAMIC.

Syntax -

READ logical-file-name
    [NEXT RECORD]  
    [INTO ws-record-name]
        [AT END statements-set1]
    [NOT AT END statements-set2]
[END-READ].
Note! All statements coded in [ ] are optional.

Parameters -

  • logical-file-name - Specifies the file from where the record is to be read.
  • NEXT RECORD - Used to read the next record in a sequential reading.
  • INTO ws-record-name - Specifies the working-storage record name to where the record is retrieved. ws-record-name matches with the actual record layout.
  • END-READ - Specifies the end of the READ statement. END-READ is not required when a READ statement ends with a period.

Error Handling -

  • AT END - This phrase specifies the action to take if you're at the end of a file or no more records are left. It applies to sequential files only.
  • NOT AT END - This phrase specifies the action to perform when the read is successful and it's not the end of the file. It applies to sequential files only.
Note! If the FILE-STATUS clause is coded, the associated file status is updated when the READ NEXT statement is executed.

Practical Example -


Scenario - Reading sequentially from record key 'E0003' in forward direction.

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

Code -

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

       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 in INPUT mode
           OPEN INPUT EMPFILE. 
      * Set the file pointer to read the record 
           MOVE 'E0003'       TO EMP-ID.
           START EMPFILE
                 KEY IS EQUAL TO EMP-ID
                     INVALID KEY DISPLAY "RECORD NOT FOUND"
                 NOT INVALID KEY PERFORM 1000-READ-EMPFILE 
                                    THRU 1000-EXIT 
           END-START.
      * Closing file
           CLOSE EMPFILE. 
           STOP RUN.

       1000-READ-EMPFILE. 
      * Reading records sequentially using NEXT RECORD
      * until end of the file
           PERFORM UNTIL WS-EOF 
                READ EMPFILE 
                     NEXT RECORD
                         AT END SET WS-EOF TO TRUE
                     NOT AT END DISPLAY EMPFILE-RECORD
                END-READ 
           END-PERFORM.

       1000-EXIT.
            EXIT. 

Run JCL -

//MATESYF JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID
//*                                                 
//STEP01  EXEC PGM=FILEBRFW
//STEPLIB  DD  DSN=MATESY.COBOL.LOADLIB,DISP=SHR
//INPUT01  DD  DSN=MATESY.EMPLOYEE.INPFILE,DISP=SHR 
//SYSOUT   DD  SYSOUT=*

Output -

E0003EMPLOYEE3      SE        0000050000
E0004EMPLOYEE4      SSE       0000040000
E0005EMPLOYEE5      SE        0000045000