Compaq COBOL
User Manual


Previous Contents Index

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. 

On Alpha, READ PRIOR retrieves from an Indexed file a record that logically precedes the one 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 (Alpha)

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

Example 6-36 is another example of READ PRIOR. This example contrasts how duplicates are handled with a DESCENDING key and with READ PRIOR. Also, this example shows how to use START before initiating a sequence of either READ NEXT statements or READ PRIOR statements. This example highlights how to use START, if you switch between READ NEXT and READ PRIOR.

Example 6-36 Another Example of READ PRIOR (Alpha)

***READ_PRIOR2*** 
Read ascending key 
a1 
b2 
c2 
d2 
e3 
Read descending key 
e3 
b2 
c2 
d2 
a1 
Read prior 
e3 
d2 
c2 
b2 
a1 
***END*** 
 
IDENTIFICATION DIVISION. 
PROGRAM-ID. READ_PRIOR2. 
ENVIRONMENT DIVISION. 
INPUT-OUTPUT SECTION. 
FILE-CONTROL. 
    SELECT OPTIONAL F1 
     ASSIGN TO "READPR" 
     ORGANIZATION IS INDEXED 
     ACCESS MODE IS DYNAMIC 
     RECORD KEY IS K1 = W2  ASCENDING WITH DUPLICATES 
     ALTERNATE 
 RECORD KEY IS K2 = W2 DESCENDING WITH DUPLICATES. 
DATA DIVISION. 
FILE SECTION. 
FD F1. 
01 R1. 
   02 W1 PIC X. 
   02 W2 PIC X. 
PROCEDURE DIVISION. 
P0. DISPLAY "***READ_PRIOR2***". 
*+ 
* Indexed file creation. 
*- 
    OPEN OUTPUT F1. 
    MOVE "a1" TO R1. 
    WRITE R1 INVALID KEY DISPLAY "?a1". 
    MOVE "b2" TO R1. 
    WRITE R1 INVALID KEY DISPLAY "?b2". 
    MOVE "c2" TO R1. 
    WRITE R1 INVALID KEY DISPLAY "?c2". 
    MOVE "d2" TO R1. 
    WRITE R1 INVALID KEY DISPLAY "?d2". 
    MOVE "e3" TO R1. 
    WRITE R1 INVALID KEY DISPLAY "?e3". 
    CLOSE F1. 
*+ 
* Read using ascending key. 
*- 
    OPEN INPUT F1. 
    DISPLAY "Read ascending key". 
    MOVE "0" TO W2. 
    START F1 KEY IS GREATER THAN K1 INVALID KEY DISPLAY "?S1". 
    PERFORM 5 TIMES 
      READ F1 NEXT AT END DISPLAY "?R2" END-READ 
      DISPLAY R1 
    END-PERFORM. 
    CLOSE F1. 
*+ 
* Read using descending key. 
*- 
    OPEN INPUT F1. 
    DISPLAY "Read descending key". 
    MOVE "4" TO W2. 
    START F1 KEY IS GREATER THAN K2 INVALID KEY DISPLAY "?S2". 
    PERFORM 5 TIMES 
      READ F1 NEXT AT END DISPLAY "?R2" END-READ 
      DISPLAY R1 
    END-PERFORM. 
*+ 
* READ PRIOR - note the difference in duplicate order from 
* Read with a descending key. 
*- 
    DISPLAY "Read prior". 
    MOVE "4" TO W2. 
    START F1 KEY IS LESS THAN K1 INVALID KEY DISPLAY "?S3". 
    PERFORM 5 TIMES 
      READ F1 PRIOR AT END DISPLAY "?R3" END-READ 
      DISPLAY R1 
    END-PERFORM. 
    CLOSE F1. 
    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). Refer to 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 File or Line Sequential (Alpha) 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-37 reads a sequential file and rewrites as many records as the operator wants.

Example 6-37 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. 

You cannot open a line sequential file (Alpha) for I-O or use the REWRITE statement. <>

Extending a Sequential File or Line Sequential File (Alpha)

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-38 shows how to extend a sequential file.

Example 6-38 Extending a Sequential File or Line Sequential File (Alpha)

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.

6.5.2 Updating a Relative File

A program updates a relative file with the WRITE, REWRITE, and DELETE statements. The WRITE statement adds a record to the file. Only the REWRITE and DELETE statements change the contents of records already existing in the file. In either case, adequate backup must be available in the event of error. Sections 6.5.2.1 and 6.5.2.2 explain how to rewrite and delete relative records, respectively.

6.5.2.1 Rewriting a Relative File

The REWRITE statement logically replaces a record in a relative file; the original contents of the record are lost. Two options are available for rewriting relative records:

Rewriting Relative Records in Sequential Access Mode

Rewriting relative records in sequential access mode involves the following:

  1. Specifying ORGANIZATION IS RELATIVE in the Environment Division SELECT clause
  2. Specifying ACCESS MODE IS SEQUENTIAL in the Environment Division SELECT clause
  3. Opening the file for I-O
  4. Using a START statement and then a READ statement to read the target record
  5. Updating the record
  6. Rewriting the record into its cell

Example 6-39 reads a relative record sequentially and displays the record on the terminal. The program then passes the record to an update routine that is not included in the example. The update routine updates the record, and passes the updated record back to the program illustrated in Example 6-39, which displays the updated record on the terminal and rewrites the record in the same cell.

Example 6-39 Rewriting Relative Records in Sequential Access Mode

IDENTIFICATION DIVISION. 
PROGRAM-ID. REL07. 
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 VALUE 99. 
PROCEDURE DIVISION. 
A000-BEGIN. 
    OPEN I-O FLAVORS. 
    PERFORM A100-UPDATE-RECORD UNTIL KETCHUP-MASTER-KEY = 00. 
A005-EOJ. 
    DISPLAY "END OF JOB". 
    CLOSE FLAVORS. 
    STOP RUN. 
A100-UPDATE-RECORD. 
    DISPLAY "TO UPDATE A RECORD ENTER ITS RECORD NUMBER (ZERO to END)". 
    ACCEPT KETCHUP-MASTER-KEY WITH CONVERSION. 
    IF KETCHUP-MASTER-KEY IS NOT EQUAL TO 00 
       START FLAVORS KEY IS EQUAL TO KETCHUP-MASTER-KEY 
             INVALID KEY DISPLAY "BAD START" 
                         STOP RUN. 
                    END-START 
       PERFORM A200-READ-FLAVORS 
       DISPLAY  "*********BEFORE UPDATE*********" 
       DISPLAY KETCHUP-MASTER 
************************************************************ 
* 
*      Update routine code here 
* 
************************************************************ 
       DISPLAY  "*********AFTER UPDATE*********" 
       DISPLAY KETCHUP-MASTER 
       REWRITE KETCHUP-MASTER. 
A200-READ-FLAVORS. 
    READ FLAVORS 
         AT END DISPLAY "END OF FILE" 
                GO TO A005-EOJ. 

Rewriting Relative Records in Random Access Mode

Rewriting relative records in random access mode 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 I-O
  4. Moving the relative record number value of the record you want to read to the RELATIVE KEY data name
  5. Reading the record from the cell identified by the relative record number
  6. Updating the record
  7. Rewriting the record into the cell identified by the relative record number

During execution of the REWRITE statement, the I/O system randomly reads the record identified by the RELATIVE KEY IS clause. The REWRITE statement then places the successfully read record back into its cell in the file.

If the cell does not contain a valid record, or if the REWRITE operation is unsuccessful, the invalid key condition occurs, and the REWRITE operation fails (see Chapter 7).

Example 6-40 reads a relative record randomly, displays its contents on the terminal, updates the record, displays its updated contents on the terminal, and rewrites the record in the same cell.

Example 6-40 Rewriting Relative Records in Random Access Mode

IDENTIFICATION DIVISION. 
PROGRAM-ID. REL08. 
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. 
PROCEDURE DIVISION. 
A000-BEGIN. 
    OPEN I-O FLAVORS. 
    PERFORM A100-UPDATE-RECORD UNTIL KETCHUP-MASTER-KEY = 00. 
A005-EOJ. 
    DISPLAY "END OF JOB". 
    CLOSE FLAVORS. 
    STOP RUN. 
A100-UPDATE-RECORD. 
    DISPLAY "TO UPDATE A RECORD ENTER ITS RECORD NUMBER". 
    ACCEPT KETCHUP-MASTER-KEY. 
    READ FLAVORS INVALID KEY DISPLAY "BAD READ" 
                        GO TO A005-EOJ. 
    DISPLAY  "*********BEFORE UPDATE*********". 
    DISPLAY KETCHUP-MASTER. 
******************************************************** 
* 
*               Update routine 
* 
******************************************************** 
    DISPLAY  "*********AFTER UPDATE*********". 
    DISPLAY KETCHUP-MASTER. 
    REWRITE KETCHUP-MASTER INVALID KEY DISPLAY "BAD REWRITE" 
                                       GO TO A005-EOJ. 

6.5.2.2 Deleting Records from a Relative File

The DELETE statement logically removes an existing record from a relative file. After successfully removing a record from a file, the program cannot later access it. Two options are available for deleting relative records:

Deleting a Relative Record in Sequential Access Mode

Deleting a relative record in sequential access mode involves the following:

  1. Specifying ORGANIZATION IS RELATIVE in the Environment Division SELECT clause
  2. Specifying ACCESS MODE IS SEQUENTIAL in the Environment Division SELECT clause
  3. Opening the file for I-O
  4. Using a START statement to position the record pointer, or sequentially reading the file up to the target record
  5. Deleting the last read record

Example 6-41 deletes relative records in sequential access mode.

Example 6-41 Deleting Relative Records in Sequential Access Mode

IDENTIFICATION DIVISION. 
PROGRAM-ID. REL09. 
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 VALUE 1. 
PROCEDURE DIVISION. 
A000-BEGIN. 
    OPEN I-O FLAVORS. 
    PERFORM A010-DELETE-RECORDS UNTIL KETCHUP-MASTER-KEY = 00. 
A005-EOJ. 
    DISPLAY "END OF JOB". 
    CLOSE FLAVORS. 
 
    STOP RUN. 
A010-DELETE-RECORDS. 
    DISPLAY "TO DELETE A RECORD ENTER ITS RECORD NUMBER". 
    ACCEPT KETCHUP-MASTER-KEY. 
    IF KETCHUP-MASTER-KEY NOT = 00 PERFORM A200-READ-FLAVORS 
                                   DELETE FLAVORS RECORD. 
A200-READ-FLAVORS. 
    START FLAVORS 
        INVALID KEY DISPLAY "INVALID START" 
                        STOP RUN. 
    READ FLAVORS AT END DISPLAY "FILE AT END" 
                        GO TO A005-EOJ. 

Deleting a Relative Record in Random Access Mode

Deleting a relative record in random access mode involves the following:

  1. Specifing ORGANIZATION IS RELATIVE in the Environment Division SELECT clause
  2. Specifying ACCESS MODE IS RANDOM in the Environment Division SELECT clause
  3. Opening the file for I-O
  4. Moving the relative record number value to the RELATIVE KEY data name
  5. Deleting the record identified by the relative record number

If the file does not contain a valid record, an invalid key condition exists.

Example 6-42 deletes relative records in random access mode.

Example 6-42 Deleting Relative Records in Random Access Mode

IDENTIFICATION DIVISION. 
PROGRAM-ID. REL10. 
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 1. 
PROCEDURE DIVISION. 
A000-BEGIN. 
    OPEN I-O FLAVORS. 
    PERFORM A010-DELETE-RECORDS UNTIL KETCHUP-MASTER-KEY = 00. 
A005-EOJ. 
    DISPLAY "END OF JOB". 
    CLOSE FLAVORS. 
    STOP RUN. 
A010-DELETE-RECORDS. 
    DISPLAY "TO DELETE A RECORD ENTER ITS RECORD NUMBER". 
    ACCEPT KETCHUP-MASTER-KEY. 
    IF KETCHUP-MASTER-KEY NOT = 00 
       DELETE FLAVORS RECORD 
              INVALID KEY DISPLAY "INVALID DELETE" 
                          STOP RUN. 


Previous Next Contents Index