In COBOL, the flow of a program is controlled almost entirely by IF-ELSE statements, the PERFORM verb, and GO TO, which is a new verb you will look at today. There are some additional versions of the PERFORM verb and the IF-ELSE statement, allowing even more control, and these are covered as well. Today, you learn about the following topics:
You can force the program to jump to the beginning of any paragraph with a GO TO. Here is an example:
GO TO paragraph-name.
A GO TO is like a PERFORM in that the program jumps to a new paragraph. However, when that paragraph is completed, the PERFORM returns to the line at which the PERFORM was requested, but the GO TO does not. When a GO TO reaches the end of the paragraph to which it has jumped, it moves into the next paragraph.
GO TO is written as two words, but it is used as one. The words always appear together. Listing 5.1 uses GO TO to bail out of a program.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. QUIT01. 000300 ENVIRONMENT DIVISION. 000400 DATA DIVISION. 000500 WORKING-STORAGE SECTION. 000600 000700 01 YES-OR-NO PIC X. 000800 000900 PROCEDURE DIVISION. 001000 PROGRAM-BEGIN. 001100 001200 PERFORM SHALL-WE-CONTINUE. 001300 IF YES-OR-NO = "N" 001400 GO TO PROGRAM-DONE. 001500 001600 PERFORM MAIN-LOGIC. 001700 001800 PROGRAM-DONE. 001900 STOP RUN. 002000 002100 SHALL-WE-CONTINUE. 002200 DISPLAY "Continue (Y/N)?". 002300 ACCEPT YES-OR-NO. 002400 IF YES-OR-NO = "n" 002500 MOVE "N" TO YES-OR-NO. 002600 002700 MAIN-LOGIC. 002800 DISPLAY "This is the main logic.". 002900
ANALYSIS: At line 001200, a PERFORM is requested of SHALL-WE-CONTINUE. In this paragraph, at lines 002100 and 002200, the user is asked whether he wants to continue. When the user enters a response, a possible "n" is converted to "N" and the logic at line 001300 checks whether the user entered N, and, if so, the program flow at line 001400 jumps straight to PROGRAM-DONE. PROGRAM-DONE contains the now familiar STOP RUN, and execution of the program is terminated.
The alternative is that the user enters something other than N (or n), and line 001300 is skipped. The next executed line is 001600, where the program requests a PERFORM of MAIN-LOGIC. (In this example, the content of MAIN-LOGIC isn't important.)
GO TO is the only four-letter verb in COBOL. (That's a joke.) The use of GO TO in programs is a hotly debated issue, and academics will tell you, "You never use a GO TO," or "One more GO TO out of you, and I'm going to wash your mouth out with soap!" One professor of computer science was so incensed by GO TO that he designed a whole new programming language with no GO TO in it.
If you plan to work with COBOL in the real world, rather than behind closed university doors, you must know what a GO TO does and how to work with and around it. Any working program that you have to modify will be littered with GO TO verbs, and you ignore them at your own peril. Just remember that mentioning a GO TO around some people will make their faces red and cause steam to come out of their ears.
You shouldn't use GO TO in programs that you write, but you will have to deal with GO TO in programs that you modify. Listing 5.2 is an example of a GO TO that would be considered a minor sin by some people. The program, mult01.cbl, displays multiplication tables (such as the ones you had to memorize in school) based on which table the user selects to display.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. MULT01. 000300*-------------------------------------------------- 000400* This program asks the user for a number for a 000500* multiplication table, 000600* and then displays a table for that number times 000700* the values 1 through 12. 000800*-------------------------------------------------- 000900 ENVIRONMENT DIVISION. 001000 DATA DIVISION. 001100 WORKING-STORAGE SECTION. 001200 001300 01 THE-NUMBER PIC 99. 001400 01 THE-MULTIPLIER PIC 999. 001500 01 THE-PRODUCT PIC 9999. 001600 001700 PROCEDURE DIVISION. 001800* LEVEL 1 ROUTINES 001900 PROGRAM-BEGIN. 002000 PERFORM PROGRAM-INITIALIZATION. 002100 PERFORM GET-TABLE-NUMBER. 002200 PERFORM DISPLAY-THE-TABLE. 002300 002400 PROGRAM-DONE. 002500 STOP RUN. 002600 002700* LEVEL 2 ROUTINES 002800 PROGRAM-INITIALIZATION. 002900 MOVE 0 TO THE-MULTIPLIER. 003000 003100 GET-TABLE-NUMBER. 003200 DISPLAY 003300 "Which multiplication table (01-99)?". 003400 ACCEPT THE-NUMBER. 003500 003600 DISPLAY-THE-TABLE. 003700 DISPLAY "The " THE-NUMBER `s table is:". 003800 PERFORM CALCULATE-AND-DISPLAY. 003900 004000* LEVEL 3 ROUTINES. 004100 CALCULATE-AND-DISPLAY. 004200 ADD 1 TO THE-MULTIPLIER. 004300 COMPUTE THE-PRODUCT = THE-NUMBER * THE-MULTIPLIER. 004400 DISPLAY 004500 THE-NUMBER " * " THE-MULTIPLIER " = " THE-PRODUCT. 004600 IF THE-MULTIPLIER < 12 004700 GO TO CALCULATE-AND-DISPLAY. 004800
This is the output of mult01.cbl for the 7's table (which I had a great deal of trouble memorizing in school):
OUTPUT:
Which multiplication table (01-99)? 07 The 07's table is: 07 * 001 = 0007 07 * 002 = 0014 07 * 003 = 0021 07 * 004 = 0028 07 * 005 = 0035 07 * 006 = 0042 07 * 007 = 0049 07 * 008 = 0056 07 * 009 = 0063 07 * 010 = 0070 07 * 011 = 0077 07 * 012 = 0084 C> C>
ANALYSIS: In PROGRAM-INITIALIZATION, the variable THE-MULTIPLIER is set to 0. In GET-TABLE-NUMBER, the user is asked to select the multiplication table and is prompted for a number between 01 and 99. Remember that some versions of COBOL require that you enter a number with a leading zero, here--03, for example, if you want 3.
These two paragraphs, when performed, set things up for the main activity of the program, which is to display a table of the entered number times 1, times 2, times 3, and so on to 12.
Now look at the paragraph CALCULATE-AND-DISPLAY. THE-MULTIPLIER is initialized to 0 by PROGRAM-INITIALIZATION, so the action of this paragraph is to add 1 to THE-MULTIPLIER, calculate THE-PRODUCT by multiplying THE-MULTIPLIER by THE-NUMBER, and then display this information.
In the COBOL COMPUTE statement, the asterisk (*) is the multiplication symbol.
The DISPLAY statement is organized to display the results as follows:
03 * 01 = 0003 03 * 02 = 0006
The basic repetitive task of the program to is add 1 to THE-MULTIPLIER, calculate the new product, and display the result. It is necessary to do this 12 times. At line 004600, an IF tests whether THE-MULTIPLIER is less than 12. As long as it is, the program will jump back to the beginning of CALCULATE-AND-DISPLAY. Each time, the program adds 1 to THE-MULTIPLIER and calculates and displays the new product. When THE-MULTIPLIER reaches 12, the IF condition is no longer true. The GO TO CALCULATE-AND-DISPLAY at line 004700 is not executed and the CALCULATE-AND-DISPLAY paragraph ends. The program returns to the end of line 003800 looking for more commands. There are none. No further commands are in DISPLAY-THE-TABLE, so that paragraph ends and the program returns to line 002200, where there also are no further commands. The program proceeds to lines 002400 and 002500 and ends.
It is certainly legitimate to use a GO TO at the bottom of a paragraph to jump back to the top of the paragraph in order to execute the paragraph again under some condition, although some would dispute even that use.
After you've worked with modifying real code, you will find out why GO TO should be discouraged. It is very confusing to be following a paragraph of logic, and find a GO TO to another paragraph somewhere else in the program. Because a GO TO does not bounce back, you have no way of knowing whether the rest of the current paragraph is ever executed or the programmer just skipped everything else for some reason.
One danger of GO TO verbs is the likelihood that the programmer skipped some code for no reason at all (other than carelessness), instead of having some reason to skip the code.
Understand GO TO, because you will find it in various programs. You can avoid GO TO completely, as you will see a little later in today's lesson. So, if you ever work in a shop that has banned the use of GO TO, you can work your way around the stricture.
Now that you have been warned about the evils of GO TO, how could you write the previous program without one? The PERFORM verb is available for that purpose--in a variety of flavors. One of them allows you to perform a paragraph several times:
PERFORM A-PARAGRAPH 10 TIMES.
Listing 5.3, mult02.cbl, uses this version of the PERFORM verb to present the same multiplication tables based on the user's selection. Edit, compile, and run this program. It will accept factors up to 99.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. MULT02. 000300*-------------------------------------------------- 000400* This program asks the user for a number for a 000500* multiplication table, 000600* and then displays a table for that number times 000700* the values 1 through 12. 000800*-------------------------------------------------- 000900 ENVIRONMENT DIVISION. 001000 DATA DIVISION. 001100 WORKING-STORAGE SECTION. 001200 001300 01 THE-NUMBER PIC 99. 001400 01 THE-MULTIPLIER PIC 999. 001500 01 THE-PRODUCT PIC 9999. 001600 001700 PROCEDURE DIVISION. 001800* LEVEL 1 ROUTINES 001900 PROGRAM-BEGIN. 002000 PERFORM PROGRAM-INITIALIZATION. 002100 PERFORM GET-TABLE-NUMBER. 002200 PERFORM DISPLAY-THE-TABLE. 002300 002400 PROGRAM-DONE. 002500 STOP RUN. 002600 002700* LEVEL 2 ROUTINES 002800 PROGRAM-INITIALIZATION. 002900 MOVE 0 TO THE-MULTIPLIER. 003000 003100 GET-TABLE-NUMBER. 003200 DISPLAY 003300 "Which multiplication table (01-99)?". 003400 ACCEPT THE-NUMBER. 003500 003600 DISPLAY-THE-TABLE. 003700 DISPLAY "The " THE-NUMBER "`s table is:". 003800 PERFORM CALCULATE-AND-DISPLAY 12 TIMES. 003900 004000* LEVEL 3 ROUTINES. 004100 CALCULATE-AND-DISPLAY. 004200 ADD 1 TO THE-MULTIPLIER. 004300 COMPUTE THE-PRODUCT = THE-NUMBER * THE-MULTIPLIER. 004400 DISPLAY 004500 THE-NUMBER " * " THE-MULTIPLIER " = " THE-PRODUCT.
ANALYSIS: The program is identical to mult01.cbl except that the IF and GO TO at lines 004600 and 004700 are removed, and the PERFORM at line 003800 has been replaced with PERFORM CALCULATE-AND-DISPLAY 12 TIMES.
Again, the basic repetitive task of the program is to add 1, calculate, and display the result. It is necessary to do this 12 times, and this job is taken care of at line 003800.
When the PERFORM verb is used to perform something a number of times, the COBOL compiler takes care of setting things so that a PERFORM is requested over and over until the number of times is exhausted. When the program is running, it actually jumps down to line 004100 and then back to line 003800 12 times.
The PERFORM...TIMES verb is flexible, and the number of times to perform something can be a variable itself. Here is an example:
PERFORM A-PARAGRAPH HOW-MANY TIMES.
Listing 5.4 takes the multiplication table program one step further by allowing the user to specify the number of entries to be displayed.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. MULT03. 000300*-------------------------------------------------- 000400* This program asks the user for a number for a 000500* multiplication table, and a table size 000600* and then displays a table for that number times 000700* the values 1 through HOW-MANY. 000800* 000900* 001000*-------------------------------------------------- 001100 ENVIRONMENT DIVISION. 001200 DATA DIVISION. 001300 WORKING-STORAGE SECTION. 001400 001500 01 THE-NUMBER PIC 99. 001600 01 THE-MULTIPLIER PIC 999. 001700 01 THE-PRODUCT PIC 9999. 001800 01 HOW-MANY PIC 99. 001900 002000 002100 002200 002300 PROCEDURE DIVISION. 002400* LEVEL 1 ROUTINES 002500 PROGRAM-BEGIN. 002600 PERFORM PROGRAM-INITIALIZATION. 002700 PERFORM GET-TABLE-DATA. 002800 PERFORM DISPLAY-THE-TABLE. 002900 003000 PROGRAM-DONE. 003100 STOP RUN. 003200 003300* LEVEL 2 ROUTINES 003400 PROGRAM-INITIALIZATION. 003500 MOVE 0 TO THE-MULTIPLIER. 003600 003700 003800 GET-TABLE-DATA. 003900 DISPLAY 004000 "Which multiplication table(01-99)?". 004100 ACCEPT THE-NUMBER. 004200 004300 DISPLAY "How many entries would you like (01-99)?". 004400 ACCEPT HOW-MANY. 004500 004600 DISPLAY-THE-TABLE. 004700 DISPLAY "The " THE-NUMBER "`s table is:". 004800 PERFORM CALCULATE-AND-DISPLAY HOW-MANY TIMES. 004900 005000* LEVEL 3 ROUTINES. 005100 CALCULATE-AND-DISPLAY. 005200 ADD 1 TO THE-MULTIPLIER. 005300 COMPUTE THE-PRODUCT = THE-NUMBER * THE-MULTIPLIER. 005400 DISPLAY 005500 THE-NUMBER " * " THE-MULTIPLIER " = " THE-PRODUCT. 005600
The following is the output from mult03.cbl for 15 entries of the 15's table:
OUTPUT:
Which multiplication table(01-99)? 15 How many entries would you like (01-99)? 15 The 15's table is: 15 * 001 = 0015 15 * 002 = 0030 15 * 003 = 0045 15 * 004 = 0060 15 * 005 = 0075 15 * 006 = 0090 15 * 007 = 0105 15 * 008 = 0120 15 * 009 = 0135 15 * 010 = 0150 15 * 011 = 0165 15 * 012 = 0180 15 * 013 = 0195 15 * 014 = 0210 15 * 015 = 0225 C> C>
ANALYSIS: In Listing 5.4, mult03.cbl, the GET-TABLE-NUMBER paragraph has been changed to GET-TABLE-DATA and additionally asks the user for the number of entries to be displayed. This value is stored in the variable HOW-MANY. Instead of performing CALCULATE-AND-DISPLAY 12 TIMES, the program performs it HOW-MANY TIMES.
If you edit, compile, and run this program, you can display the 15's table with 24 or 25 entries. If you enter more than 25 for the number of entries, the first entries in the table will scroll off the top of the screen.
Certain terminals known as block mode terminals do not display all lines. Instead they display one line, wait for you to press Enter, then display the next line, and so on. If this happens to you, consult with your system administrator for verification that you are using block mode terminals. If this is the case, you should consider acquiring the Micro Focus Personal COBOL Compiler to continue these lessons.
The program mult03.cbl contains a few extra blank lines because you will be modifying it shortly. Spend some time going over Listing 5.4 to make sure that you really understand what is happening in the program. Run it several times with different values (with the program in front of you) and work out where you are in the code at each point in the running program.
In mult03.cbl, the flaw, as mentioned before, is that early entries in the table scroll off the screen if more than 20 entries are requested.
You have all the tools you need to correct this problem; it is just a matter of using them. To tidy up the display in the next example, the program halts the display after every 15 lines.
The traditional way of doing this would be to display 15 lines, display Press ENTER to continue . . ., and wait for the user to press the Enter key.
Remember that using the ACCEPT verb causes the computer to wait for input from the keyboard until the user presses Enter. In this case, you want the user to press Enter, but you don't care about any values entered. The simple solution is to ACCEPT a dummy variable.
Edit, compile, and run Listing 5.5, trying numbers of entries greater than 15. The display will pause after 15 lines and wait for you to press Enter; then it will continue the display.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. MULT04. 000300*-------------------------------------------------- 000400* This program asks the user for a number for a 000500* multiplication table, and a table size 000600* and then displays a table for that number 000700* times the values 1 through HOW-MANY. 000800* 000900* The display is paused after each 15 lines. 001000*-------------------------------------------------- 001100 ENVIRONMENT DIVISION. 001200 DATA DIVISION. 001300 WORKING-STORAGE SECTION. 001400 001500 01 THE-NUMBER PIC 99. 001600 01 THE-MULTIPLIER PIC 999. 001700 01 THE-PRODUCT PIC 9999. 001800 01 HOW-MANY PIC 99. 001900 01 SCREEN-LINES PIC 99. 002000 002100 01 A-DUMMY PIC X. 002200 002300 PROCEDURE DIVISION. 002400* LEVEL 1 ROUTINES 002500 PROGRAM-BEGIN. 002600 PERFORM PROGRAM-INITIALIZATION. 002700 PERFORM GET-TABLE-DATA. 002800 PERFORM DISPLAY-THE-TABLE. 002900 003000 PROGRAM-DONE. 003100 STOP RUN. 003200 003300* LEVEL 2 ROUTINES 003400 PROGRAM-INITIALIZATION. 003500 MOVE 0 TO THE-MULTIPLIER. 003600 MOVE 0 TO SCREEN-LINES. 003700 003800 GET-TABLE-DATA. 003900 DISPLAY 004000 "Which multiplication table (01-99)?". 004100 ACCEPT THE-NUMBER. 004200 004300 DISPLAY "How many entries would you like (01-99)?". 004400 ACCEPT HOW-MANY. 004500 004600 DISPLAY-THE-TABLE. 004700 DISPLAY "The " THE-NUMBER "`s table is:". 004800 PERFORM CALCULATE-AND-DISPLAY HOW-MANY TIMES. 004900 005000* LEVEL 3 ROUTINES. 005100 CALCULATE-AND-DISPLAY. 005200 ADD 1 TO THE-MULTIPLIER. 005300 COMPUTE THE-PRODUCT = THE-NUMBER * THE-MULTIPLIER. 005400 DISPLAY 005500 THE-NUMBER " * " THE-MULTIPLIER " = " THE-PRODUCT. 005600 005700 ADD 1 TO SCREEN-LINES. 005800 IF SCREEN-LINES = 15 005900 DISPLAY "Press ENTER to continue . . ." 006000 ACCEPT A-DUMMY 006100 MOVE 0 TO SCREEN-LINES. 006200
Three screens of output occur when mult04.cbl is used to display 31 entries of the 14's table. Here is the first screen:
OUTPUT:
Which multiplication table (01-99)? 14 How many entries would you like (01-99)? 31 The 14's table is: 14 * 001 = 0014 14 * 002 = 0028 14 * 003 = 0042 14 * 004 = 0056 14 * 005 = 0070 14 * 006 = 0084 14 * 007 = 0098 14 * 008 = 0112 14 * 009 = 0126 14 * 010 = 0140 14 * 011 = 0154 14 * 012 = 0168 14 * 013 = 0182 14 * 014 = 0196 14 * 015 = 0210 Press ENTER to continue . . .
After you press Enter, the current display scrolls upward, making room for 15 more lines of tables and another Press ENTER message. The tail end of the first 15 lines still appears at the top of the screen. Here is the output after you press Enter:
OUTPUT:
14 * 010 = 0140 14 * 011 = 0154 14 * 012 = 0168 14 * 013 = 0182 14 * 014 = 0196 14 * 015 = 0210 Press ENTER to continue . . . 14 * 016 = 0224 14 * 017 = 0238 14 * 018 = 0252 14 * 019 = 0266 14 * 020 = 0280 14 * 021 = 0294 14 * 022 = 0308 14 * 023 = 0322 14 * 024 = 0336 14 * 025 = 0350 14 * 026 = 0364 14 * 027 = 0378 14 * 028 = 0392 14 * 029 = 0406 14 * 030 = 0420 Press ENTER to continue . . .
After you press Enter a second time, one more line of information is displayed at the bottom of the screen, leaving the remains of the first two displays of 15 lines at the top:
OUTPUT:
14 * 015 = 0210 Press ENTER to continue . . . 14 * 016 = 0224 14 * 017 = 0238 14 * 018 = 0252 14 * 019 = 0266 14 * 020 = 0280 14 * 021 = 0294 14 * 022 = 0308 14 * 023 = 0322 14 * 024 = 0336 14 * 025 = 0350 14 * 026 = 0364 14 * 027 = 0378 14 * 028 = 0392 14 * 029 = 0406 14 * 030 = 0420 Press ENTER to continue . . . 14 * 031 = 0434 C> C>
ANALYSIS: Listing 5.5 adds two additional variables: SCREEN-LINES to count the number of lines that have been displayed on the screen, and A-DUMMY, which is a dummy variable to be used with ACCEPT. The SCREEN-LINES variable is set to an initial value of 0 in PROGRAM-INITIALIZATION.
All the other changes are in the CALCULATE-AND-DISPLAY paragraph at line 005100. The first part of the paragraph is identical to Listing 5.4, mult03.cbl, up to line 005600. Note that the line numbers have stayed the same for Listing 5.4 and 5.5 because of the extra blank lines in Listing 5.4. The blanks are there to keep the line numbers the same, but this is not a standard programming practice.
At line 005700, 1 is added to the variable. At line 005800, a test is made to determine whether SCREEN-LINES has reached 15 (that is, 15 lines have been displayed). When 15 lines have been displayed, the logic at lines 005900 through 006100 is executed. At line 005900, a message is displayed. At line 006000, A-DUMMY is accepted. Remember that you don't care what value is placed in A-DUMMY; you just want some method of waiting for the user to press Enter. At line 006100, the SCREEN-LINES variable is reset to 0.
If SCREEN-LINES were not reset to 0, it would continue counting up from 15 to 16, 17, and so on. It never again would equal 15, and the IF at line 005800 would never test true. The result would be that the screen would stop after the first 15 entries were displayed, but it wouldn't stop after the next 15.
Listing 5.5 has a minor bug (a logic error) in it. To see the result of the bug, do the following: Run mult04.cbl and enter any multiplication table that you want. For the number of entries, enter an even multiple of 15, such as 15, 30, or 45. After the program has displayed the number of entries, it asks you to press Enter to continue. When you press Enter, nothing else is displayed and the program ends. The Press ENTER message implies to the user that there is more to see when, in fact, there is not. Try following the logic and work out why this happens. You will deal with this bug later in today's lesson, but first you have a few more things to learn about the PERFORM verb.
A computer is designed to do things over and over, but if it does the same thing endlessly, the computer is limited to a single job. In practice, a processing loop is brought to an end by some condition. The condition is set up to be tested at the beginning of each pass through the processing loop or at the last step in the loop. The condition is used to determine whether the processing loop should end or continue. The processing loop is the logic that is performed over and over.
New Term: You have just written a couple programs containing examples of a processing loop. A processing loop is one or more paragraphs that are executed over and over. Processing loops (which are almost always controlled by some condition and should be called controlled processing loops) are sometimes simply called loops.
New Term: The condition that controls the processing loop usually is called the processing loop control, or simply the loop control.
Sometimes it is difficult to separate completely the processing loop from the control of the loop, and the two areas are referred to jointly as a loop or a processing loop. You should train yourself to spot the processing loop and the control of the processing loop.
Listing 5.6 is a portion of mult02.cbl from Listing 5.3.
003800 PERFORM CALCULATE-AND-DISPLAY 12 TIMES. 003900 004000 004100 CALCULATE-AND-DISPLAY. 004200 ADD 1 TO THE-MULTIPLIER. 004300 COMPUTE THE-PRODUCT = THE-NUMBER * THE-MULTIPLIER. 004400 DISPLAY 004500 THE-NUMBER " * " THE-MULTIPLIER " = " THE-PRODUCT.
ANALYSIS: The processing loop portion is the CALCULATE-AND-DISPLAY paragraph at lines 004100 through 004500. This paragraph is performed over and over.
The control for the processing loop is the PERFORM 12 TIMES statement at line 003800. The condition that controls or ends the loop occurs when the paragraph has been performed 12 times.
Listing 5.7 shows a portion of Listing 5.2, mult01.cbl.
003800 PERFORM CALCULATE-AND-DISPLAY. 003900 004000 004100 CALCULATE-AND-DISPLAY. 004200 ADD 1 TO THE-MULTIPLIER. 004300 COMPUTE THE-PRODUCT = THE-NUMBER * THE-MULTIPLIER. 004400 DISPLAY 004500 THE-NUMBER " * " THE-MULTIPLIER " = " THE-PRODUCT. 004600 IF THE-MULTIPLIER < 12 004700 GO TO CALCULATE-AND-DISPLAY.
ANALYSIS: In this example, the processing loop is also the CALCULATE-AND-DISPLAY paragraph. The control for the loop is at lines 004600 and 004700. The loop ends when THE-MULTIPLIER is no longer less than 12.
A controlled processing loop is one of the key elements of every working program. Remember that one of the main functions of a computer is to perform repetitive tasks. Unless you want the computer to perform the same task forever, you must use some condition to stop the repetition. This is where the control loop comes in.
The control loop is such a key part of any computer program that every programming language includes some specialized verb or statement that can be used to create a controlled processing loop. COBOL is no exception.
The PERFORM verb has some other formats that allow control over a loop. The first of these formats, as you have seen, is using the PERFORM verb with a number of TIMES. The next is PERFORM UNTIL. Use this syntax:
PERFORM a paragraph UNTIL a condition.
The following is an example:
PERFORM CALCULATE-AND-DISPLAY UNTIL THE-MULTIPLIER > 12.
The PERFORM UNTIL sentence is a repetitive request to perform a paragraph, with a built-in IF test in the UNTIL. The PERFORM verb is requested over and over until the condition tests true.
Listing 5.8 illustrates a PERFORM UNTIL.
003800 PERFORM CALCULATE-AND-DISPLAY 003900 UNTIL THE-MULTIPLIER > 12. 004000 004100 CALCULATE-AND-DISPLAY. 004200 ADD 1 TO THE-MULTIPLIER. 004300 COMPUTE THE-PRODUCT = THE-NUMBER * THE-MULTIPLIER. 004400 DISPLAY 004500 THE-NUMBER " * " THE-MULTIPLIER " = " THE-PRODUCT.
ANALYSIS: At lines 003800 and 003900, the paragraph CALCULATE-AND-DISPLAY is performed repetitively. This repetition stops when THE-MULTIPLIER is greater than 12 (as specified in line 003900). PERFORM UNTIL is one long sentence with the period at the end of line 003900. There is a bug in this example that we will be fixing before the end of the chapter.
A PERFORM UNTIL sentence tests the condition before the perform is executed. COBOL does not allow you to go to a line number, but if it did, a PERFORM UNTIL sentence could be thought of as executing the following logic, which is not proper COBOL code:
003800 IF THE-MULTIPLIER > 12 GO TO line 004100. 003900 PERFORM CALCULATE-AND-DISPLAY 004000 GO TO line 003800. 004100* PROGRAM continues here
Previous examples started by setting THE-MULTIPLIER to 0. The CALCULATE-AND-DISPLAY paragraph always began by adding 1 to the multiplier, as in Listing 5.8.
If you follow the path of the logic in Listing 5.8, starting at the top of CALCULATE-AND-DISPLAY when THE-MULTIPLIER equals 11, you'll notice an error in the logic (a bug). The paragraph adds 1 to THE-MULTIPLIER, making it 12, and displays the results for 12. The program then returns to line 003900, falls through to line 004000, where it jumps back up to line 003800, and checks the condition again. THE-MULTIPLIER equals 12 (so it is not greater than 12), however, and the paragraph CALCULATE-AND-DISPLAY is performed one more time. The first action in CALCULATE-AND-DISPLAY is to add 1 to THE-MULTIPLIER, so the results will be displayed when THE-MULTIPLIER equals 13.
The quickest fix for this is to change the test at line 003900 to test for greater than 11, but it looks a little confusing when you are reading the code. It takes a moment to realize that the loop executes 12 times, because you have to look back through the code to establish that THE-MULTIPLIER originally was set to 0:
003800 PERFORM CALCULATE-AND-DISPLAY 003900 UNTIL THE-MULTIPLIER > 11.
A solution that works just as well is illustrated in Listing 5.9. This has the advantage of keeping all the key pieces of the loop together in one section of the code.
003700 MOVE 1 TO THE-MULTIPLIER. 003800 PERFORM CALCULATE-AND-DISPLAY 003900 UNTIL THE-MULTIPLIER > 12. 004000 004100 CALCULATE-AND-DISPLAY. 004200 COMPUTE THE-PRODUCT = THE-NUMBER * THE-MULTIPLIER. 004300 DISPLAY 004400 THE-NUMBER " * " THE-MULTIPLIER " = " THE-PRODUCT. 004500 ADD 1 TO THE-MULTIPLIER.
ANALYSIS: The variable THE-MULTIPLIER first is set to a value of 1. The paragraph CALCULATE-AND-DISPLAY is performed until THE-MULTIPLIER is greater than 12. Because THE-MULTIPLIER starts with an initially correct value of 1, the ADD 1 TO THE-MULTIPLIER logic is moved to the end of CALCULATE-AND-DISPLAY.
It is much quicker to figure out that the loop is performed with THE-MULTIPLIER ranging in value from 1 through 12.
Listing 5.9 also illustrates a very common method of constructing and controlling a processing loop. These are the three steps of this construction:
Look again at Listing 5.9 for these three steps. Based on the first step, the value in THE-MULTIPLIER must be set to 1. This is the first value that THE-MULTIPLIER must have on entry to the loop (CALCULATE-AND-DISPLAY). This is taken care of at line 003700.
In the second step, CALCULATE-AND-DISPLAY is performed until the MULTIPLIER is greater than 12, at lines 003800 and 003900.
In the final step, the variable that controls the loop, THE-MULTIPLIER, is modified as the last step in the loop. The ADD 1 logic is moved and now occurs at the end of CALCULATE-AND-DISPLAY at line 004500. The requested paragraph is performed over and over until the condition tests true.
The three steps of process loop control are so common in programs that the PERFORM verb has been extended even further, to allow the first and last steps to be incorporated directly into the PERFORM verb:
PERFORM a paragraph VARYING a variable FROM a value BY a value UNTIL a condition.
The following is an example:
PERFORM CALCULATE-AND-DISPLAY VARYING THE-MULTIPLIER FROM 1 BY 1 UNTIL THE-MULTIPLIER > 12.
This is an extension of PERFORM UNTIL.
Compare the partial programs in Listings 5.10 and 5.11. They produce the same results using different versions of the PERFORM verb. (I've inserted the blank line in Listing 5.10 in the middle of the PERFORM UNTIL logic to keep the line numbers the same in the two listings. Remember that the blank line means nothing; even if it appears in the middle of a sentence, it is ignored.)
003700 MOVE 1 TO THE-MULTIPLIER. 003800 PERFORM CALCULATE-AND-DISPLAY 003900 004000 UNTIL THE-MULTIPLIER > 12. 004100 004200 CALCULATE-AND-DISPLAY. 004300 COMPUTE THE-PRODUCT = THE-NUMBER * THE-MULTIPLIER. 004400 DISPLAY 004500 THE-NUMBER " * " THE-MULTIPLIER " = " THE-PRODUCT. 004600 ADD 1 TO THE-MULTIPLIER.
003700 003800 PERFORM CALCULATE-AND-DISPLAY 003900 VARYING THE-MULTIPLIER FROM 1 BY 1 004000 UNTIL THE-MULTIPLIER > 12. 004100 004200 CALCULATE-AND-DISPLAY. 004300 COMPUTE THE-PRODUCT = THE-NUMBER * THE-MULTIPLIER. 004400 DISPLAY 004500 THE-NUMBER " * " THE-MULTIPLIER " = " THE-PRODUCT. 004600
ANALYSIS: In Listing 5.10, initializing THE-MULTIPLIER at line 003700 and adding 1 to THE-MULTIPLIER at line 004600 have been replaced by a single line at 003900 in Listing 5.11.
A PERFORM VARYING UNTIL can be broken down into the following steps (again assuming that COBOL allows you to go to a line number, which it doesn't):
003700 MOVE 1 TO THE-MULTIPLIER. 003800 IF THE-MULTIPLIER > 12 GO TO line 004200. 003900 PERFORM CALCULATE-AND-DISPLAY. 004000 ADD 1 TO THE-MULTIPLIER. 004100 GO TO line 003800. 004200* Program continues here
Listing 5.12 shows the multiplication tables program again, using PERFORM VARYING UNTIL to control the processing loop.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. MULT05. 000300*-------------------------------------------------- 000400* This program asks the user for a number for a 000500* multiplication table, and a table size and then 000600* displays a table for that number times the values 000700* 1 through HOW-MANY using PERFORM VARYING UNTIL. 000800*-------------------------------------------------- 000900 ENVIRONMENT DIVISION. 001000 DATA DIVISION. 001100 WORKING-STORAGE SECTION. 001200 001300 01 THE-NUMBER PIC 99. 001400 01 THE-MULTIPLIER PIC 999. 001500 01 THE-PRODUCT PIC 9999. 001600 01 HOW-MANY PIC 99. 001700 001800 PROCEDURE DIVISION. 001900* LEVEL 1 ROUTINES 002000 PROGRAM-BEGIN. 002100 PERFORM PROGRAM-INITIALIZATION. 002200 PERFORM GET-TABLE-DATA. 002300 PERFORM DISPLAY-THE-TABLE. 002400 002500 PROGRAM-DONE. 002600 STOP RUN. 002700 002800* LEVEL 2 ROUTINES 002900 PROGRAM-INITIALIZATION. 003000* MOVE 0 TO THE-MULTIPLIER. 003100* is no longer needed 003200 003300 GET-TABLE-DATA. 003400 DISPLAY 003500 "Which multiplication table(01-99)?". 003600 ACCEPT THE-NUMBER. 003700 003800 DISPLAY "How many entries would you like (01-99)?". 003900 ACCEPT HOW-MANY. 004000 004100 DISPLAY-THE-TABLE. 004200 DISPLAY "The " THE-NUMBER "`s table is:". 004300 PERFORM CALCULATE-AND-DISPLAY 004400 VARYING THE-MULTIPLIER 004500 FROM 1 BY 1 004600 UNTIL THE-MULTIPLIER > HOW-MANY. 004700 004800* LEVEL 3 ROUTINES. 004900 CALCULATE-AND-DISPLAY. 005000 005100 COMPUTE THE-PRODUCT = THE-NUMBER * THE-MULTIPLIER. 005200 DISPLAY 005300 THE-NUMBER " * " THE-MULTIPLIER " = " THE-PRODUCT. 005400
Remember the bug in Listing 5.5, mult04.cbl? It displays a Press ENTER message, even when there is nothing else to display. Now we're going to solve this problem; you'll find the solution in mult05.cbl. The processing loop from mult05.cbl is shown in Listing 5.13.
004900 CALCULATE-AND-DISPLAY. 005000 005100 COMPUTE THE-PRODUCT = THE-NUMBER * THE-MULTIPLIER. 005200 DISPLAY 005300 THE-NUMBER " * " THE-MULTIPLIER " = " THE-PRODUCT. 005400
The two important points in any processing loop are the top of the loop and the bottom of the loop. These might seem obvious at first glance, but you must understand two things about these points. If the processing loop is constructed correctly, you know at the top of the loop that the rest of the loop is going to be executed. At the bottom of the loop, you know that the loop has been executed. Now you can try to use these two points in the loop to solve the Press ENTER problem.
There really are two problems. One is to count the number of lines that have been displayed, which is fairly simple to do. The other is to display a Press ENTER message (and wait for the user) when only 15 lines have been displayed and there is more data to display.
The obvious place to count the lines is at the end of the loop where it is obvious that one line has been displayed (the loop has been executed). Listing 5.14 adds the instruction to count the lines at line 5400.
004900 CALCULATE-AND-DISPLAY. 005000 005100 COMPUTE THE-PRODUCT = THE-NUMBER * THE-MULTIPLIER. 005200 DISPLAY 005300 THE-NUMBER " * " THE-MULTIPLIER " = " THE-PRODUCT. 005400 ADD 1 TO SCREEN-LINES.
The second problem (displaying a Press ENTER message at the correct point) seems to fit at the top of the loop. There you know that a line is about to be displayed. If you make the program stop the user at this point and the user presses Enter, you can be certain that at least one more line will be displayed. Listing 5.15 is a complete listing, using a test for SCREEN-LINES at the top of the loop and adding to SCREEN-LINES at the bottom of the loop. Code, compile, and run this listing; try any number of entries, including multiples of 15. You will see that the minor bug in mult04.cbl has been eliminated.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. MULT06. 000300*-------------------------------------------------- 000400* This program asks the user for a number for a 000500* multiplication table, and a table size 000600* and then displays a table for that number 000700* times the values 1 through HOW-MANY. 000800* 000900* The display is paused after each 15 lines. 001000*-------------------------------------------------- 001100 ENVIRONMENT DIVISION. 001200 DATA DIVISION. 001300 WORKING-STORAGE SECTION. 001400 001500 01 THE-NUMBER PIC 99. 001600 01 THE-MULTIPLIER PIC 999. 001700 01 THE-PRODUCT PIC 9999. 001800 01 HOW-MANY PIC 99. 001900 01 SCREEN-LINES PIC 99. 002000 002100 01 A-DUMMY PIC X. 002200 002300 PROCEDURE DIVISION. 002400* LEVEL 1 ROUTINES 002500 PROGRAM-BEGIN. 002600 PERFORM PROGRAM-INITIALIZATION. 002700 PERFORM GET-TABLE-DATA. 002800 PERFORM DISPLAY-THE-TABLE. 002900 003000 PROGRAM-DONE. 003100 STOP RUN. 003200 003300* LEVEL 2 ROUTINES 003400 PROGRAM-INITIALIZATION. 003500 003600 MOVE 0 TO SCREEN-LINES. 003700 003800 GET-TABLE-DATA. 003900 DISPLAY 004000 "Which multiplication table(01-99)?". 004100 ACCEPT THE-NUMBER. 004200 004300 DISPLAY "How many entries would you like (01-99)?". 004400 ACCEPT HOW-MANY. 004500 004600 DISPLAY-THE-TABLE. 004700 DISPLAY "The " THE-NUMBER "`s table is:". 004800 PERFORM CALCULATE-AND-DISPLAY 004900 VARYING THE-MULTIPLIER 005000 FROM 1 BY 1 005100 UNTIL THE-MULTIPLIER > HOW-MANY. 005200 005300* LEVEL 3 ROUTINES. 005400 CALCULATE-AND-DISPLAY. 005500 005600 IF SCREEN-LINES = 15 005700 DISPLAY "Press ENTER to continue . . ." 005800 ACCEPT A-DUMMY 005900 MOVE 0 TO SCREEN-LINES. 006000 006100 COMPUTE THE-PRODUCT = THE-NUMBER * THE-MULTIPLIER. 006200 DISPLAY 006300 THE-NUMBER " * " THE-MULTIPLIER " = " THE-PRODUCT. 006400 006500 ADD 1 TO SCREEN-LINES. 006600
You now have seen several ways of avoiding a GO TO. You can use PERFORM to control a processing loop in different ways, and it should be possible to set up the control in such a way that GO TO can be avoided.
DO/DON'T:
DO understand GO TO so that you know what it is doing when you see it in a program.
DON'T use a GO TO in a program that you write.
DO use PERFORM, PERFORM UNTIL, PERFORM VARYING, and PERFORM nn TIMES to control loops. If a problem seems to require GO TO to solve it, it can be solved better using one of the versions of PERFORM.
Today, you learned how to use PERFORM, GO TO, and IF to control programs. The following are the basic truths about those three statements:
PERFORM DO-SOMETHING 10 TIMES
PERFORM DO-SOMETHING THE-NUMBER TIMES
PERFORM a paragraph number TIMES. PERFORM a paragraph UNTIL condition. PERFORM a paragraph VARYING a variable FROM starting value BY increment value UNTIL condition.
Which multiplication table(01-99)? 15 How many entries would you like (01-99)? 00 The 15's table is: C> C>
1. How many times will DISPLAY-HELLO be performed in the following example?
003600 PERFORM DISPLAY-HELLO 10 TIMES. 003700 003800 DISPLAY-HELLO. 003900 DISPLAY "hello". 004000
003600 PERFORM DISPLAY-HELLO 003700 VARYING THE-COUNT FROM 1 BY 1 003800 UNTIL THE-COUNT > 5. 003900 004000 DISPLAY-HELLO. 004100 DISPLAY "hello". 004200
Code two different ways to perform a paragraph named A-PARAGRAPH eight times.
© Copyright, Macmillan Computer Publishing. All rights reserved.