Your Browser is not longer supported

Please use Google Chrome, Mozilla Firefox or Microsoft Edge to view the page correctly
Loading...

{{viewport.spaceProperty.prod}}

Positioning with START

Any record in an indexed (or relative) file can be selected as the starting point for subsequent sequential read operations by means of START. START sets up a comparison via a relation condition in order to establish the (primary or secondary) key of the first record to be read.

The following example illustrates how the language extension (to ANS85) START...KEY LESS... and READ...PREVIOUS can be used to sequentially process an indexed file in reverse order, i.e. in the order of descending record keys, beginning with the highest key in the file. The precise location within a file is identified by means of a conceptual entity called the file position indicator.

Example 9-11

Processing an indexed file in reverse order

  IDENTIFICATION DIVISION.
  PROGRAM-ID. INDREV.
 *    INDREV PROCESSES THE RECORDSOF AN INDIVIDUAL FILE
 *    IN DESCENDING RECORD KEY ORDER.
  ENVIRONMENT DIVISION.
  CONFIGURATION SECTION.
  SPECIAL-NAMES.
     TERMINAL IS T.
  INPUT-OUTPUT SECTION.
  FILE-CONTROL.
      SELECT IND-FILE
      ASSIGN TO "INDFILE"
      ORGANIZATION IS INDEXED
      ACCESS IS DYNAMIC
      RECORD KEY IS REC-KEY.
  DATA DIVISION.
  FILE SECTION.
  FD  IND-FILE.
  01  IND-REC.
      05  REC-KEY                     PIC X(8).
      05  REC-TEXT                    PIC X(72).
  WORKING-STORAGE SECTION.
  01  PROCESSING-SWITCH               PIC X.
      88  END-OF-PROCESSING                      VALUE "1".
  PROCEDURE DIVISION.
  INITIALIZTION.
     OPEN I-O IND-FILE —————————————————————————————————————————(1)
     MOVE HIGH-VALUE TO REC-KEY ————————————————————————————————(2)
     MOVE "0" TO PROCESSING SWITCH.
  PROCESS FILE.
      START IND-FILE KEY LESS OR EQUAL REC-KEY
         INVALID KEY
            DISPLAY "FILE IS EMPTY" UPON T
            SET END-OF-PROCESSING TO TRUE
         NOT INVALID KEY
           READ IND-FILE PREVIOUS ——————————————————————————————(3)
                AT END
                    SET END-OF-PROCESSING TO TRUE
                NOT AT END
                   DISPLAY "HIGHEST RECORD NUMBER: " REC-KEY
                      UPON T
                   PERFORM PROCESS-RECORD
             END-READ
       END-START
 
       PERFORM WITH TEST BEFORE UNTIL END-OF-PROCESSING
        READ IND-FILE PREVIOUS —————————————————————————————————(4)
            AT END
               SET END-OF-PROCESSING TO TRUE
            NOT AT END
               DISPLAY "NEXT RECORD KEY: " REC-KEY
                  UPON T
               PERFORM PROCESS-RECORD
         END-READ
       END-PERFORM.
   TERMINATION.
       CLOSE IND-FILE
       STOP RUN.
   PROCESS-RECORD.
 *
 *    PROCESSING OF CURRENT RECORD —————————————————————————————(5)
 *

(1)

The file IND-FILE is opened for processing with OPEN I-O.

(2)

To obtain the record with the highest key in the file,

  • the RECORD KEY is preset to the highest possible value (HIGH-VALUE in the NATIVE alphabet), and

  • START...KEY LESS OR EQUAL sets the file position indicator to it.

(3)

READ...PREVIOUS reads the record to which the file position indicator was previously set by START.

(4)

READ...PREVIOUS reads the record preceding the last record to be read.

(5)

The read record is processed. If its RECORD KEY is changed during processing, the original value must be restored before the next START statement.