Previous | Contents | Index |
However, the first way provides easier program readability when working with multiple record types. For example, 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)--------------- WRITE STOCK-RECORD FROM STOCK-WORK. MOVE STOCK-WORK TO STOCK-RECORD. WRITE STOCK-RECORD. |
When you omit the FROM phrase, you process the records directly in the record area or buffer (for example, STOCK-RECORD).
The following example writes the record PRINT-LINE to the device assigned to that record's file, then skips three lines. At the end of the page (as specified by the LINAGE clause), it causes program control to transfer to HEADER-ROUTINE.
WRITE PRINT-LINE BEFORE ADVANCING 3 LINES AT END-OF-PAGE PERFORM HEADER-ROUTINE. |
For a WRITE FROM statement, if the destination area is shorter than the
file's record length, the destination area is padded on the right with
spaces; if longer, the destination area is truncated on the right. This
follows the rules for a group move.
6.3.3 File Handling for Relative Files
Creating a relative file involves the following tasks:
Creating a Relative File in Sequential Access Mode
When your program creates a relative file in sequential access mode, the I/O system does not use the relative key. Instead, it writes the first record in the file at relative record number 1, the second record at relative record number 2, and so on, until the program closes the file. If you use the RELATIVE KEY IS clause, the compiler moves the relative record number of the record being written to the relative key data item. Example 6-24 writes 10 records with relative record numbers 1 to 10.
Example 6-24 Creating a Relative File in Sequential Access Mode |
---|
IDENTIFICATION DIVISION. PROGRAM-ID. REL02. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT FLAVORS ASSIGN TO "BRAND" ORGANIZATION IS RELATIVE ACCESS MODE IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD FLAVORS. 01 KETCHUP-MASTER. 02 FILLER PIC X(14). 02 REC-NUM PIC 9(05). 02 FILLER PIC X(31). 02 FILLER PIC X(31). WORKING-STORAGE SECTION. 01 REC-COUNT PIC S9(5) VALUE 0. PROCEDURE DIVISION. A000-BEGIN. OPEN OUTPUT FLAVORS. PERFORM A010-WRITE 10 TIMES. CLOSE FLAVORS. STOP RUN. A010-WRITE. MOVE "Record number" TO KETCHUP-MASTER. ADD 1 TO REC-COUNT. MOVE REC-COUNT TO REC-NUM. WRITE KETCHUP-MASTER INVALID KEY DISPLAY "BAD WRITE" STOP RUN. |
Creating a Relative File in Random Access Mode
When a program creates a relative file using random access mode, the program must place a value in the RELATIVE KEY data item before executing a WRITE statement. Example 6-25 shows how to supply the relative key. It writes 10 records in the cells numbered: 2, 4, 6, 8, 10, 12, 14, 16, 18, and 20. Record cells 1, 3, 5, 7, 9, 11, 13, 15, 17, and 19 are also created, but contain no valid records.
Example 6-25 Creating a Relative File in Random Access Mode |
---|
IDENTIFICATION DIVISION. PROGRAM-ID. REL03. 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. 02 FILLER PIC X(14). 02 REC-NUM PIC 9(05). 02 FILLER PIC X(31). WORKING-STORAGE SECTION. 01 KETCHUP-MASTER-KEY PIC 99. 01 REC-COUNT PIC S9(5) VALUE 0. PROCEDURE DIVISION. A000-BEGIN. OPEN OUTPUT FLAVORS. MOVE 0 TO KETCHUP-MASTER-KEY. PERFORM A010-CREATE-RELATIVE-FILE 10 TIMES. DISPLAY "END OF JOB". CLOSE FLAVORS. STOP RUN. A010-CREATE-RELATIVE-FILE. ADD 2 TO KETCHUP-MASTER-KEY. MOVE "Record number" TO KETCHUP-MASTER. ADD 2 TO REC-COUNT. MOVE REC-COUNT TO REC-NUM. WRITE KETCHUP-MASTER INVALID KEY DISPLAY "BAD WRITE" STOP RUN. |
Statements for Relative File Processing
Processing a relative file involves the following:
Table 6-5 lists the valid I/O statements and illustrates the following relationships:
Open Mode | ||||||
---|---|---|---|---|---|---|
File Organization |
Access Mode |
Statement | INPUT | OUTPUT | I-O | EXTEND |
RELATIVE | 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 |
Each WRITE statement places a record into a cell that contains no valid
data. If the cell does not already exist, the I/O system creates it. To
change the contents of a cell that already contains valid data, use the
REWRITE statement.
6.3.4 File Handling for Indexed Files
Creating an indexed file involves the following tasks:
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:
Statements for Indexed File Processing
Processing an indexed file involves the following:
Table 6-6 lists the valid I/O statements and illustrates the following relationships:
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 |
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). |
RECORD KEY IS NAME = SURNAME FORENAME INITIAL |
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.
See 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. |
Reading sequential, line sequential, relative, and indexed files includes the following tasks:
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 File
Reading a sequential or line sequential file involves the following:
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. |
Previous | Next | Contents | Index |