Michael Coughlan
Page 56
Example 17-2. Revision of GetFilmByDirectorId to Show All of a Director’s Films
GetFilmByDirectorId.
DISPLAY "Enter the Director Id - " WITH NO ADVANCING
ACCEPT DirectorId
READ FilmFile
KEY IS DirectorId
INVALID KEY DISPLAY "Film not found - " FilmStatus
NOT INVALID KEY DISPLAY FilmId SPACE FilmTitle SPACE DirectorId
PERFORM GetOtherFilmsByThisDirector
END-READ.
GetOtherFilmsByThisDirector.
MOVE DirectorId TO PrevDirectorId
READ FilmFile NEXT RECORD
AT END SET EndOfFilms TO TRUE
END-READ
PERFORM UNTIL DirectorId NOT EQUAL TO PrevDirectorId
OR EndOfFilms
DISPLAY FilmId SPACE FilmTitle SPACE DirectorId
READ FilmFile NEXT RECORD
AT END SET EndOfFilms TO TRUE
END-READ
END-PERFORM.
454
Chapter 17 ■ DireCt aCCess Files
Creating an Indexed File from a Sequential File
In Listing 17-5, an indexed file is created from a sequential file. Sequential files are useful because you can create them with an ordinary editor. There are tools available that can convert a sequential file into an indexed file, but this program does the job itself.
Listing 17-5. Creating an Indexed File from a Sequential File
IDENTIFICATION DIVISION.
PROGRAM-ID. Listing17-5.
AUTHOR. Michael Coughlan.
*Creating an Indexed File from a Sequential File
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
SELECT FilmFile ASSIGN TO "Listing17-5Film.DAT"
ORGANIZATION IS INDEXED
ACCESS MODE IS DYNAMIC
RECORD KEY IS FilmId
ALTERNATE RECORD KEY IS FilmTitle
WITH DUPLICATES
ALTERNATE RECORD KEY IS DirectorId
WITH DUPLICATES
FILE STATUS IS FilmStatus.
SELECT SeqFilmFile ASSIGN TO "Listing17-5Film.SEQ"
ORGANIZATION IS LINE SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD FilmFile.
01 FilmRec.
02 FilmId PIC 9(7).
02 FilmTitle PIC X(40).
02 DirectorId PIC 999.
FD SeqFilmFile.
01 SeqFilmRec PIC X(50).
88 EndOfFilmFile VALUE HIGH-VALUES.
WORKING-STORAGE SECTION.
01 FilmStatus PIC XX.
88 FilmOK VALUE ZEROS.
PROCEDURE DIVISION.
Begin.
OPEN INPUT SeqFilmFile
OPEN OUTPUT FilmFile
READ SeqFilmFile
AT END SET EndOfFilmFile TO TRUE
END-READ
455
Chapter 17 ■ DireCt aCCess Files
PERFORM UNTIL EndOfFilmFile
WRITE FilmRec FROM SeqFilmRec
INVALID KEY DISPLAY "Error writing to film file"
END-WRITE
READ SeqFilmFile
AT END SET EndOfFilmFile TO TRUE
END-READ
END-PERFORM
CLOSE SeqFilmFile, FilmFile
STOP RUN.
The first issue to bring to your attention is the statement WRITE FilmRec FROM SeqFilmRec. When you consider this statement, you may wonder why there is no KEY IS phrase as there is with the direct READ. The reason is that records are always written to an indexed file based on the value in the primary key, so no KEY IS phrase is required.
You may also wonder why I don’t put the key value into the primary-key data item before the WRITE is executed.
The answer is that I do put the key value into the primary-key data item—but I do it in a different way. WRITE FilmRec FROM SeqFilmRec has the same effect as
MOVE SeqFilmRec TO FilmRec
WRITE FilmRec
INVALID KEY DISPLAY "Error writing to film file"
END-WRITE
Using Indexed Files in Combination
Listing 17-6 uses an indexed file of film directors and an indexed file containing film details in combination to display all the films directed by a particular director. The program accepts the name of a director from the user and then displays all the films made by that director. For each film, the director ID, the surname of the director, the film ID, and the title of the film are displayed.
Listing 17-6. Using Indexed Files in Combination
IDENTIFICATION DIVISION.
PROGRAM-ID. Listing17-6.
AUTHOR. Michael Coughlan.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
SELECT FilmFile ASSIGN TO "Listing17-6Film.DAT"
ORGANIZATION IS INDEXED
ACCESS MODE IS DYNAMIC
RECORD KEY IS FilmId-FF
ALTERNATE RECORD KEY IS FilmTitle-FF
WITH DUPLICATES
ALTERNATE RECORD KEY IS DirectorId-FF
WITH DUPLICATES
FILE STATUS IS FilmStatus.
SELECT DirectorFile ASSIGN TO "Listing17-6Dir.DAT"
ORGANIZATION IS INDEXED
ACCESS MODE IS DYNAMIC
456
Chapter 17 ■ DireCt aCCess Files
RECORD KEY IS DirectorId-DF
ALTERNATE RECORD KEY IS DirectorSurname-DF
FILE STATUS IS DirectorStatus.
DATA DIVISION.
FILE SECTION.
FD FilmFile.
01 FilmRec-FF.
88 EndOfFilms VALUE HIGH-VALUES.
02 FilmId-FF PIC 9(7).
02 FilmTitle-FF PIC X(40).
02 DirectorId-FF PIC 999.
FD DirectorFile.
01 DirectorRec-DF.
88 EndOfDirectors VALUE HIGH-VALUES.
02 DirectorId-DF PIC 999.
02 DirectorSurname-DF PIC X(20).
WORKING-STORAGE SECTION.
01 AllStatusFlags VALUE ZEROS.
02 FilmStatus PIC XX.
88 FilmOk VALUE "02", "00".
02 DirectorStatus PIC XX.
01 DirectorName PIC X(20).
PROCEDURE DIVISION.
Begin.
OPEN INPUT FilmFile
OPEN INPUT DirectorFile
DISPLAY "Please enter the director surname :- "
WITH NO ADVANCING
ACCEPT DirectorSurname-DF
READ DirectorFile
KEY IS DirectorSurname-DF
INVALID KEY DISPLAY "-DF ERROR Status = " DirectorStatus
NOT INVALID KEY PERFORM GetFilmsForDirector
END-READ
CLOSE FilmFile
CLOSE DirectorFile
STOP RUN.
GetFilmsForDirector.
MOVE DirectorId-DF TO DirectorId-FF
READ FilmFile
KEY IS DirectorId-FF
457
Chapter 17 ■ DireCt aCCess Files
INVALID KEY DISPLAY "-FF ERROR Status = " FilmStatus
END-READ
IF FilmOk
PERFORM UNTIL DirectorId-DF NOT Equal TO DirectorId-FF OR EndOfFilms
DISPLAY DirectorId-DF SPACE DirectorSurname-DF SPACE
FilmId-FF SPACE FilmTitle-FF
READ FilmFile NEXT RECORD
AT END SET EndOfFilms TO TRUE
END-READ
END-PERFORM
END-IF.
This program uses two indexed files in combination. Used this way, indexed files are similar to a database where each file is a table, the records in the file are the table rows, and the fields in the records are the table columns.
The program starts by getting the name of the director from the user. This name is used as the key value for a direct READ on the director file. When the record is retrieved, DirectorId-DF is used to get all the director’s film titles.
One item of interest in the program is the file status for FilmFile. Note that one of two codes is specified to indicat
e the operation was successful. Normally, "00" indicates that the operation was successful; but in this case, the code "02" indicates success and also carries extra information. A code of "02" may be returned for indexed files only and is returned in these cases:
• When after a READ operation, the next record has the same key value as the key used for the READ
• When a WRITE or a REWRITE creates a duplicate key value for an alternate key that has the WITH
DUPLICATES phrase
If you want to detect when you have processed all the films directed by a particular director without having to compare keys, you can use the returned "02" code as shown in Example 17-3.
Example 17-3. Using the "02" File Status to Create a More Succinct Loop
01 AllStatusFlags VALUE ZEROS.
02 FilmStatus PIC XX.
88 AnotherFilmForThisDirector VALUE "02".
: : : : : : : : : : : : : : : :
GetFilmsForDirector.
MOVE DirectorId-DF TO DirectorId-FF
READ FilmFile
KEY IS DirectorId-FF
INVALID KEY DISPLAY "-FF ERROR Status = " FilmStatus
458
Chapter 17 ■ DireCt aCCess Files
NOT INVALID KEY DISPLAY DirectorId-DF SPACE DirectorSurname-DF SPACE
FilmId-FF SPACE FilmTitle-FF
END-READ
PERFORM UNTIL NOT AnotherFilmForThisDirector
READ FilmFile NEXT RECORD
AT END SET EndOfFilms TO TRUE
END-READ
DISPLAY DirectorId-DF SPACE DirectorSurname-DF SPACE
FilmId-FF SPACE FilmTitle-FF
END-PERFORM.
Applying Transactions to an Indexed File
Listing 17-7 applies a set of transactions (deletions, insertions, and updates) to the film file. The result of applying the transactions is shown in Figure 17-12. Applying the insertions to the film file is complicated by the issue of referential integrity. It should not be valid to insert a new film record when there is no record in the directors file for the director of the film. In a relational database system, referential integrity is automatically enforced by the database; but in COBOL, you have to do it yourself. The failure of programs to enforce referential integrity in COBOL legacy systems is one of the problems of legacy data. If you try to load such legacy data into a relational database that does enforce referential integrity, uniqueness, and other standards, the database system will probably crash.
Listing 17-7. Applying Transactions to an Indexed File
IDENTIFICATION DIVISION.
PROGRAM-ID. Listing17-7.
AUTHOR. Michael Coughlan.
*Applies transactions to the Indexed FilmFile and enforces referential integrity
*with the Indexed Directors File
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
SELECT FilmFile ASSIGN TO "Listing17-7Films.DAT"
ORGANIZATION IS INDEXED
ACCESS MODE IS DYNAMIC
RECORD KEY IS FilmId-FF
ALTERNATE RECORD KEY IS FilmTitle-FF
WITH DUPLICATES
ALTERNATE RECORD KEY IS DirectorId-FF
WITH DUPLICATES
FILE STATUS IS FilmStatus.
SELECT DirectorsFile ASSIGN TO "Listing17-7Dir.DAT"
ORGANIZATION IS INDEXED
ACCESS MODE IS DYNAMIC
RECORD KEY IS DirectorId-DF
ALTERNATE RECORD KEY IS DirectorSurname-DF
FILE STATUS IS DirectorStatus.
SELECT TransFile ASSIGN TO "Listing17-7Trans.dat"
ORGANIZATION IS LINE SEQUENTIAL.
459
Chapter 17 ■ DireCt aCCess Files
DATA DIVISION.
FILE SECTION.
FD FilmFile.
01 FilmRec-FF.
88 EndOfFilms VALUE HIGH-VALUES.
02 FilmId-FF PIC 9(7).
02 FilmTitle-FF PIC X(40).
02 DirectorId-FF PIC 9(3).
FD DirectorsFile.
01 DirectorsRec-DF.
88 EndOfDirectors VALUE HIGH-VALUES.
02 DirectorId-DF PIC 9(3).
02 DirectorSurname-DF PIC X(20).
FD TransFile.
01 DeletionRec-TF.
88 EndOfTrans VALUE HIGH-VALUES.
02 TypeId-TF PIC X.
88 DoDeletion VALUE "D".
88 DoInsertion VALUE "I".
88 DoUpdate VALUE "U".
02 FilmId-TF PIC 9(7).
01 InsertionRec-TF.
02 FILLER PIC 9.
02 InsertionBody-TF.
03 FILLER PIC X(47).
03 DirectorId-TF PIC 9(3).
01 UpdateRec-TF.
02 FILLER PIC X(8).
02 FilmTitle-TF PIC X(40).
WORKING-STORAGE SECTION.
01 AllStatusFlags VALUE ZEROS.
02 FilmStatus PIC XX.
88 FilmOK VALUE ZEROS.
02 DirectorStatus PIC XX.
88 MatchingDirectorFound VALUE ZEROS.
PROCEDURE DIVISION.
Begin.
OPEN I-O FilmFile
OPEN INPUT DirectorsFile
OPEN INPUT TransFile
DISPLAY "*** Film file before updates ***"
PERFORM DisplayFilmFileContents
DISPLAY SPACES
READ TransFile
AT END SET EndOfTrans TO TRUE
END-READ
460
Chapter 17 ■ DireCt aCCess Files
PERFORM UpdateFilmFile UNTIL EndofTrans
DISPLAY SPACES
DISPLAY "*** Film file after updates ***"
PERFORM DisplayFilmFileContents
CLOSE FilmFile, DirectorsFile, TransFile
STOP RUN.
DisplayFilmFileContents.
MOVE ZEROS TO FilmId-FF
START FilmFile KEY IS GREATER THAN FilmId-FF
INVALID KEY DISPLAY "Error1 - FilmStatus = " FilmStatus
END-START
READ FilmFile NEXT RECORD
AT END SET EndOfFilms TO TRUE
END-READ
PERFORM UNTIL EndOfFilms
DISPLAY FilmId-FF SPACE DirectorId-FF SPACE FilmTitle-FF
READ FilmFile NEXT RECORD
AT END SET EndOfFilms TO TRUE
END-READ
END-PERFORM.
UpdateFilmFile.
EVALUATE TRUE
WHEN DoDeletion PERFORM DeleteFilmRec
WHEN DoInsertion PERFORM InsertFilmRec
WHEN DoUpdate PERFORM UpdateFilmRec
END-EVALUATE
READ TransFile
AT END SET EndOfTrans TO TRUE
END-READ.
DeleteFilmRec.
MOVE FilmId-TF TO FilmId-FF
DELETE FilmFile RECORD
INVALID KEY DISPLAY FilmId-FF " - Delete Error. No such record"
END-DELETE.
InsertFilmRec.
*To preserve Referential Integrity check director exists for this Film
MOVE DirectorId-TF TO DirectorId-DF
START DirectorsFile
KEY IS EQUAL TO DirectorId-DF
INVALID KEY DISPLAY FilmId-FF " - Insert Error. No matching entry for director - "
DirectorId-TF
END-START
IF MatchingDirectorFound
MOVE InsertionBody-TF TO FilmRec-FF
WRITE FilmRec-FF
INVALID KEY DISPLAY FilmId-FF " - Insert Error. That FilmId already exists."
END-WRITE
END-IF.
461
Chapter 17 ■ DireCt aCCess Files
UpdateFilmRec.
MOVE FilmId-TF TO FilmId-FF
READ FilmFile RECORD
KEY IS FilmId-FF
INVALID KEY DISPLAY FilmId-FF " - Update error. No such record exists"
END-READ
IF FilmOk
MOVE FilmTitle-TF TO FilmTitle-FF
REWRITE FilmRec-FF
INVALID KEY DISPLAY "Unexpected Error1. FilmStatus - " FilmStatus
&
nbsp; END-REWRITE
END-IF.
Figure 17-12. Output from Listing 17-7
462
Chapter 17 ■ DireCt aCCess Files
There is not much to talk about here that I have not already discussed in relation to relative files, but let’s touch once more on the issue of referential integrity. When an insertion record has to be applied to FilmFile, you must make sure the director of that film has an entry in DirectorsFile. You do this in InsertFilmRec by using START with DirectorsFile and the director ID from TransFile to make sure there is a director with that ID in DirectorsFile. If there is a director with that ID, you try to apply the insertion.
Indexed Files: Syntax and Semantics
This section formally introduces the specific verb formats, clauses, and concepts required for indexed files.
Indexed Files: SELECT and ASSIGN Clause
The metalanguage for the SELECT and ASSIGN clause for indexed files is shown in Figure 17-13.
Figure 17-13. Metalanguage for SELECT and ASSIGN specific to indexed files
Consider the following:
• The key defined for a relative file by the RELATIVE KEY phrase in the SELECT and ASSIGN clause
cannot be a field in the record of the relative file. In total contrast to this, every key (primary and alternates) defined for an indexed file must be a field in record of the indexed file.
• Every indexed file must have a primary key and may have up to 254 alternate keys.
• The primary key must be unique for each record and must be a numeric or alphanumeric data
item. The primary key is identified by the RECORD KEY IS phrase in the SELECT and ASSIGN
clause.
• Each alternate key must be numeric or alphanumeric and may be unique or may have
duplicate values. The alternate keys are identified by the ALTERNATE RECORD KEY IS phrase in
the SELECT and ASSIGN clause.
• If an alternate key can have duplicate values, then the WITH DUPLICATES phrase must be
used. If WITH DUPLICATES is not used and you attempt to write a record that contains an
alternate-key value that is already present in another record in the file, WRITE will fail,
and a file status "22" (record already exists) will be returned.