FILE START Statement


START is used to set the file pointer to read the record. START won't retrieve any record and only sets the pointer before beginning a sequence of READ operations.

Points to note -

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

Syntax -

START logical-file-name
    [KEY IS {EQUAL TO | GREATER THAN | LESS THAN | NOT ...} ws-key-value]
        [INVALID KEY statements-set1]
    [NOT INVALID KEY statements-set2]
[END-START].
Note! All statements coded in [ ] are optional.

Parameters -

  • logical-file-name - Specifies the file from where the positioning needs to be done.
  • KEY IS - This clause is used to specify the position where the file pointer should be set. The key-value can be set to start from an exact match or from a greater or lesser value.
  • END-START - An optional phrase that marks the end of the START statement. END-START is not required when a START statement ends with a period.

Error Handling -

  • INVALID KEY - This phrase specifies the action to be taken when the START operation doesn't find a matching key value. The statements following INVALID KEY are executed in such cases. This is applicable to indexed or relative files.
  • NOT INVALID KEY - when the START operation finds a matching key value. 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 - Start browsing the file from EMP-ID 'E0003'.

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

       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=FILEBR
//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