You have studied indexed files rather intensively for the last three days, and it's important that you review these concepts before you tackle anything new. Today, you take a look at a single program that combines all the maintenance modes--Add, Change, Inquire (Look Up) and Delete--in one program. You also learn more about the following topics:
An indexed file is defined both logically and physically. The logical description is an FD in the FILE SECTION of the DATA DIVISION, as shown in Listing 14.1.
001600 DATA DIVISION. 001700 FILE SECTION. 001800 001900 FD VENDOR-FILE 002000 LABEL RECORDS ARE STANDARD. 002100 01 VENDOR-RECORD. 002200 05 VENDOR-NUMBER PIC 9(5). 002300 05 VENDOR-NAME PIC X(30). 002400 05 VENDOR-ADDRESS-1 PIC X(30). 002500 05 VENDOR-ADDRESS-2 PIC X(30). 002600 05 VENDOR-CITY PIC X(20). 002700 05 VENDOR-STATE PIC X(2). 002800 05 VENDOR-ZIP PIC X(10). 002900 05 VENDOR-CONTACT PIC X(30). 003000 05 VENDOR-PHONE PIC X(15).
ANALYSIS: The physical description is the SELECT statement in the FILE-CONTROL paragraph of the INPUT-OUTPUT SECTION of the ENVIRONMENT DIVISION, as shown in Listing 14.2. At lines 001000 and 001100, the logical VENDOR-FILE is associated with a physical file named "VENDOR" on the computer hard disk or other storage device. This file will have the physical name "VENDOR", "VENDOR.DAT", or something similar, on the disk or tape. At line 001200, the file organization is specified to be indexed. At line 001300, a field in the logical description of the file (in Listing 14.1) is named as the primary index or primary key to the file. The access mode is made dynamic at line 001400.
000600 ENVIRONMENT DIVISION. 000700 INPUT-OUTPUT SECTION. 000800 FILE-CONTROL. 000900 001000 SELECT VENDOR-FILE 001100 ASSIGN TO "VENDOR" 001200 ORGANIZATION IS INDEXED 001300 RECORD KEY IS VENDOR-NUMBER 001400 ACCESS MODE IS DYNAMIC. 001500
Remember that any part of a COBOL program can be written in a separate file and included in the main file by using a COPY statement in the main file. Although you can do this with any part of a program, it is common to do it with the SELECT and FD of a file. By using a COPY statement in any program that uses that file, you can ensure that each program has defined the file in the same way. An example is shown in Listing 14.3.
000600 ENVIRONMENT DIVISION. 000700 INPUT-OUTPUT SECTION. 000800 FILE-CONTROL. 000900 001000 COPY "SLVND01.CBL". 001100 001200 DATA DIVISION. 001300 FILE SECTION. 001400 001500 COPY "FDVND01.CBL". 001600
You open an indexed file by specifying the open mode and the filename. Output mode creates a new file; I/O mode allows reading and writing access to an existing file. You close a file by naming the file after a CLOSE command. Listings 14.4 and 14.5 show examples of opening and closing files.
003500 PROGRAM-BEGIN. 003600 OPEN OUTPUT VENDOR-FILE. 003700 CLOSE VENDOR-FILE.
003400 PROCEDURE DIVISION. 003500 PROGRAM-BEGIN. 003600 OPEN I-O VENDOR-FILE. 003700 PERFORM MAIN-PROCESS. 003800 CLOSE VENDOR-FILE.
When an indexed file is opened in I/O or input mode, the file is usually set up so that a READ NEXT on the file retrieves the record with the lowest primary key value. In Listing 14.6, the READ NEXT action either reads the record with the primary key of the lowest value, or it produces an error if no records are in the file.
003600 OPEN I-O VENDOR-FILE. 003700 READ VENDOR-FILE NEXT RECORD.
A READ NEXT should use the AT END condition to trap a file error condition at the end of the file, as shown in Listing 14.7.
003600 READ-NEXT-VENDOR-RECORD. 003700 READ VENDOR-FILE NEXT RECORD 003800 AT END MOVE "Y" TO END-OF-FILE.
Records are added to the file by loading the values in the record and using a WRITE command followed by the name of the record. The INVALID KEY condition should be used to trap write errors (as shown in Listing 14.8). These can be caused by trying to write a record with a primary key value that is the same as a record already in the file. Each record in an indexed file must have a unique primary key.
005100 WRITE-VENDOR-RECORD. 005200 WRITE VENDOR-RECORD 005300 INVALID KEY 005400 DISPLAY "RECORD ALREADY ON FILE".
A record can be read from an indexed file by moving a value to the field that is the primary key of the file and using READ (as shown in Listing 14.9). The INVALID KEY condition should be used to trap file error conditions that happen when a record does not exist that matches the value requested in the primary key field.
019800 PERFORM ENTER-VENDOR-NUMBER. 019900 MOVE "Y" TO RECORD-FOUND. 020000 READ VENDOR-FILE RECORD 020100 INVALID KEY 020200 MOVE "N" TO RECORD-FOUND. 020300
You can change a record in an indexed file by reading the original record, loading the new values into the fields of the record, and then using a REWRITE command followed by the name of the record (as shown in Listing 14.10). The primary key of the record cannot be changed using this method, but any other field in the record can be changed.
019200 PERFORM ENTER-VENDOR-NUMBER. 019300 PERFORM READ-VENDOR-RECORD. 019400 IF RECORD-FOUND = "Y" 019500 PERFORM LOAD-NEW-VENDOR-DATA 019600 PERFORM REWRITE-VENDOR-RECORD. 019700 019800 READ-VENDOR-RECORD. 019900 MOVE "Y" TO RECORD-FOUND. 020000 READ VENDOR-FILE RECORD 020100 INVALID KEY 020200 MOVE "N" TO RECORD-FOUND. 020300 020400 REWRITE-VENDOR-RECORD. 020500 REWRITE VENDOR-RECORD 020600 INVALID KEY 020700 DISPLAY "ERROR REWRITING VENDOR RECORD".
You can delete a record from an indexed file by reading the original record and then using the DELETE command, followed by the name of the file (as shown in Listing 14.11).
019300 PERFORM ENTER-VENDOR-NUMBER. 019400 PERFORM READ-VENDOR-RECORD. 019500 IF RECORD-FOUND = "Y" 019600 PERFORM DELETE-VENDOR-RECORD. 019700 019800 READ-VENDOR-RECORD. 019900 MOVE "Y" TO RECORD-FOUND. 020000 READ VENDOR-FILE RECORD 020100 INVALID KEY 020200 MOVE "N" TO RECORD-FOUND. 020300 020400 DELETE-VENDOR-RECORD. 020500 DELETE VENDOR-FILE RECORD 020600 INVALID KEY 020700 DISPLAY "ERROR DELETING VENDOR RECORD".
It is confusing that some file operations are performed using the filename and some are performed using the record name. Two examples of these statements appear at lines 020000 and 020500 in Listing 14.10. Just remember that WRITE and REWRITE use the record name; all other file operations, including those you have not yet learned, use the filename.
Some COBOL programmers try to remember this with the rule "Read a file, write a record." This rule is a little short on detail because it doesn't mention OPEN, CLOSE, DELETE, and REWRITE. It is better to remember, "Write and rewrite a record, do everything else to a file."
All of the four maintenance programs share common elements, and it is possible to combine the four modes into one program and take advantage of this common code.
Whether or not you do this is a matter for system design consideration. In some systems, all users have access to Inquire (Look Up) mode, several might have access to Add or Change mode, and possibly only a few have access to Delete mode. Security is much easier to control when the four modes are separate. Less coding is involved when the four modes are combined. Listing 14.12 combines all four programs into one maintenance program, with a menu for selecting the mode to be used while running the program.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. VNDMNT01. 000300*-------------------------------- 000400* Add, Change, Inquire, and Delete 000500* for the Vendor File. 000600*-------------------------------- 000700 ENVIRONMENT DIVISION. 000800 INPUT-OUTPUT SECTION. 000900 FILE-CONTROL. 001000 001100 COPY "SLVND01.CBL". 001200 001300 DATA DIVISION. 001400 FILE SECTION. 001500 001600 COPY "FDVND02.CBL". 001700 001800 WORKING-STORAGE SECTION. 001900 002000 77 MENU-PICK PIC 9. 002100 88 MENU-PICK-IS-VALID VALUES 0 THRU 4. 002200 002300 77 THE-MODE PIC X(7). 002400 77 WHICH-FIELD PIC 9. 002500 77 OK-TO-DELETE PIC X. 002600 77 RECORD-FOUND PIC X. 002700 77 VENDOR-NUMBER-FIELD PIC Z(5). 002800 002900 PROCEDURE DIVISION. 003000 PROGRAM-BEGIN. 003100 PERFORM OPENING-PROCEDURE. 003200 PERFORM MAIN-PROCESS. 003300 PERFORM CLOSING-PROCEDURE. 003400 003500 PROGRAM-DONE. 003600 STOP RUN. 003700 003800 OPENING-PROCEDURE. 003900 OPEN I-O VENDOR-FILE. 004000 004100 CLOSING-PROCEDURE. 004200 CLOSE VENDOR-FILE. 004300 004400 004500 MAIN-PROCESS. 004600 PERFORM GET-MENU-PICK. 004700 PERFORM MAINTAIN-THE-FILE 004800 UNTIL MENU-PICK = 0. 004900 005000*-------------------------------- 005100* MENU 005200*-------------------------------- 005300 GET-MENU-PICK. 005400 PERFORM DISPLAY-THE-MENU. 005500 PERFORM GET-THE-PICK. 005600 PERFORM MENU-RETRY 005700 UNTIL MENU-PICK-IS-VALID. 005800 005900 DISPLAY-THE-MENU. 006000 PERFORM CLEAR-SCREEN. 006100 DISPLAY " PLEASE SELECT:". 006200 DISPLAY " ". 006300 DISPLAY " 1. ADD RECORDS". 006400 DISPLAY " 2. CHANGE A RECORD". 006500 DISPLAY " 3. LOOK UP A RECORD". 006600 DISPLAY " 4. DELETE A RECORD". 006700 DISPLAY " ". 006800 DISPLAY " 0. EXIT". 006900 PERFORM SCROLL-LINE 8 TIMES. 007000 007100 GET-THE-PICK. 007200 DISPLAY "YOUR CHOICE (0-4)?". 007300 ACCEPT MENU-PICK. 007400 MENU-RETRY. 007500 DISPLAY "INVALID SELECTION - PLEASE RE-TRY.". 007600 PERFORM GET-THE-PICK. 007700 CLEAR-SCREEN. 007800 PERFORM SCROLL-LINE 25 TIMES. 007900 008000 SCROLL-LINE. 008100 DISPLAY " ". 008200 008300 MAINTAIN-THE-FILE. 008400 PERFORM DO-THE-PICK. 008500 PERFORM GET-MENU-PICK. 008600 008700 DO-THE-PICK. 008800 IF MENU-PICK = 1 008900 PERFORM ADD-MODE 009000 ELSE 009100 IF MENU-PICK = 2 009200 PERFORM CHANGE-MODE 009300 ELSE 009400 IF MENU-PICK = 3 009500 PERFORM INQUIRE-MODE 009600 ELSE 009700 IF MENU-PICK = 4 009800 PERFORM DELETE-MODE. 009900 010000*-------------------------------- 010100* ADD 010200*-------------------------------- 010300 ADD-MODE. 010400 MOVE "ADD" TO THE-MODE. 010500 PERFORM GET-NEW-VENDOR-NUMBER. 010600 PERFORM ADD-RECORDS 010700 UNTIL VENDOR-NUMBER = ZEROES. 010800 010900 GET-NEW-VENDOR-NUMBER. 011000 PERFORM INIT-VENDOR-RECORD. 011100 PERFORM ENTER-VENDOR-NUMBER. 011200 MOVE "Y" TO RECORD-FOUND. 011300 PERFORM FIND-NEW-VENDOR-RECORD 011400 UNTIL RECORD-FOUND = "N" OR 011500 VENDOR-NUMBER = ZEROES. 011600 011700 FIND-NEW-VENDOR-RECORD. 011800 PERFORM READ-VENDOR-RECORD. 011900 IF RECORD-FOUND = "Y" 012000 DISPLAY "RECORD ALREADY ON FILE" 012100 PERFORM ENTER-VENDOR-NUMBER. 012200 012300 ADD-RECORDS. 012400 PERFORM ENTER-REMAINING-FIELDS. 012500 PERFORM WRITE-VENDOR-RECORD. 012600 PERFORM GET-NEW-VENDOR-NUMBER. 012700 012800 ENTER-REMAINING-FIELDS. 012900 PERFORM ENTER-VENDOR-NAME. 013000 PERFORM ENTER-VENDOR-ADDRESS-1. 013100 PERFORM ENTER-VENDOR-ADDRESS-2. 013200 PERFORM ENTER-VENDOR-CITY. 013300 PERFORM ENTER-VENDOR-STATE. 013400 PERFORM ENTER-VENDOR-ZIP. 013500 PERFORM ENTER-VENDOR-CONTACT. 013600 PERFORM ENTER-VENDOR-PHONE. 013700 013800*-------------------------------- 013900* CHANGE 014000*-------------------------------- 014100 CHANGE-MODE. 014200 MOVE "CHANGE" TO THE-MODE. 014300 PERFORM GET-VENDOR-RECORD. 014400 PERFORM CHANGE-RECORDS 014500 UNTIL VENDOR-NUMBER = ZEROES. 014600 014700 CHANGE-RECORDS. 014800 PERFORM GET-FIELD-TO-CHANGE. 014900 PERFORM CHANGE-ONE-FIELD 015000 UNTIL WHICH-FIELD = ZERO. 015100 PERFORM GET-VENDOR-RECORD. 015200 015300 GET-FIELD-TO-CHANGE. 015400 PERFORM DISPLAY-ALL-FIELDS. 015500 PERFORM ASK-WHICH-FIELD. 015600 015700 ASK-WHICH-FIELD. 015800 DISPLAY "ENTER THE NUMBER OF THE FIELD". 015900 DISPLAY "TO CHANGE (1-8) OR 0 TO EXIT". 016000 ACCEPT WHICH-FIELD. 016100 IF WHICH-FIELD > 8 016200 DISPLAY "INVALID ENTRY". 016300 016400 CHANGE-ONE-FIELD. 016500 PERFORM CHANGE-THIS-FIELD. 016600 PERFORM GET-FIELD-TO-CHANGE. 016700 016800 CHANGE-THIS-FIELD. 016900 IF WHICH-FIELD = 1 017000 PERFORM ENTER-VENDOR-NAME. 017100 IF WHICH-FIELD = 2 017200 PERFORM ENTER-VENDOR-ADDRESS-1. 017300 IF WHICH-FIELD = 3 017400 PERFORM ENTER-VENDOR-ADDRESS-2. 017500 IF WHICH-FIELD = 4 017600 PERFORM ENTER-VENDOR-CITY. 017700 IF WHICH-FIELD = 5 017800 PERFORM ENTER-VENDOR-STATE. 017900 IF WHICH-FIELD = 6 018000 PERFORM ENTER-VENDOR-ZIP. 018100 IF WHICH-FIELD = 7 018200 PERFORM ENTER-VENDOR-CONTACT. 018300 IF WHICH-FIELD = 8 018400 PERFORM ENTER-VENDOR-PHONE. 018500 018600 PERFORM REWRITE-VENDOR-RECORD. 018700 018800*-------------------------------- 018900* INQUIRE 019000*-------------------------------- 019100 INQUIRE-MODE. 019200 MOVE "DISPLAY" TO THE-MODE. 019300 PERFORM GET-VENDOR-RECORD. 019400 PERFORM INQUIRE-RECORDS 019500 UNTIL VENDOR-NUMBER = ZEROES. 019600 019700 INQUIRE-RECORDS. 019800 PERFORM DISPLAY-ALL-FIELDS. 019900 PERFORM GET-VENDOR-RECORD. 020000 020100*-------------------------------- 020200* DELETE 020300*-------------------------------- 020400 DELETE-MODE. 020500 MOVE "DELETE" TO THE-MODE. 020600 PERFORM GET-VENDOR-RECORD. 020700 PERFORM DELETE-RECORDS 020800 UNTIL VENDOR-NUMBER = ZEROES. 020900 021000 DELETE-RECORDS. 021100 PERFORM DISPLAY-ALL-FIELDS. 021200 MOVE "X" TO OK-TO-DELETE. 021300 021400 PERFORM ASK-TO-DELETE 021500 UNTIL OK-TO-DELETE = "Y" OR "N". 021600 021700 IF OK-TO-DELETE = "Y" 021800 PERFORM DELETE-VENDOR-RECORD. 021900 022000 PERFORM GET-VENDOR-RECORD. 022100 022200 ASK-TO-DELETE. 022300 DISPLAY "DELETE THIS RECORD (Y/N)?". 022400 ACCEPT OK-TO-DELETE. 022500 IF OK-TO-DELETE = "y" 022600 MOVE "Y" TO OK-TO-DELETE. 022700 IF OK-TO-DELETE = "n" 022800 MOVE "N" TO OK-TO-DELETE. 022900 IF OK-TO-DELETE NOT = "Y" AND 023000 OK-TO-DELETE NOT = "N" 023100 DISPLAY "YOU MUST ENTER YES OR NO". 023200 023300*-------------------------------- 023400* Routines shared by all modes 023500*-------------------------------- 023600 INIT-VENDOR-RECORD. 023700 MOVE SPACE TO VENDOR-RECORD. 023800 MOVE ZEROES TO VENDOR-NUMBER. 023900 024000 ENTER-VENDOR-NUMBER. 024100 DISPLAY " ". 024200 DISPLAY "ENTER VENDOR NUMBER OF THE VENDOR" . 024300 DISPLAY "TO " THE-MODE " (1-99999)". 024400 DISPLAY "ENTER 0 TO STOP ENTRY". 024500 ACCEPT VENDOR-NUMBER-FIELD. 024600*OR ACCEPT VENDOR-NUMBER-FIELD WITH CONVERSION. 024700 024800 MOVE VENDOR-NUMBER-FIELD TO VENDOR-NUMBER. 024900 025000 GET-VENDOR-RECORD. 025100 PERFORM INIT-VENDOR-RECORD. 025200 PERFORM ENTER-VENDOR-NUMBER. 025300 MOVE "N" TO RECORD-FOUND. 025400 PERFORM FIND-VENDOR-RECORD 025500 UNTIL RECORD-FOUND = "Y" OR 025600 VENDOR-NUMBER = ZEROES. 025700 025800*-------------------------------- 025900* Routines shared Add and Change 026000*-------------------------------- 026100 FIND-VENDOR-RECORD. 026200 PERFORM READ-VENDOR-RECORD. 026300 IF RECORD-FOUND = "N" 026400 DISPLAY "RECORD NOT FOUND" 026500 PERFORM ENTER-VENDOR-NUMBER. 026600 026700 ENTER-VENDOR-NAME. 026800 DISPLAY "ENTER VENDOR NAME". 026900 ACCEPT VENDOR-NAME. 027000 027100 ENTER-VENDOR-ADDRESS-1. 027200 DISPLAY "ENTER VENDOR ADDRESS-1". 027300 ACCEPT VENDOR-ADDRESS-1. 027400 027500 ENTER-VENDOR-ADDRESS-2. 027600 DISPLAY "ENTER VENDOR ADDRESS-2". 027700 ACCEPT VENDOR-ADDRESS-2. 027800 027900 ENTER-VENDOR-CITY. 028000 DISPLAY "ENTER VENDOR CITY". 028100 ACCEPT VENDOR-CITY. 028200 028300 ENTER-VENDOR-STATE. 028400 DISPLAY "ENTER VENDOR STATE". 028500 ACCEPT VENDOR-STATE. 028600 028700 ENTER-VENDOR-ZIP. 028800 DISPLAY "ENTER VENDOR ZIP". 028900 ACCEPT VENDOR-ZIP. 029000 029100 ENTER-VENDOR-CONTACT. 029200 DISPLAY "ENTER VENDOR CONTACT". 029300 ACCEPT VENDOR-CONTACT. 029400 029500 ENTER-VENDOR-PHONE. 029600 DISPLAY "ENTER VENDOR PHONE". 029700 ACCEPT VENDOR-PHONE. 029800 029900*-------------------------------- 030000* Routines shared by Change, 030100* Inquire and Delete 030200*-------------------------------- 030300 DISPLAY-ALL-FIELDS. 030400 DISPLAY " ". 030500 PERFORM DISPLAY-VENDOR-NUMBER. 030600 PERFORM DISPLAY-VENDOR-NAME. 030700 PERFORM DISPLAY-VENDOR-ADDRESS-1. 030800 PERFORM DISPLAY-VENDOR-ADDRESS-2. 030900 PERFORM DISPLAY-VENDOR-CITY. 031000 PERFORM DISPLAY-VENDOR-STATE. 031100 PERFORM DISPLAY-VENDOR-ZIP. 031200 PERFORM DISPLAY-VENDOR-CONTACT. 031300 PERFORM DISPLAY-VENDOR-PHONE. 031400 DISPLAY " ". 031500 031600 DISPLAY-VENDOR-NUMBER. 031700 DISPLAY " VENDOR NUMBER: " VENDOR-NUMBER. 031800 031900 DISPLAY-VENDOR-NAME. 032000 DISPLAY "1. VENDOR NAME: " VENDOR-NAME. 032100 032200 DISPLAY-VENDOR-ADDRESS-1. 032300 DISPLAY "2. VENDOR ADDRESS-1: " VENDOR-ADDRESS-1. 032400 032500 DISPLAY-VENDOR-ADDRESS-2. 032600 DISPLAY "3. VENDOR ADDRESS-2: " VENDOR-ADDRESS-2. 032700 032800 DISPLAY-VENDOR-CITY. 032900 DISPLAY "4. VENDOR CITY: " VENDOR-CITY. 033000 033100 DISPLAY-VENDOR-STATE. 033200 DISPLAY "5. VENDOR STATE: " VENDOR-STATE. 033300 033400 DISPLAY-VENDOR-ZIP. 033500 DISPLAY "6. VENDOR ZIP: " VENDOR-ZIP. 033600 033700 DISPLAY-VENDOR-CONTACT. 033800 DISPLAY "7. VENDOR CONTACT: " VENDOR-CONTACT. 033900 034000 DISPLAY-VENDOR-PHONE. 034100 DISPLAY "8. VENDOR PHONE: " VENDOR-PHONE. 034200 034300*-------------------------------- 034400* File I-O Routines 034500*-------------------------------- 034600 READ-VENDOR-RECORD. 034700 MOVE "Y" TO RECORD-FOUND. 034800 READ VENDOR-FILE RECORD 034900 INVALID KEY 035000 MOVE "N" TO RECORD-FOUND. 035100 035200*or READ VENDOR-FILE RECORD WITH LOCK 035300* INVALID KEY 035400* MOVE "N" TO RECORD-FOUND. 035500 035600*or READ VENDOR-FILE RECORD WITH HOLD 035700* INVALID KEY 035800* MOVE "N" TO RECORD-FOUND. 035900 036000 WRITE-VENDOR-RECORD. 036100 WRITE VENDOR-RECORD 036200 INVALID KEY 036300 DISPLAY "RECORD ALREADY ON FILE". 036400 036500 REWRITE-VENDOR-RECORD. 036600 REWRITE VENDOR-RECORD 036700 INVALID KEY 036800 DISPLAY "ERROR REWRITING VENDOR RECORD". 036900 037000 DELETE-VENDOR-RECORD. 037100 DELETE VENDOR-FILE RECORD 037200 INVALID KEY 037300 DISPLAY "ERROR DELETING VENDOR RECORD". 037400
The following menu output of vndmnt01.cbl asks the user to select an entry mode:
OUTPUT:
PLEASE SELECT: 1. ADD RECORDS 2. CHANGE A RECORD 3. LOOK UP A RECORD 4. DELETE A RECORD 0. EXIT YOUR CHOICE (0-4)?
ANALYSIS: The sections of the program have been moved around to separate the routines that are exclusive to the menu, or to Add, Change, Inquire, and Delete modes.
Other sections have been created to combine the routines that are shared by different modes. Each of these groups of code is commented. Two deliberate errors are in this collection. Two paragraphs are grouped under comments where they don't really belong. This is for the exercises at the end of the chapter. If you happen to spot them, you've got a jump on the exercise.
Even though this program is nearly 400 lines long, it is possible to break it into sections and understand these sections one piece at a time. A couple of changes have been made in Add mode, but overall, the combined program is the same as the code used in the separate programs.
One trick was used in ENTER-VENDOR-NUMBER at line 024000. In the original add, change, delete, and inquire programs, the prompt for the user to enter the vendor number is one of the following:
ENTER VENDOR NUMBER OF THE VENDOR TO ADD (1-99999) ENTER 0 TO STOP ENTRY ENTER VENDOR NUMBER OF THE VENDOR TO CHANGE (1-99999) ENTER 0 TO STOP ENTRY ENTER VENDOR NUMBER OF THE VENDOR TO DISPLAY (1-99999) ENTER 0 TO STOP ENTRY ENTER VENDOR NUMBER OF THE VENDOR TO DELETE (1-99999) ENTER 0 TO STOP ENTRY
These prompts are identical except for the bold keyword.
In vndmnt01.cbl, the display logic has been changed to the code shown in Listing 14.13.
024200 DISPLAY "ENTER VENDOR NUMBER OF THE VENDOR" . 024300 DISPLAY "TO " THE-MODE " (1-99999)". 024400 DISPLAY "ENTER 0 TO STOP ENTRY".
ANALYSIS: THE-MODE is filled in at the beginning of each mode at lines 010400, 014200, 019200, and 020500 with "ADD", "CHANGE", "DISPLAY", or "DELETE".
The GET-MENU-PICK logic starting at line 005300 displays the menu, asks the user for an entry, and then starts a processing loop if the user has entered an invalid entry. The processing loop consists of displaying an invalid entry message and then asking for another entry. Figure 14.1 illustrates this relationship.
Figure 14.1.
The menu pick loop.
One other new coding technique is used in DO-THE-PICK at line 008700. This is the use of a series of IF ELSE combinations linked one to the other as shown in Listing 14.14 (extracted from vndmnt01.cbl).
008700 DO-THE-PICK. 008800 IF MENU-PICK = 1 008900 PERFORM ADD-MODE 009000 ELSE 009100 IF MENU-PICK = 2 009200 PERFORM CHANGE-MODE 009300 ELSE 009400 IF MENU-PICK = 3 009500 PERFORM INQUIRE-MODE 009600 ELSE 009700 IF MENU-PICK = 4 009800 PERFORM DELETE-MODE.
This is a series of IF ELSE tests nested inside one another and would be more properly represented with something similar to the code shown in Listing 14.15.
008700 DO-THE-PICK. 008800 IF MENU-PICK = 1 008900 PERFORM ADD-RECORDS 009000 ELSE 009100 IF MENU-PICK = 2 009200 PERFORM CHANGE-RECORDS 009300 ELSE 009400 IF MENU-PICK = 3 009500 PERFORM LOOK-UP-RECORDS 009600 ELSE 009700 IF MENU-PICK = 4 009800 PERFORM DELETE-RECORDS.
ANALYSIS: The first IF tests for a MENU-PICK of 1. If the user picks 1, line 008900 is executed. If 1 is not picked, the code below the ELSE at line 009000 is executed. This section of code starts immediately with another IF test at line 009100. If the MENU-PICK is 2, line 009200 is executed; otherwise, everything below the ELSE at line 009300 is executed. Again, this section of code starts with an IF at line 009400.
This particular method of testing for one of several possible values is very common in programs--especially in menu programs. It usually is written as shown in Listing 14.14, because it is slightly clearer that the paragraph is testing for one possible condition and then performing something based on that one condition. The full analysis of this program is left to you at the end of this chapter as an exercise.
Further information on IF ELSE is in order here. When an IF appears within an IF, it might not be obvious how this works. The inner IF is tested only if the outer IF is true. IF and IF ELSE commands can be nested inside one another. Use this construction to create nested IF statements:
IF condition do something IF condition do something
In the construction above, the first IF condition is tested. If it is false, none of the remaining statements is performed. If it is true, all statements are performed, including the test at the second IF. Use the following construction for a nested IF-ELSE.
IF condition do something IF condition do something ELSE do something ELSE do something
The first IF is tested. If it is false, the logic under the final ELSE is performed. If the first IF condition tests true, then everything between the IF and the final ELSE is performed, including an inner IF ELSE test.
The following are examples of nested IF statements:
IF VENDOR-NUMBER NOT = ZEROES PERFORM READ-VENDOR-RECORD IF RECORD-FOUND = "N" DISPLAY "RECORD NOT FOUND". IF VENDOR-NUMBER NOT = ZEROES PERFORM READ-VENDOR-RECORD IF RECORD-FOUND = "N" DISPLAY "RECORD NOT FOUND" ELSE DISPLAY "RECORD WAS FOUND" ELSE DISPLAY "YOU ENTERED ZEROES"
The indentation is a matter of style and is used only to indicate which IF matches which ELSE and to make it easier to read.
Figures 14.2 and 14.3 show the relationships caused by nesting IF and IF ELSE commands.
Figure 14.2.
Nested IF commands.
Figure 14.3.
Nested IF ELSE commands.
DO/DON'T:
DO break up complex IF ELSE logic into smaller paragraphs, or rewrite that area of the program to simplify the problem.DON'T nest IF commands more than two or three levels. Nesting an IF within another IF can lead to some confusion in the program, and if you find that you need to nest three levels of IF, you might want to rethink the way you are writing the paragraph. You can nest IF ELSE logic in such a way that it is difficult to understand what a program is doing. For an exception to this general rule, see the Q&A section in the Workshop at the end of this chapter.
Code, compile, and run this program; then add, change, delete, and look up records in the vendor file using this one program.
Today, you reviewed how to define an indexed file in a COBOL program, and the syntax of each type of file operation: OPEN, CLOSE, READ, READ NEXT, WRITE, REWRITE, and DELETE. You also learned the following basics:
a. Two of the paragraphs are placed incorrectly. They appear in groups
of routines that have comments indicating in which modes the routines are used, but
the routines actually are not used in the modes indicated. Which routines are they?
b. Where should these routines be placed correctly?
c. Which modes use the READ-VENDOR-RECORD routine?
d. Which modes use the WRITE-VENDOR-RECORD routine?
e. Which modes use the REWRITE-VENDOR-RECORD routine?
f. Which modes use the DELETE-VENDOR-RECORD routine?
© Copyright, Macmillan Computer Publishing. All rights reserved.