Compaq COBOL
User Manual


Previous Contents Index

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.

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 file position indicator. Subsequent READ NEXT statements sequentially retrieve records until another START statement or random READ statement executes.

Example 6-34 processes an indexed file containing 26 records. Each record has a unique letter of the alphabet as its primary key. The program positions the file to the first record whose INPUT-RECORD-KEY is equal to the specified letter of the alphabet. The program's READ NEXT statement sequentially retrieves the remaining valid records in the file for display on the terminal.

Example 6-34 Reading an Indexed File Dynamically

IDENTIFICATION DIVISION. 
PROGRAM-ID. INDEX05. 
ENVIRONMENT DIVISION. 
INPUT-OUTPUT SECTION. 
FILE-CONTROL. 
    SELECT IND-ALPHA  ASSIGN TO "ALPHA" 
                      ORGANIZATION IS INDEXED 
                      ACCESS MODE IS DYNAMIC 
                      RECORD KEY IS INPUT-RECORD-KEY. 
DATA DIVISION. 
FILE SECTION. 
FD  IND-ALPHA. 
01  INPUT-RECORD. 
    02  INPUT-RECORD-KEY             PIC X. 
    02  INPUT-RECORD-DATA            PIC X(50). 
WORKING-STORAGE SECTION. 
01  END-OF-FILE                      PIC X. 
PROCEDURE DIVISION. 
A000-BEGIN. 
    OPEN I-O IND-ALPHA. 
    DISPLAY "Enter letter" 
    ACCEPT INPUT-RECORD-KEY. 
    START IND-ALPHA KEY = INPUT-RECORD-KEY 
          INVALID KEY DISPLAY "BAD START STATEMENT" 
          NOT INVALID KEY 
    PERFORM A100-GET-RECORDS THROUGH A100-GET-RECORDS-EXIT 
           UNTIL END-OF-FILE = "Y" END-START. 
A010-END-OF-JOB. 
    DISPLAY "END OF JOB". 
    CLOSE IND-ALPHA. 
    STOP RUN. 
A100-GET-RECORDS. 
    READ IND-ALPHA NEXT RECORD AT END MOVE "Y" TO END-OF-FILE. 
    IF END-OF-FILE NOT = "Y" DISPLAY INPUT-RECORD. 
A100-GET-RECORDS-EXIT. 
    EXIT. 

READ PRIOR retrieves a record from an Indexed file which logically precedes the one which was made current by the previous file access operation, if such a logically previous record exists. READ PRIOR can only be used with a file whose organization is INDEXED and whose access mode is DYNAMIC. The file must be opened for INPUT or I-O. Example 6-35 is an example of READ PRIOR in a program.

Example 6-35 Reading an Indexed File Dynamically, with READ PRIOR

IDENTIFICATION DIVISION. 
PROGRAM-ID. READ_PRIOR. 
ENVIRONMENT DIVISION. 
INPUT-OUTPUT SECTION. 
FILE-CONTROL. 
    SELECT F  ASSIGN TO "READPR" 
        ORGANIZATION IS INDEXED 
        ACCESS IS DYNAMIC 
        RECORD KEY       IS K0 
        ALTERNATE RECORD IS K2 DUPLICATES. 
DATA DIVISION. 
FILE SECTION. 
FD F. 
01 R. 
    02  K0     PIC  X(3). 
    02  FILLER PIC  X(5). 
    02  K2     PIC  X(2). 
PROCEDURE DIVISION. 
P0. DISPLAY "***READ_PRIOR***". 
*+ 
* Indexed file creation: After this load, the indexed file 
* contains the following records : 0123456789, 1234567890, 
* 2345678990, and 9876543291 
*+ 
   OPEN OUTPUT F. 
   MOVE "0123456789" TO R. 
   WRITE R INVALID KEY DISPLAY "?1". 
   MOVE "1234567890" TO R. 
   WRITE R INVALID KEY DISPLAY "?2". 
   MOVE "2345678990" TO R. 
   WRITE R INVALID KEY DISPLAY "?3". 
   MOVE "9876543291" TO R. 
   WRITE R INVALID KEY DISPLAY "?4". 
   CLOSE F. 
*+ 
* READ PREVIOUS immediately after file open for IO 
*+ 
   OPEN I-O F. 
   MOVE "000" TO K0. 
   READ F PREVIOUS AT END GO TO P1 END-READ. 
   DISPLAY "?5 " R. 
P1. CLOSE F. 
*+ 
* READ PREVIOUS after file open for IO, from a middle 
* record to beginning record on primary key. 
*+ 
   OPEN I-O F. 
   MOVE "2345678990" TO R. 
   READ F INVALID KEY DISPLAY "?6" GO TO P2 END-READ. 
   IF R NOT = "2345678990" THEN DISPLAY "?7 " R. 
   READ F PREVIOUS AT END DISPLAY "?8" GO TO P2 END-READ. 
   IF R NOT = "1234567890" THEN DISPLAY "?9 " R. 
   READ F PREVIOUS AT END DISPLAY "?10" GO TO P2 END-READ. 
   IF R NOT = "0123456789" THEN DISPLAY "?11 " R. 
   READ F PREVIOUS AT END GO TO P2. 
   DISPLAY "?12 " R. 
*+ 
* Multiple READ PREVIOUS on a display alternate key with 
* duplicates. 
*+ 
P2. MOVE "91" TO K2. 
   READ F KEY K2 INVALID KEY DISPLAY "?13" GO TO P5 END-READ. 
   R NOT = "9876543291" THEN DISPLAY "?14 " R. 
   READ F PREVIOUS AT END DISPLAY "?15" GO TO P5 END-READ. 
   IF R NOT = "2345678990" THEN DISPLAY "?16 " R. 
   READ F PREVIOUS AT END DISPLAY "?17" GO TO P5 END-READ. 
   IF R NOT = "1234567890" THEN DISPLAY "?18 " R. 
   READ F PREVIOUS AT END DISPLAY "?19" GO TO P5 END-READ. 
   IF R NOT = "0123456789" THEN DISPLAY "?20 " R. 
   READ F PREVIOUS AT END GO TO P5. 
   DISPLAY "?21 " R. 
P5. CLOSE F. 
   DISPLAY "***END***". 
   STOP RUN. 

Reading an Indexed File from Other Languages on Tru64 UNIX

COBOL supports more data types for indexed keys than are supported in the ISAM definition. For keys in any of the data types not supported in the ISAM definition, the run-time system will translate those keys to strings. Table 6-7 specifies the appropriate mapping to create or use indexed files outside of COBOL (For example, if you are using the C language on Tru64 UNIX and you need to access COBOL files). See the ISAM package documentation for details of the file format.

Table 6-7 Indexed File---ISAM Mapping
COBOL Data Type Maps To Transformation Method
character string
PIC x(n)
CHARTYPE None.
short signed int
PIC S9(4) COMP
INTTYPE C-ISAM
long signed int
PIC S9(9) COMP
LONGTYPE C-ISAM
signed quadword
PIC S9(18) COMP
CHARTYPE Reverse the bytes (integers: most significant byte (msb) last; character strings: msb first).

If the data type is not _UNSIGNED, then complement the sign bit. This causes negative values to sort correctly with respect to each other, and precede positive values.
unsigned quadword
PIC 9(18) COMP
CHARTYPE Same as signed quadword.
packed decimal
PIC S9(n) COMP-3
CHARTYPE (Note that sign nibble after is the only case allowed in COBOL.) If the sign nibble is minus, complement all bits. This will give a sign nibble of 1 for a minus, which will come before the plus.

Copy the nibbles so the sign nibble is placed on the left and all the other nibbles are shifted one to the right.

Note that any data type not directly supported by ISAM is translated to a character string, which will sort as a character string in the correct order. <>

6.5 Updating Files

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

  1. Opening the file
  2. Executing a READ or START statement
  3. Executing a REWRITE and a DELETE statement

Sections 6.5.1, 6.5.2, and 6.5.3 describe how to update sequential, relative, and indexed files.

6.5.1 Updating a Sequential or Line Sequential File

Updating a record in a sequential file involves the following:

  1. Opening the file for I/O
  2. Reading the target record
  3. Rewriting the target record

The REWRITE statement places the record just read back into the file. The REWRITE statement completely replaces the contents of the target record with new data. You can use the REWRITE statement for files on mass storage devices only (for example, disk units). There are two ways of rewriting 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)-------------- 
REWRITE STOCK-RECORD FROM STOCK-WORK.   MOVE STOCK-WORK TO STOCK-RECORD. 
                                        REWRITE STOCK-RECORD. 

When you omit the FROM phrase, you process the records directly in the record area or buffer (for example, STOCK-RECORD).

For a REWRITE statement on a sequential file, the record being rewritten must be the same length as the record being replaced.

Example 6-36 reads a sequential file and rewrites as many records as the operator wants.

Example 6-36 Rewriting a Sequential File

IDENTIFICATION DIVISION. 
PROGRAM-ID. SEQ03. 
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). 
WORKING-STORAGE SECTION. 
01  ANSWER                PIC X. 
PROCEDURE DIVISION. 
A000-BEGIN. 
    OPEN I-O 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" 
       PERFORM A300-GET-ANSWER UNTIL ANSWER = "Y" OR "N" 
        IF ANSWER = "Y" DISPLAY "Please enter new record content" 
           ACCEPT TRANSACTION-RECORD 
           REWRITE TRANSACTION-RECORD. 
A300-GET-ANSWER. 
    DISPLAY "Do you want to replace this record? -- " 
             TRANSACTION-RECORD. 
    DISPLAY "Please answer Y or N". 
    ACCEPT ANSWER. 

Extending a Sequential or Line Sequential File

To position a file to its current end, and to allow the program to write new records beyond the last record in the file, use both:

Example 6-37 shows how to extend a sequential file.

Example 6-37 Extending a Sequential File

IDENTIFICATION DIVISION. 
PROGRAM-ID. SEQ04. 
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 EXTEND TRANS-FILE. 
    PERFORM A100-WRITE-RECORD 
       UNTIL TRANSACTION-RECORD = "END". 
    CLOSE TRANS-FILE. 
    STOP RUN. 
A100-WRITE-RECORD. 
    DISPLAY "Enter next record  - X(25)". 
    DISPLAY "Enter END to terminate the session". 
    DISPLAY "-------------------------". 
    ACCEPT TRANSACTION-RECORD. 
    IF TRANSACTION-RECORD NOT = "END" 
       WRITE TRANSACTION-RECORD. 

Without the EXTEND mode, a Compaq COBOL program would have to open the input file, copy it to an output file, and add records to the output file.


Previous Next Contents Index