Compaq COBOL
User Manual


Previous Contents Index

6.3.4 File Handling for Indexed Files

Creating an indexed file involves the following tasks:

  1. Specifying ORGANIZATION IS INDEXED in the Environment Division SELECT clause
  2. Specifying ACCESS MODE IS SEQUENTIAL (or RANDOM or DYNAMIC) in the Environment Division SELECT clause
  3. Opening the file for OUTPUT (to create and add records) or for I-O (to add, change, delete, or extend records)
  4. Initializing the key values
  5. Executing a WRITE statement
  6. Closing the file

One way to populate an indexed file is to sequentially write the records in ascending order by primary key. Example 6-26 creates and populates an indexed file from a sequential file, which has been sorted in ascending sequence on the primary key field. Notice that the primary and alternate keys are initialized in ICE-CREAM-MASTER when the contents of the fields in INPUT-RECORD are read into ICE-CREAM-MASTER before the record is written.

Example 6-26 Creating and Populating an Indexed File

IDENTIFICATION DIVISION. 
PROGRAM-ID. INDEX02. 
ENVIRONMENT DIVISION. 
INPUT-OUTPUT SECTION. 
FILE-CONTROL. 
    SELECT INPUT-FILE ASSIGN TO "DAIRYI". 
    SELECT FLAVORS    ASSIGN TO "DAIRY" 
                      ORGANIZATION IS INDEXED 
                      ACCESS MODE IS SEQUENTIAL 
                      RECORD KEY IS ICE-CREAM-MASTER-KEY 
                      ALTERNATE RECORD KEY IS ICE-CREAM-STORE-STATE 
                                           WITH DUPLICATES 
                      ALTERNATE RECORD KEY IS ICE-CREAM-STORE-CODE. 
DATA DIVISION. 
FILE SECTION. 
FD  INPUT-FILE. 
01  INPUT-RECORD. 
    02  INPUT-RECORD-KEY             PIC 9999. 
    02  INPUT-RECORD-DATA            PIC X(47). 
FD  FLAVORS. 
01  ICE-CREAM-MASTER. 
    02 ICE-CREAM-MASTER-KEY          PIC XXXX. 
    02 ICE-CREAM-MASTER-DATA. 
       03  ICE-CREAM-STORE-CODE      PIC XXXXX. 
       03  ICE-CREAM-STORE-ADDRESS   PIC X(20). 
       03  ICE-CREAM-STORE-CITY      PIC X(20). 
       03  ICE-CREAM-STORE-STATE     PIC XX. 
WORKING-STORAGE SECTION. 
01  END-OF-FILE                      PIC X. 
PROCEDURE DIVISION. 
A000-BEGIN. 
    OPEN INPUT INPUT-FILE. 
    OPEN OUTPUT FLAVORS. 
A010-POPULATE. 
    PERFORM A100-READ-INPUT UNTIL END-OF-FILE = "Y". 
A020-EOJ. 
    DISPLAY "END OF JOB". 
    STOP RUN. 
A100-READ-INPUT. 
    READ INPUT-FILE INTO ICE-CREAM-MASTER 
         AT END MOVE "Y" TO END-OF-FILE. 
    IF END-OF-FILE NOT = "Y" 
       WRITE ICE-CREAM-MASTER INVALID KEY DISPLAY "BAD WRITE" 
                                          STOP RUN. 

The program can add records to the file until it reaches the physical limitations of its storage device. When this occurs, you should follow these steps:

  1. Delete unnecessary records.
  2. Back up the file.
  3. Recreate the file either by using the OpenVMS Alpha CONVERT Utility to optimize file space, or by using a Compaq COBOL program.

Statements for Indexed File Processing

Processing an indexed file involves the following:

  1. Opening the file
  2. Processing the file with valid I/O statements
  3. Closing the file

Table 6-6 lists the valid I/O statements and illustrates the following relationships:

Table 6-6 Valid I/O Statements for Indexed Files
      Open Mode
File
Organization
Access
Mode
Statement INPUT OUTPUT I-O EXTEND
INDEXED SEQUENTIAL DELETE
READ
REWRITE
START
WRITE
UNLOCK
No
Yes
No
Yes
No
Yes
No
No
No
No
Yes
Yes
Yes
Yes
Yes
Yes
No
Yes
No
No
No
No
Yes
Yes
  RANDOM DELETE
READ
REWRITE
WRITE
UNLOCK
No
Yes
No
No
Yes
No
No
No
Yes
Yes
Yes
Yes
Yes
Yes
Yes
No
No
No
No
No
  DYNAMIC DELETE
READ
READ NEXT
REWRITE
START
WRITE
UNLOCK
No
Yes
Yes
No
Yes
No
Yes
No
No
No
No
No
Yes
Yes
Yes
Yes
Yes
Yes
Yes
Yes
Yes
No
No
No
No
No
No
No

Writing an Indexed File

You specify sequential access mode in the Environment Division SELECT clause when you want to write records in ascending or descending order by primary key, depending on the sort order. Specify random or dynamic access mode to enable your program to write records in any order.

Using Segmented Keys in Indexed Files

Segmented keys are a form of primary or alternate keys. A segmented key can be made up of multiple pieces, or segments. These segments are data items that you define in the record description entry for a file. They are concatenated, in order of specification in the ALTERNATE RECORD KEY or RECORD KEY clause, to form the segmented key, which will be treated like any "simple" primary or alternate key.

With segmented keys, you have more flexibility in defining record description entries for indexed files. A segmented key is made up of between one and eight data items, which can be defined anywhere and in any order within the record description, and which can even overlap. For example, you might use the following record definition in your program:


01 EMPLOYEE. 
    02 FORENAME    PIC X(10). 
    02 BADGE-NO    PIC X(6). 
    02 DEPT        PIC X(2). 
    02 SURNAME     PIC X(20). 
    02 INITIAL     PIC X(1). 
Then the following line in your program, which specifies the segmented key name and three of its segments:


    RECORD KEY IS NAME = SURNAME FORENAME INITIAL 
causes Compaq COBOL to treat name as if it were an explicitly defined group item consisting of the following:


    02 SURNAME   PIC X(20). 
    02 FORENAME  PIC X(10). 
    02 INITIAL   PIC X(1). 

You define a segmented key in either the RECORD KEY clause or the ALTERNATE RECORD KEY clause. You use the START or READ statement to reference a segmented key.

Each segment is a data-name of a data item in a record description entry. A segment can be an alphanumeric or alphabetic item, a group item, or an unsigned numeric display item. A segment can be qualified, but it cannot be a group item containing a variable-occurrence item.

Refer to the chapters on the Data Division and the Procedure Division in the Compaq COBOL Reference Manual for more information on segmented keys.

Example 6-27 shows how you might use segmented keys. In this example, SEG-ICE-CREAM-KEY is a segmented-key name. ICE-CREAM-STORE-KIND and ICE-CREAM-STORE-ZIP are the segments. Notice that the segmented-key name is referenced in the READ statement.

Example 6-27 Using Segmented Keys

IDENTIFICATION DIVISION. 
PROGRAM-ID. MANAGER. 
ENVIRONMENT DIVISION. 
INPUT-OUTPUT SECTION. 
FILE-CONTROL. 
   SELECT FLAVORS    ASSIGN TO "STORE" 
       ORGANIZATION IS INDEXED 
       ACCESS MODE IS RANDOM 
       RECORD KEY IS 
     SEG-ICE-CREAM-KEY = 
       ICE-CREAM-STORE-KIND, 
       ICE-CREAM-STORE-ZIP. 
DATA DIVISION. 
FILE SECTION. 
FD  FLAVORS. 
01  ICE-CREAM-MASTER. 
    02 ICE-CREAM-DATA. 
       03  ICE-CREAM-STORE-KIND      PIC XX. 
       03  ICE-CREAM-STORE-MANAGER   PIC X(40). 
       03  ICE-CREAM-STORE-SIZE      PIC XX. 
       03  ICE-CREAM-STORE-ADDRESS   PIC X(20). 
       03  ICE-CREAM-STORE-CITY      PIC X(20). 
       03  ICE-CREAM-STORE-STATE     PIC XX. 
       03  ICE-CREAM-STORE-ZIP       PIC XXXXX. 
WORKING-STORAGE SECTION. 
01  PROGRAM-STAT                     PIC X. 
    88  OPERATOR-STOPS-IT            VALUE "1". 
PROCEDURE DIVISION. 
A000-BEGIN. 
      OPEN I-O FLAVORS. 
      PERFORM A020-INITIAL-PROMPT. 
      IF OPERATOR-STOPS-IT 
         PERFORM A005-TERMINATE. 
      PERFORM A030-RANDOM-READ. 
      PERFORM A025-SUBSEQUENT-PROMPTS UNTIL OPERATOR-STOPS-IT. 
      PERFORM A005-TERMINATE. 
A005-TERMINATE. 
      DISPLAY "END OF JOB". 
      STOP RUN. 
A020-INITIAL-PROMPT. 
      DISPLAY "Do you want to see the manager of a store?". 
      PERFORM A040-GET-ANS UNTIL PROGRAM-STAT = "Y" OR "y" OR "N" OR "n". 
      IF PROGRAM-STAT = "N" OR "n" 
      THEN 
          MOVE "1" TO PROGRAM-STAT. 
A025-SUBSEQUENT-PROMPTS. 
      MOVE SPACE TO PROGRAM-STAT. 
      DISPLAY "Do you want to see the manager of another store?". 
      PERFORM A040-GET-ANS UNTIL PROGRAM-STAT = "Y" OR "y" OR "N" OR "n". 
      IF PROGRAM-STAT = "Y" OR "y" 
      THEN 
          PERFORM A030-RANDOM-READ 
      ELSE 
          MOVE "1" TO PROGRAM-STAT. 
A030-RANDOM-READ. 
      DISPLAY "Enter store kind: ". 
      ACCEPT ICE-CREAM-STORE-KIND. 
      DISPLAY "Enter zip code: " AT LINE PLUS 2. 
      ACCEPT ICE-CREAM-STORE-ZIP. 
      PERFORM A100-READ-INPUT-BY-KEY. 
A040-GET-ANS. 
      DISPLAY "Please answer Y or N" 
      ACCEPT PROGRAM-STAT. 
A100-READ-INPUT-BY-KEY. 
      READ FLAVORS KEY IS SEG-ICE-CREAM-KEY 
      INVALID KEY 
        DISPLAY "Store does not exist - Try again" 
      NOT INVALID KEY 
        DISPLAY "The manager is: ", ICE-CREAM-STORE-MANAGER. 

6.4 Reading Files

Reading sequential, line sequential, relative, and indexed files includes the following tasks:

  1. Opening the file
  2. Executing a READ or START statement

Sections 6.4.1, 6.4.2, and 6.4.3 describe the specific tasks involved in reading sequential, line sequential, relative, and indexed files.

6.4.1 Reading a Sequential or Line Sequential (Alpha) File

Reading a sequential or (on Alpha only) line sequential file involves the following:

  1. Opening the file for INPUT or I/O for sequential files, or INPUT for line sequential files (I/O is not permitted for line sequential files)
  2. Executing a READ statement

Each READ statement reads a single logical record and makes its contents available to the program in the record area. There are two ways of reading records:

Statements (1) and (2) in the following example are logically equivalent:


FILE SECTION. 
FD  STOCK-FILE. 
01  STOCK-RECORD     PIC X(80). 
WORKING-STORAGE SECTION. 
01  STOCK-WORK       PIC X(80). 
 
-------------(1)---------------    -------------(2)--------------- 
READ STOCK-FILE INTO STOCK-WORK.   READ STOCK-FILE. 
                                   MOVE STOCK-RECORD TO STOCK-WORK. 

When you omit the INTO phrase, you process the records directly in the record area or buffer (for example, STOCK-RECORD). The record is also available in the record area if you use the INTO phrase.

In a READ INTO clause, if the destination area is shorter than the length of the record area being read, the record is truncated on the right and a warning is issued; if longer, the destination area is filled on the right with blanks.

If the data in the record being read is shorter than the length of the record (for example, a variable-length record), the contents of the record beyond that data are undefined.

Generally speaking, if the recordtype is fixed, the prolog and epilog are zero. The exceptions to this are: for relative files there is a 1 byte record status flag prolog; for sequential files there is a 1 byte epilog if the record length is odd.

Example 6-28 reads a sequential file and displays its contents on the terminal.

Example 6-28 Reading a Sequential File

IDENTIFICATION DIVISION. 
PROGRAM-ID. SEQ02. 
ENVIRONMENT DIVISION. 
INPUT-OUTPUT SECTION. 
FILE-CONTROL. 
    SELECT TRANS-FILE ASSIGN TO "TRANS". 
DATA DIVISION. 
FILE SECTION. 
FD  TRANS-FILE. 
01  TRANSACTION-RECORD    PIC X(25). 
PROCEDURE DIVISION. 
A000-BEGIN. 
    OPEN INPUT TRANS-FILE. 
    PERFORM A100-READ-TRANS-FILE 
       UNTIL TRANSACTION-RECORD = "END". 
    CLOSE TRANS-FILE. 
    STOP RUN. 
A100-READ-TRANS-FILE. 
    READ TRANS-FILE 
       AT END MOVE "END" TO TRANSACTION-RECORD. 
    IF TRANSACTION-RECORD NOT = "END" 
       DISPLAY TRANSACTION-RECORD. 

6.4.2 Reading a Relative File

Your program can read a relative file sequentially, randomly, or dynamically. The following three sections describe the specific tasks involved in reading a relative file sequentially, randomly, and dynamically.

Reading a Relative File Sequentially

Reading relative records sequentially involves the following:

  1. Specifying ORGANIZATION IS RELATIVE in the Environment Division SELECT clause
  2. Specifying ACCESS MODE IS SEQUENTIAL (or DYNAMIC) in the Environment Division SELECT clause (and using the READ NEXT phrase)
  3. Opening the file for INPUT or I-O
  4. Reading records as you would a sequential file, or using a START statement

The READ statement makes the next logical record of an open file available to the program. The system reads the file sequentially from either cell 1 or wherever you START the file, up to cell n. It skips the empty cells and retrieves only valid records. Each READ statement updates the contents of the file's RELATIVE KEY data item, if specified. The data item contains the relative number of the available record. When the at end condition occurs, execution of the READ statement is unsuccessful (see Chapter 7).

Sequential processing need not begin at the first record of a relative file. The START statement specifies the next record to be read and positions the file position indicator for subsequent I/O operations.

Example 6-29 reads a relative file sequentially, displaying every record on the terminal.

Example 6-29 Reading a Relative File Sequentially

IDENTIFICATION DIVISION. 
PROGRAM-ID. REL04. 
ENVIRONMENT DIVISION. 
INPUT-OUTPUT SECTION. 
FILE-CONTROL. 
    SELECT FLAVORS ASSIGN TO "BRAND" 
                   ORGANIZATION IS RELATIVE 
                   ACCESS MODE IS SEQUENTIAL 
                   RELATIVE KEY IS KETCHUP-MASTER-KEY. 
DATA DIVISION. 
FILE SECTION. 
FD  FLAVORS. 
01  KETCHUP-MASTER           PIC X(50). 
WORKING-STORAGE SECTION. 
01  KETCHUP-MASTER-KEY       PIC 99. 
01  END-OF-FILE              PIC X. 
PROCEDURE DIVISION. 
A000-BEGIN. 
    OPEN INPUT FLAVORS. 
    PERFORM A010-DISPLAY-RECORDS UNTIL END-OF-FILE = "Y". 
A005-EOJ. 
    DISPLAY "END OF JOB". 
    CLOSE FLAVORS. 
    STOP RUN. 
A010-DISPLAY-RECORDS. 
    READ FLAVORS AT END MOVE "Y" TO END-OF-FILE. 
    IF END-OF-FILE NOT = "Y" DISPLAY KETCHUP-MASTER. 

Reading a Relative File Randomly

Reading relative records randomly involves the following:

  1. Specifying ORGANIZATION IS RELATIVE in the Environment Division SELECT clause
  2. Specifying ACCESS MODE IS RANDOM (or DYNAMIC) in the Environment Division SELECT clause
  3. Opening the file for INPUT or I-O
  4. Moving the relative record number value to the RELATIVE KEY data name
  5. Reading the record from the cell identified by the relative record number

The READ statement selects a specific record from an open file and makes it available to the program. The value of the relative key identifies the specific record. The system reads the record identified by the RELATIVE KEY data name clause. If the cell does not contain a valid record, the invalid key condition occurs, and the READ operation fails (see Chapter 7).

Example 6-30 reads a relative file randomly, displaying every record on the terminal.

Example 6-30 Reading a Relative File Randomly

IDENTIFICATION DIVISION. 
PROGRAM-ID. REL05. 
ENVIRONMENT DIVISION. 
INPUT-OUTPUT SECTION. 
FILE-CONTROL. 
    SELECT FLAVORS ASSIGN TO "BRAND" 
                   ORGANIZATION IS RELATIVE 
                   ACCESS MODE IS RANDOM 
                   RELATIVE KEY IS KETCHUP-MASTER-KEY. 
DATA DIVISION. 
FILE SECTION. 
FD  FLAVORS. 
01  KETCHUP-MASTER           PIC X(50). 
 
WORKING-STORAGE SECTION. 
01  KETCHUP-MASTER-KEY       PIC 99 VALUE 99. 
PROCEDURE DIVISION. 
A000-BEGIN. 
    OPEN INPUT FLAVORS. 
    PERFORM A100-DISPLAY-RECORD UNTIL KETCHUP-MASTER-KEY = 00. 
    DISPLAY "END OF JOB". 
    CLOSE FLAVORS. 
    STOP RUN. 
A100-DISPLAY-RECORD. 
    DISPLAY "TO DISPLAY A RECORD ENTER ITS RECORD NUMBER (0 to END)". 
    ACCEPT KETCHUP-MASTER-KEY WITH CONVERSION. 
    IF KETCHUP-MASTER-KEY > 00 
       READ FLAVORS 
        INVALID KEY DISPLAY "BAD KEY" 
                        CLOSE FLAVORS 
                        STOP RUN 
       END-READ 
       DISPLAY KETCHUP-MASTER. 

Reading a Relative File Dynamically

The READ statement has two formats so that it can select the next logical record (sequential access) or select a specific record (random access) and make it available to the program. In dynamic mode, the program can switch from random access I/O statements to sequential access I/O statements in any order, without closing and reopening files. However, you must use the READ NEXT statement to sequentially read a relative file open in dynamic mode.

Sequential processing need not begin at the first record of a relative file. The START statement repositions the file position indicator for subsequent I/O operations.

A sequential read of a dynamic file is indicated by the NEXT phrase of the READ statement. A READ NEXT statement should follow the START statement since the READ NEXT statement reads the next record indicated by the current record pointer. Subsequent READ NEXT statements sequentially retrieve records until another START statement or random READ statement executes.

Example 6-31 processes a relative file containing 10 records. If the previous program examples in this chapter have been run, each record has a unique even number from 2 to 20 as its key. The program positions the record pointer (using the START statement) to the cell corresponding to the value in INPUT-RECORD-KEY. The program's READ...NEXT statement retrieves the remaining valid records in the file for display on the terminal.

Example 6-31 Reading a Relative File Dynamically

IDENTIFICATION DIVISION. 
PROGRAM-ID. REL06. 
ENVIRONMENT DIVISION. 
INPUT-OUTPUT SECTION. 
FILE-CONTROL. 
    SELECT FLAVORS ASSIGN TO "BRAND" 
                   ORGANIZATION IS RELATIVE 
                   ACCESS MODE IS DYNAMIC 
                   RELATIVE KEY IS KETCHUP-MASTER-KEY. 
DATA DIVISION. 
FILE SECTION. 
FD  FLAVORS. 
01  KETCHUP-MASTER           PIC X(50). 
WORKING-STORAGE SECTION. 
01  KETCHUP-MASTER-KEY       PIC 99. 
01  END-OF-FILE              PIC X   VALUE "N". 
PROCEDURE DIVISION. 
A000-BEGIN. 
    OPEN I-O FLAVORS. 
    DISPLAY "Enter number". 
    ACCEPT KETCHUP-MASTER-KEY. 
    START FLAVORS KEY = KETCHUP-MASTER-KEY 
          INVALID KEY DISPLAY "Bad START statement" 
          GO TO A005-END-OF-JOB. 
    PERFORM A010-DISPLAY-RECORDS UNTIL END-OF-FILE = "Y". 
A005-END-OF-JOB. 
    DISPLAY "END OF JOB". 
    CLOSE FLAVORS. 
    STOP RUN. 
A010-DISPLAY-RECORDS. 
    READ FLAVORS NEXT RECORD AT END MOVE "Y" TO END-OF-FILE. 
    IF END-OF-FILE NOT = "Y" DISPLAY KETCHUP-MASTER. 

6.4.3 Reading an Indexed File

Your program can read an indexed file sequentially, randomly, or dynamically.

Reading an Indexed File Sequentially

Reading indexed records sequentially involves the following:

  1. Specifying ORGANIZATION IS INDEXED in the Environment Division SELECT clause
  2. Specifying ACCESS MODE IS SEQUENTIAL in the Environment Division SELECT clause
  3. Opening the file for INPUT or I-O
  4. Reading records from the beginning of the file as you would a sequential file (using a READ...AT END statement)

The READ statement makes the next logical record of an open file available to the program. It skips deleted records and sequentially reads and retrieves only valid records. When the at end condition occurs, execution of the READ statement is unsuccessful (see Chapter 7).

Example 6-32 reads an entire indexed file sequentially beginning with the first record in the file, displaying every record on the terminal.

Example 6-32 Reading an Indexed File Sequentially

IDENTIFICATION DIVISION. 
PROGRAM-ID. INDEX03. 
ENVIRONMENT DIVISION. 
INPUT-OUTPUT SECTION. 
FILE-CONTROL. 
    SELECT FLAVORS    ASSIGN TO "DAIRY" 
                      ORGANIZATION IS INDEXED 
                      ACCESS MODE IS SEQUENTIAL 
                      RECORD KEY IS ICE-CREAM-MASTER-KEY 
                      ALTERNATE RECORD KEY IS ICE-CREAM-STORE-STATE 
                                           WITH DUPLICATES 
                      ALTERNATE RECORD KEY IS ICE-CREAM-STORE-CODE. 
DATA DIVISION. 
FILE SECTION. 
FD  FLAVORS. 
01  ICE-CREAM-MASTER. 
    02 ICE-CREAM-MASTER-KEY          PIC XXXX. 
    02 ICE-CREAM-MASTER-DATA. 
       03  ICE-CREAM-STORE-CODE      PIC XXXXX. 
       03  ICE-CREAM-STORE-ADDRESS   PIC X(20). 
       03  ICE-CREAM-STORE-CITY      PIC X(20). 
       03  ICE-CREAM-STORE-STATE     PIC XX. 
WORKING-STORAGE SECTION. 
01  END-OF-FILE                      PIC X. 
PROCEDURE DIVISION. 
A000-BEGIN. 
    OPEN INPUT FLAVORS. 
A010-SEQUENTIAL-READ. 
    PERFORM A100-READ-INPUT UNTIL END-OF-FILE = "Y". 
A020-EOJ. 
    DISPLAY "END OF JOB". 
    STOP RUN. 
A100-READ-INPUT. 
    READ  FLAVORS AT END MOVE "Y" TO END-OF-FILE. 
    IF END-OF-FILE NOT = "Y" 
       DISPLAY ICE-CREAM-MASTER 
       STOP "Type CONTINUE to display next master". 

Reading an Indexed File Randomly

Reading indexed records randomly involves the following:

  1. Specifying ORGANIZATION IS INDEXED in the Environment Division SELECT clause
  2. Specifying ACCESS MODE IS RANDOM in the Environment Division SELECT clause
  3. Opening the file for INPUT or I-O
  4. Initializing the RECORD KEY or ALTERNATE RECORD KEY data name before reading the record
  5. Reading the record using the KEY IS clause

To read the file randomly, the program must initialize either the primary key data name or the alternate key data name before reading the target record, and specify that data name in the KEY IS phrase of the READ statement.

The READ statement selects a specific record from an open file and makes it available to the program. The value of the primary or alternate key identifies the specific record. The system randomly reads the record identified by the KEY clause. If the I/O system does not find a valid record, the invalid key condition occurs, and the READ statement fails (see Chapter 7).

Example 6-33 reads an indexed file randomly, displaying its contents on the terminal.

Example 6-33 Reading an Indexed File Randomly

IDENTIFICATION DIVISION. 
PROGRAM-ID. INDEX04. 
ENVIRONMENT DIVISION. 
INPUT-OUTPUT SECTION. 
FILE-CONTROL. 
    SELECT FLAVORS    ASSIGN TO "DAIRY" 
                      ORGANIZATION IS INDEXED 
                      ACCESS MODE IS RANDOM 
                      RECORD KEY IS ICE-CREAM-KEY. 
DATA DIVISION. 
FILE SECTION. 
FD  FLAVORS. 
01  ICE-CREAM-MASTER. 
    02 ICE-CREAM-KEY                 PIC XXXX. 
    02 ICE-CREAM-DATA. 
       03  ICE-CREAM-STORE-CODE      PIC XXXXX. 
       03  ICE-CREAM-STORE-ADDRESS   PIC X(20). 
       03  ICE-CREAM-STORE-CITY      PIC X(20). 
       03  ICE-CREAM-STORE-STATE     PIC XX. 
WORKING-STORAGE SECTION. 
01  PROGRAM-STAT                     PIC X. 
    88  OPERATOR-STOPS-IT            VALUE "1". 
PROCEDURE DIVISION. 
A000-BEGIN. 
    OPEN I-O FLAVORS. 
    PERFORM A020-INITIAL-PROMPT. 
    IF OPERATOR-STOPS-IT 
       PERFORM A005-TERMINATE. 
    PERFORM A030-RANDOM-READ. 
    PERFORM A025-SUBSEQUENT-PROMPTS UNTIL OPERATOR-STOPS-IT. 
    DISPLAY "END OF JOB". 
    STOP RUN. 
A020-INITIAL-PROMPT. 
    DISPLAY "Do you want to see a store?". 
    PERFORM A040-GET-ANSWER UNTIL PROGRAM-STAT = "Y" OR "y" OR "N" OR "n". 
    IF PROGRAM-STAT = "N" OR "n" 
       MOVE "1" TO PROGRAM-STAT. 
A025-SUBSEQUENT-PROMPTS. 
    MOVE SPACE TO PROGRAM-STAT. 
    DISPLAY "Do you want to see another store ?". 
    PERFORM A040-GET-ANSWER UNTIL PROGRAM-STAT = "Y" OR "y" OR "N" OR "n". 
    IF PROGRAM-STAT = "Y" OR "y" 
       PERFORM A030-RANDOM-READ 
    ELSE 
       MOVE "1" TO PROGRAM-STAT. 
A030-RANDOM-READ. 
    DISPLAY "Enter key". 
    ACCEPT ICE-CREAM-KEY. 
    PERFORM A100-READ-INPUT-BY-KEY. 
A040-GET-ANSWER. 
    DISPLAY "Please answer Y or N" 
    ACCEPT PROGRAM-STAT. 
A100-READ-INPUT-BY-KEY. 
    READ FLAVORS KEY IS ICE-CREAM-KEY 
         INVALID KEY DISPLAY "Record does not exist - Try again" 
         NOT INVALID KEY DISPLAY "The record is: ", ICE-CREAM-MASTER. 
A005-TERMINATE. 
    DISPLAY "terminated". 

Reading an Indexed File Dynamically

The READ statement has two formats, so it can select the next logical record (sequential access) or select a specific record (random access) and make it available to the program. In dynamic mode, the program can switch from using random access I/O statements to sequential access I/O statements, in any order and any number of times, without closing and reopening files. However, the program must use the READ NEXT statement to sequentially read an indexed file opened in dynamic mode.

Sequential processing need not begin at the first record of an indexed file. The START statement specifies the next record to be read sequentially, selects which key to use to determine the logical sort order, and repositions the file position indicator for subsequent I/O operations anywhere within the file.


Previous Next Contents Index