[an error occurred while processing this directive]

HP OpenVMS Systems Documentation

Content starts here

HP 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 and I64 CONVERT Utility to optimize file space, or by using an HP 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:

  • File organization determines valid access modes.
  • File organization and access mode determine valid open modes.
  • All three (organization, access, and open mode) enable or disable I/O statements.

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


Previous Next Contents Index