Teach Yourself COBOL in 21 days, Second Edition

Previous chapterNext chapterContents


- Day 3 -
A First Look at Structured COBOL

COBOL is a structured language. You already have seen some of the rules for layout, but structure goes deeper than just physical layout. Structuring applies to the DATA and the PROCEDURE DIVISIONs of a COBOL program. Today, you learn the structure of the PROCEDURE DIVISION and explore the following topics:

A New COBOL Shell

From now on, all programs will have some sort of data in them, so it is a good idea to modify cobshl01.cbl, created in Day 1, "Your First COBOL Program." Listing 3.1, cobshl02.cbl, now includes WORKING-STORAGE.

TYPE: Listing 3.1. A new COBOL shell including data.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. COBSHL02.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500 WORKING-STORAGE SECTION.
000600
000700 PROCEDURE DIVISION.
000800 PROGRAM-BEGIN.
000900
001000 PROGRAM-DONE.
001100     STOP RUN.

Program Flow

The normal course of execution of a COBOL program is from the first statement in the PROCEDURE DIVISION to the last. Let's look at Listing 3.2, add01.cbl, line by line.

TYPE: Listing 3.2. Top-to-bottom execution.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. ADD03.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500
000600 WORKING-STORAGE SECTION.
000700
000800 01  FIRST-NUMBER      PICTURE IS 99.
000900 01  SECOND-NUMBER     PICTURE IS 99.
001000 01  THE-RESULT        PICTURE IS 999.
001100
001200 PROCEDURE DIVISION.
001300
001400 PROGRAM-BEGIN.
001500     DISPLAY "This program will add 2 numbers.".
001600     DISPLAY "Enter the first number.".
001700
001800     ACCEPT FIRST-NUMBER.
001900
002000     DISPLAY "Enter the second number.".
002100
002200     ACCEPT SECOND-NUMBER.
002300
002400     COMPUTE THE-RESULT = FIRST-NUMBER + SECOND-NUMBER.
002500
002600     DISPLAY "The result is " THE-RESULT.
002700
002800
002900 PROGRAM-DONE.
003000     STOP RUN.
003100

ANALYSIS: The program starts executing at line 001300 in the PROCEDURE DIVISION. Blank lines are skipped, so nothing happens on that line. Line 001400 is a paragraph name. Paragraphs in COBOL are used as bookmarks. The program doesn't do anything for line 001400 except to note internally that it has started a paragraph named PROGRAM-BEGIN.

At line 001500, the program displays a message on-screen. At line 001600, another is displayed. Line 001700 is blank, so it is skipped. At line 001800, the program stops, waits for keyboard input, and places the results in the variable FIRST-NUMBER.

This type of step-by-step action occurs until line 002900, when the program notes that it has begun executing a paragraph named PROGRAM-DONE. At line 003000, the statement STOP RUN is executed, and this halts the execution of the program.

Paragraph Names

Because paragraph names are used only as bookmarks, it is possible to insert more paragraph names into this program. Remember that you can assign your own paragraph names. The rules for naming paragraphs are similar to the rules for naming variables:


DO/DON'T:
DO
use uppercase paragraph names if you want your code to be portable.

DON'T use lowercase paragraph names. Even the simplest COBOL programs have a tendency to survive and grow. One day, you might find yourself porting the program to a new computer, and you will curse yourself for having used lowercase. Listing 3.3 is sprinkled with some extra paragraph names. If you compare Listing 3.2 and Listing 3.3, you will see that the sentences are identical. Because a paragraph name does not cause any command to be executed, these two programs behave identically. Enter them both into the computer and compile them. Run them one after the other and you will see no difference.


TYPE: Listing 3.3. Adding extra paragraph names.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. ADD04.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500
000600 WORKING-STORAGE SECTION.
000700
000800 01  FIRST-NUMBER      PIC 99.
000900 01  SECOND-NUMBER     PIC 99.
001000 01  THE-RESULT        PIC 999.
001100
001200 PROCEDURE DIVISION.
001300
001400 PROGRAM-BEGIN.
001500
001600     DISPLAY "This program will add 2 numbers.".
001700
001800 GET-FIRST-NUMBER.
001900
002000     DISPLAY "Enter the first number.".
002100
002200     ACCEPT FIRST-NUMBER.
002300
002400 GET-SECOND-NUMBER.
002500
002600     DISPLAY "Enter the second number.".
002700
002800     ACCEPT SECOND-NUMBER.
002900
003000 COMPUTE-AND-DISPLAY.
003100     COMPUTE THE-RESULT = FIRST-NUMBER + SECOND-NUMBER.
003200
003300     DISPLAY "The result is " THE-RESULT.
003400
003500
003600 PROGRAM-DONE.
003700     STOP RUN.
003800

ANALYSIS: Listing 3.4 includes an empty paragraph at line 001400. At lines 001500, 001800, 002400, and 003000, the paragraph names have been changed to STEP-01, STEP-02, and so on. If you inspect the code, you will notice that, because of the placement of the paragraph names, the paragraph PROGRAM-BEGIN contains no statements. Some compilers allow this, and others complain of an empty paragraph with either a warning or an error. Personal COBOL and ACUCOBOL both allow it. If you want to test your compiler, you can type this and compile it.

TYPE: Listing 3.4. An empty paragraph.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. ADD05.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500
000600 WORKING-STORAGE SECTION.
000700
000800 01  FIRST-NUMBER      PIC 99.
000900 01  SECOND-NUMBER     PIC 99.
001000 01  THE-RESULT        PIC 999.
001100
001200 PROCEDURE DIVISION.
001300
001400 PROGRAM-BEGIN.
001500 STEP-01.
001600     DISPLAY "This program will add 2 numbers.".
001700
001800 STEP-02.
001900
002000     DISPLAY "Enter the first number.".
002100
002200     ACCEPT FIRST-NUMBER.
002300
002400 STEP-03.
002500
002600     DISPLAY "Enter the second number.".
002700
002800     ACCEPT SECOND-NUMBER.
002900
003000 STEP-04.
003100     COMPUTE THE-RESULT = FIRST-NUMBER + SECOND-NUMBER.
003200
003300     DISPLAY "The result is " THE-RESULT.
003400
003500
003600 PROGRAM-DONE.
003700     STOP RUN.
003800

What Is STOP RUN?

In any programming language, certain words have special meanings in the language. In COBOL, DISPLAY "Hello" causes the word Hello to be displayed on-screen. DISPLAY has a special meaning in COBOL. It means "put the next thing on the screen."

New Term: Reserved words are reserved in the language to have a special meaning, and the programmer cannot use these words for some other purpose.

The words DATA and DIVISION appearing together mean that the section of the program where data is defined is beginning. DATA, DIVISION, and DISPLAY are reserved words. Therefore, if you create a program that displays something, it would be incorrect to name the program DISPLAY as in the following:

PROGRAM-ID. DISPLAY.

The compiler probably would complain of an invalid program name, because DISPLAY is reserved for a special meaning in COBOL. You already have learned several reserved words: COMPUTE, ACCEPT, ADD, PROCEDURE, DIVISION, and others. You learn about most of them as you move through this book.


DO/DON'T:
DO
name programs, variables, and paragraphs with descriptive names that make their use obvious.

DON'T name programs, variables, or paragraphs with reserved words.


You also have seen that WORKING-STORAGE is a reserved word for the name of the SECTION in the DATA DIVISION that contains the data. The compiler will complain if you try to name a variable WORKING-STORAGE. That combination of words is reserved for use by COBOL.

STOP RUN has appeared in every program so far. STOP RUN is a sentence in COBOL, just as DISPLAY "Hello" is. STOP and RUN are both reserved words, and the sentence STOP RUN does exactly what it says; it stops the execution of the program.

Some COBOL implementations do not require a STOP RUN; for example, Personal COBOL does not. Most compilers will compile a program that does not include a STOP RUN, and the problem, if there is one, occurs while the program is running. A program will come to the end and appear to start over again, or it will come to the end and crash with some sort of ABORT message. If you want to check out your COBOL compiler, take any of the examples already covered and remove the PROGRAM-DONE paragraph and the STOP RUN sentence. Compile the program and then try to run it. See what happens when the program reaches the end.

STOP RUN can occur anywhere in the program, and it will stop execution. In all the examples so far, the STOP RUN is placed in its own separate paragraph to make it stand out as the end of the program, but Listing 3.2 could have been written without the PROGRAM-DONE paragraph name, as long as it included STOP RUN. It would have worked as well. In Listing 3.5, the STOP RUN at line 002400 causes the program to terminate at that spot.

TYPE: Listing 3.5. A forced STOP RUN.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. ADD06.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500
000600 WORKING-STORAGE SECTION.
000700
000800 01  FIRST-NUMBER      PIC 99.
000900 01  SECOND-NUMBER     PIC 99.
001000 01  THE-RESULT        PIC 999.
001100
001200 PROCEDURE DIVISION.
001300
001400 PROGRAM-BEGIN.
001500     DISPLAY "This program will add 2 numbers.".
001600
001700
001800     DISPLAY "Enter the first number.".
001900
002000     ACCEPT FIRST-NUMBER.
002100
002200     DISPLAY "Fooled you.".
002300
002400     STOP RUN.
002500
002600     DISPLAY "Enter the second number.".
002700
002800     ACCEPT SECOND-NUMBER.
002900
003000     COMPUTE THE-RESULT = FIRST-NUMBER + SECOND-NUMBER.
003100
003200     DISPLAY "The result is " THE-RESULT.
003300
003400
003500 PROGRAM-DONE.
003600     STOP RUN.
003700

Obviously, the PROGRAM-DONE paragraph at line 003500 is misleading in this example because the program stops before this point.

What Is the PERFORM Verb?

A program that executes from beginning to end and then stops might be useful for something, but it wouldn't do much more than the examples already covered. Suppose you had one action that you performed several times in a program. In top-to-bottom execution, you would have to code that same logic over and over.

The PERFORM verb avoids this problem of coding repetitive actions. In order to illustrate the effect of a PERFORM, Listing 3.6 uses another version of the "Hello world" program. A PERFORM is a kind of "jump" with a "bounce back."

TYPE: Listing 3.6. Using PERFORM.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. HELLO04.
000300
000400* This program illustrates the use of a PERFORM
000500
000600 ENVIRONMENT DIVISION.
000700 DATA DIVISION.
000800 PROCEDURE DIVISION.
000900
001000 PROGRAM-BEGIN.
001100     DISPLAY "Today's message is:".
001200     PERFORM SAY-HELLO.
001300
001400 PROGRAM-DONE.
001500     STOP RUN.
001600
001700 SAY-HELLO.
001800     DISPLAY "Hello world".
001900

OUTPUT:

Today's message is:
Hello world
C>
C>

ANALYSIS: At line 001200, PERFORM SAY-HELLO indicates the following:

1. Locate the paragraph named SAY-HELLO.

2. Jump to that paragraph and start executing there.

3. When that paragraph ends, return to the end of this sentence (PERFORM SAY-HELLO).

A paragraph ends in two ways. Either another paragraph begins or the end of the source code file is reached. In Listing 3.6, the paragraph PROGRAM-BEGIN ends at line 001400 when PROGRAM-DONE begins. The paragraph PROGRAM-DONE ends at line 001700 when SAY-HELLO begins, and SAY-HELLO ends just after line 001900 at the end of the source code file.

Ignoring blank lines (because they will not execute), the sequence of execution in Listing 3.6 is the following: Line 001000. Internally note that the paragraph PROGRAM-BEGIN has started.

Line 001100. DISPLAY "Today's message is:" on-screen.

Line 001200. Locate the paragraph SAY-HELLO at line 001700. Jump to line 001700, the beginning of SAY-HELLO.

Line 001700. Internally note that the paragraph SAY-HELLO has started.

Line 001800. DISPLAY "Hello world" on-screen.

End of file. COBOL recognizes that it has hit the end of the SAY-HELLO paragraph, but it also knows that it is in the middle of a PERFORM requested at line 001200. Whenever a paragraph ends because of an end-of-file or because a new paragraph starts, COBOL checks whether it is in the middle of a PERFORM. If it is, it returns to the line that requested the PERFORM. In this example, the SAY-HELLO paragraph ends, and execution resumes at the end of line 001200. There are no further instructions on that line, so execution continues at line 001400.

Line 001400. Internally note that the paragraph PROGRAM-DONE has started. Line 001500. Stop execution of the program. The top-to-bottom course of a COBOL program continues unless it is interrupted by a PERFORM. The paragraph being performed is also executed top to bottom. When the PERFORM is complete, the program returns to the point just after the PERFORM was requested, and it continues from there to the bottom.

It is important to recognize this "keep-on-trucking" flow of a COBOL program, because it is critical to place your PERFORMed paragraphs below the STOP RUN statement. Listing 3.7 has the SAY-HELLO paragraph placed differently.

TYPE: Listing 3.7. An incorrectly placed paragraph.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. HELLO05.
000300
000400* This program illustrates the incorrect placement of a
000500* Paragraph that is the target of a perform
000600
000700 ENVIRONMENT DIVISION.
000800 DATA DIVISION.
000900 PROCEDURE DIVISION.
001000
001100 PROGRAM-BEGIN.
001200     DISPLAY "Today's message is:".
001300     PERFORM SAY-HELLO.
001400
001500 SAY-HELLO.
001600     DISPLAY "Hello world".
001700
001800 PROGRAM-DONE.
001900     STOP RUN.
002000

If you followed the steps describing the flow of hello05.cbl, it should come as no surprise that the program displays Hello world twice:

OUTPUT:

Today's message is:
Hello world
Hello world
C>
C>

ANALYSIS: Ignoring blank lines, the sequence of execution in Listing 3.7 is as follows: Line 001100. Internally note that the paragraph PROGRAM-BEGIN has started.

Line 001200. DISPLAY "Today's message is:" on-screen.

Line 001300. Jump to line 001500, the beginning of SAY-HELLO.

Line 001500. Internally note that the paragraph SAY-HELLO has started.

Line 001600. DISPLAY "Hello world" on-screen.

Line 001800. COBOL recognizes that it has hit the end of the SAY-HELLO paragraph, but it also knows that it is in the middle of a PERFORM requested at line 001300. The SAY-HELLO paragraph ends, and execution resumes at the end of line 001300. There are no further instructions on that line, so execution continues at line 001500.

Line 001500. Internally note that the paragraph SAY-HELLO has started.

Line 001600. DISPLAY "Hello world" on-screen.

Line 001800. COBOL recognizes that it has hit the end of the SAY-HELLO paragraph, but in this case it is not in the middle of a PERFORM.

Line 001800. Internally note that the paragraph PROGRAM-DONE has started. Line 001900. Stop execution of the program.

When to Use PERFORM

A PERFORM has several uses in COBOL. First, it is used to section off a repetitive action that is performed in several places or several times in a program to prevent writing the same code over and over.(I hinted at this use when I introduced PERFORM earlier in today's lesson.) This creates two advantages: It not only cuts down on the amount of typing, but it cuts down on the number of potential errors. Less typing means fewer opportunities to copy it incorrectly.

Imagine typing the following retail profit formula five or six times in different places in a program, and you begin to see the sense of putting this in a paragraph called COMPUTE-RETAIL-PROFIT and using the PERFORM verb every time you want it done:

COMPUTE MARGIN-PERCENT =
    ( (GOODS-PRICE - GOODS-COST) /
             GOODS-PRICE ) * 100 .

The second use of PERFORM might not be so obvious, because the programs used so far in this book have been relatively small. A PERFORM serves to break up a program into smaller, more manageable pieces. If you're changing the sales commission from 10 percent to 11 percent, it's much easier to search through a long program looking for a paragraph named CALCULATE-COMMISSION than to plow through a long list of code not broken into paragraphs. It is very common for programs to perform more than one major task. A payroll system might have a program in it used both to calculate pay totals and to print checks after the hours for each employee are entered into the computer.

A program that carries out these actions might have one area of the program to deal with the calculations, while further down in the program another area of code deals with the printing activity. Above these two areas is the main logic of the program that performs both pieces of the program:

MAIN-LOGIC.
    PERFORM CALC-PAYROLL-TOTALS.
    PERFORM PRINT-PAYROLL-CHECKS.

The third reason to use a PERFORM is that the program is easier to read and understand if the paragraphs are named sensibly. In the following code fragment, it is fairly easy to figure out what the paragraph PAY-THE-SALESPERSON is doing, even though the whole paragraph is made up of PERFORMs:

PAY-THE-SALESPERSON
    PERFORM GET-SALES-TOTAL.
    PERFORM CALCULATE-COMMISSION.
    PERFORM PRINT-THE-CHECK.

A fourth reason to use PERFORM would be to conserve memory. Look back at the retail profit formula and imagine that piece of code repeated five or six times in a single program. Each time the formula appears in the program it takes up several bytes of memory. Coding it once in a single paragraph and performing that paragraph five or six times uses far less memory.

Let's take a closer look at the first reason for a PERFORM, which is to handle repetitive code. Listing 3.8, "The Lady from Eiger," is similar to jack03.cbl, used in Day 2, "Using Variables and Constants." At line 001800, THE-NUMBER is initialized to 0, and then (instead of moving 1 to THE-NUMBER at line 002300) 1 is added to THE-NUMBER.

TYPE: Listing 3.8. Repetitive actions.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. EIGER03.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500
000600 WORKING-STORAGE SECTION.
000700
000800 01  THE-MESSAGE      PIC X(50).
000900 01  THE-NUMBER       PIC 9(2).
001000 01  A-SPACE          PIC X.
001100
001200 PROCEDURE DIVISION.
001300 PROGRAM-BEGIN.
001400
001500* Initialize the space variable
001600     MOVE " " TO A-SPACE.
001700* Start THE-NUMBER at 0
001800     MOVE 0 TO THE-NUMBER.
001900
002000* Set up and display line 1
002100     MOVE "There once was a lady from Eiger,"
002200         TO THE-MESSAGE.
002300     ADD 1 TO THE-NUMBER.
002400     DISPLAY
002500         THE-NUMBER
002600         A-SPACE
002700         THE-MESSAGE.
002800
002900* Set up and Display line 2
003000     MOVE "Who smiled and rode forth on a tiger."
003100         TO THE-MESSAGE.
003200     ADD 1 TO THE-NUMBER.
003300     DISPLAY
003400         THE-NUMBER
003500         A-SPACE
003600         THE-MESSAGE.
003700
003800* Set up and display line 3
003900     MOVE "They returned from the ride" TO THE-MESSAGE.
004000     ADD 1 TO THE-NUMBER.
004100     DISPLAY
004200         THE-NUMBER
004300         A-SPACE
004400         THE-MESSAGE.
004500
004600* Set up and display line 4
004700     MOVE "With the lady inside," TO THE-MESSAGE.
004800     ADD 1 TO THE-NUMBER.
004900     DISPLAY
005000         THE-NUMBER
005100         A-SPACE
005200         THE-MESSAGE.
005300
005400* Set up and display line 5
005500     MOVE "And the smile on the face of the tiger."
005600         TO THE-MESSAGE.
005700     ADD 1 TO THE-NUMBER.
005800     DISPLAY
005900         THE-NUMBER
006000         A-SPACE
006100         THE-MESSAGE.
006200
006300
006400 PROGRAM-DONE.
006500     STOP RUN.
006600

OUTPUT:

01 There once was a lady from Eiger,
02 Who smiled and rode forth on a tiger.
03 They returned from the ride
04 With the lady inside,
05 And the smile on the face of the tiger.
C>
C>

ANALYSIS: If you inspect lines 002300 through 002700 and lines 003200 through 003600, you'll find that the actions are identical. These appear again in lines 004000 through 004400. In fact, these two sentences are repeated five times in the program, appearing again in lines 004800 through 005200 and 005700 through 006100.

The DISPLAY command (lines 002400 through 002700, 003300 through 003600, and so on) is rather long because it is a DISPLAY of three variables. The odds of typing incorrectly are reasonably high. A typographical error wouldn't be so bad (because the compiler would complain if something were spelled incorrectly), but suppose that in one of the five instances you left out A-SPACE in the list of variables to display. It wouldn't be a disaster. It would show up the first time you ran the program; one of the lines would look odd, and you would be able to track it down quickly. Unfortunately, not all errors of this sort are so easy to spot. If this were a series of calculations, you might be able to spot an error in the final result, but you wouldn't know where it had originated.

There are two repetitive actions in Listing 3.8:

ADD 1 TO THE-NUMBER

and

DISPLAY THE-NUMBER A-SPACE THE-MESSAGE.

It is simple to extract these two lines and create a paragraph that performs both of these actions:

ADD-NUMBER-AND-DISPLAY.
ADD 1 TO THE-NUMBER
DISPLAY THE-NUMBER A-SPACE THE-MESSAGE.

Listing 3.9 is an example of using this paragraph, with PERFORMs inserted at the appropriate points.

TYPE: Listing 3.9. Using a PERFORMed paragraph.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. EIGER04.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500
000600 WORKING-STORAGE SECTION.
000700
000800 01  THE-MESSAGE      PIC X(50).
000900 01  THE-NUMBER       PIC 9(2).
001000 01  A-SPACE          PIC X.
001100
001200 PROCEDURE DIVISION.
001300 PROGRAM-BEGIN.
001400
001500* Initialize the space variable
001600     MOVE " " TO A-SPACE.
001700* Start THE-NUMBER at 0
001800     MOVE 0 TO THE-NUMBER.
001900
002000* Set up and display line 1
002100     MOVE "There once was a lady from Eiger,"
002200         TO THE-MESSAGE.
002300     PERFORM ADD-NUMBER-AND-DISPLAY.
002400
002500* Set up and Display line 2
002600     MOVE "Who smiled and rode forth on a tiger."
002700         TO THE-MESSAGE.
002800     PERFORM ADD-NUMBER-AND-DISPLAY.
002900
003000* Set up and display line 3
003100     MOVE "They returned from the ride" TO THE-MESSAGE.
003200     PERFORM ADD-NUMBER-AND-DISPLAY.
003300
003400* Set up and display line 4
003500     MOVE "With the lady inside," TO THE-MESSAGE.
003600     PERFORM ADD-NUMBER-AND-DISPLAY.
003700
003800* Set up and display line 5
003900     MOVE "And the smile on the face of the tiger."
004000         TO THE-MESSAGE.
004100     PERFORM ADD-NUMBER-AND-DISPLAY.
004200
004300 PROGRAM-DONE.
004400     STOP RUN.
004500
004600 ADD-NUMBER-AND-DISPLAY.
004700     ADD 1 TO THE-NUMBER.
004800     DISPLAY
004900         THE-NUMBER
005000         A-SPACE
005100         THE-MESSAGE.
005200

Code eiger04.cbl, compile it, and run it. Work out the flow of each PERFORM and how the program returns to the main stream of the logic. Here is the output of eiger04.cbl:

OUTPUT:

01 There once was a lady from Eiger,
02 Who smiled and rode forth on a tiger.
03 They returned from the ride
04 With the lady inside,
05 And the smile on the face of the tiger.
C>
C>

ANALYSIS: At line 002300, the computer locates ADD-NUMBER-AND-DISPLAY at line 004600 and jumps to that line. This paragraph is PERFORMed, and when complete, execution resumes at the end of line 002300. Execution continues on line 002600. Then at line 002800, another jump is made to line 004600, and the program returns to the end of line 002800. This process continues until all five PERFORM requests have been executed and ADD-NUMBER-AND-DISPLAY has been performed five times.

It is possible to request a PERFORM when you already are within a PERFORM, by nesting them together. If a paragraph that is being PERFORMed itself requests a PERFORM of another paragraph, COBOL keeps track of the layers of PERFORMed paragraphs and returns to the correct level.

In general, when a PERFORMed paragraph ends, the program returns to the line that requested the PERFORM, at a position in the line just after the PERFORM was requested. In Listing 3.10, the ADD-NUMBER-AND-DISPLAY paragraph at line 005100 has been broken down into two sentences that each PERFORM smaller paragraphs. These PERFORM sentences refer to paragraphs at lines 005800 and 006100--ADD-THE-NUMBER and DISPLAY-THE-MESSAGE. Each of these paragraphs does only one thing. In practice, you rarely would create a paragraph to execute a single statement, but this example serves to illustrate nested PERFORMs.

TYPE: Listing 3.10. Nested PERFORMs.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. EIGER05.
000300
000400* This program illustrates nested PERFORMS
000500 ENVIRONMENT DIVISION.
000600 DATA DIVISION.
000700
000800 WORKING-STORAGE SECTION.
000900
001000 01  THE-MESSAGE      PIC X(50).
001100 01  THE-NUMBER       PIC 9(2).
001200 01  A-SPACE          PIC X.
001300
001400 PROCEDURE DIVISION.
001500 PROGRAM-BEGIN.
001600
001700* Initialize the space variable
001800     MOVE " " TO A-SPACE.
001900* Start THE-NUMBER at 0
002000     MOVE 0 TO THE-NUMBER.
002100
002200* Set up and display line 1
002300     MOVE "There once was a lady from Eiger,"
002400         TO THE-MESSAGE.
002500     PERFORM ADD-NUMBER-AND-DISPLAY.
002600
002700* Set up and Display line 2
002800     MOVE "Who smiled and rode forth on a tiger."
002900         TO THE-MESSAGE.
003000     PERFORM ADD-NUMBER-AND-DISPLAY.
003100
003200* Set up and display line 3
003300     MOVE "They returned from the ride" TO THE-MESSAGE.
003400     PERFORM ADD-NUMBER-AND-DISPLAY.
003500
003600* Set up and display line 4
003700     MOVE "With the lady inside," TO THE-MESSAGE.
003800     PERFORM ADD-NUMBER-AND-DISPLAY.
003900
004000* Set up and display line 5
004100     MOVE "And the smile on the face of the tiger."
004200         TO THE-MESSAGE.
004300     PERFORM ADD-NUMBER-AND-DISPLAY.
004400
004500 PROGRAM-DONE.
004600     STOP RUN.
004700
004800* This paragraph is PERFORMED 5 times from within
004900* PROGRAM-BEGIN. This paragraph in turn PERFORMS
005000* Two other paragraphs
005100 ADD-NUMBER-AND-DISPLAY.
005200     PERFORM ADD-THE-NUMBER.
005300     PERFORM DISPLAY-THE-MESSAGE.
005400
005500* These two paragraphs will each be performed 5 times as
005600* they are each performed every time ADD-NUMBER-AND-DISPLAY
005700* is performed.
005800 ADD-THE-NUMBER.
005900     ADD 1 TO THE-NUMBER.
006000
006100 DISPLAY-THE-MESSAGE.
006200     DISPLAY
006300         THE-NUMBER
006400         A-SPACE
006500         THE-MESSAGE.
006600

ANALYSIS: The flow of the program at line 005100 is executed every time PERFORM ADD-NUMBER-AND-DISPLAY is requested: Line 005100. Internally note that the paragraph ADD-NUMBER-AND-DISPLAY has started.

Line 005200. Locate the paragraph called ADD-THE-NUMBER and jump to it at line 005800.

Line 005800. Internally note that the paragraph ADD-THE-NUMBER has started.

Line 005900. ADD 1 TO THE-NUMBER.

Line 006100. COBOL notes that ADD-THE-NUMBER has ended and returns to line 005200, where there are no further instructions.

Line 005300. Locate the paragraph named DISPLAY-THE-MESSAGE and jump to it at line 006100.

Line 006100. Internally note that the paragraph DISPLAY-THE-MESSAGE has started.

Lines 006200 through 006500. These lines are executed as one long sentence, displaying all the variables.

End of file (the last line of the source code). COBOL notes the end of DISPLAY-THE-MESSAGE and knows it is in the middle of a PERFORM. It returns to line 005300, where there are no further instructions. Line 005800. (Remember that blank lines and comment lines have no effect on the program, so the next active line is 005800.) COBOL notes that ADD-THE-NUMBER starts here; therefore, the current paragraph, ADD-NUMBER-AND-DISPLAY, must have ended. Execution returns to whatever line originally requested the PERFORM of ADD-NUMBER-AND-DISPLAY.


DO/DON'T:
DO
locate repetitive actions in your programs, and create separate paragraphs containing those actions. Then PERFORM the paragraph wherever those actions are needed.

DON'T keep typing the same code over and over in one program.


It is common for PERFORMs to be nested in COBOL programs. In fact, Listing 3.11 shows how an experienced programmer actually might organize "The Lady from Eiger." The callouts down the right side show you the sequence of execution.

TYPE: Listing 3.11. A structured program.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. EIGER06.
000300
000400* This program illustrates nested PERFORMS in a
000500* structured program.
000600 ENVIRONMENT DIVISION.
000700 DATA DIVISION.
000800
000900 WORKING-STORAGE SECTION.
001000
001100 01  THE-MESSAGE      PIC X(50).
001200 01  THE-NUMBER       PIC 9(2).
001300 01  A-SPACE          PIC X.
001400
001500 PROCEDURE DIVISION.
001600
001700* LEVEL 1 ROUTINES
001800 PROGRAM-BEGIN.	
001900
002000     PERFORM PROGRAM-INITIALIZATION.	
002100     PERFORM MAIN-LOGIC.		
002200
002300 PROGRAM-DONE.	
002400     STOP RUN.	
002500
002600*LEVEL 2 ROUTINES	
002700 PROGRAM-INITIALIZATION.
002800* Initialize the space variable
002900     MOVE " " TO A-SPACE.	
003000* Start THE-NUMBER at 0
003100     MOVE 0 TO THE-NUMBER.	
003200
003300 MAIN-LOGIC.
003400* Set up and display line 1
003500     MOVE "There once was a lady from Eiger,"	
003600         TO THE-MESSAGE.
003700     PERFORM ADD-NUMBER-AND-DISPLAY.	
003800
003900* Set up and Display line 2
004000     MOVE "Who smiled and rode forth on a tiger."	
004100         TO THE-MESSAGE.
004200     PERFORM ADD-NUMBER-AND-DISPLAY.	
004300
004400* Set up and display line 3
004500     MOVE "They returned from the ride" TO THE-MESSAGE.	
004600     PERFORM ADD-NUMBER-AND-DISPLAY.	
004700
004800* Set up and display line 4
004900     MOVE "With the lady inside," TO THE-MESSAGE.	
005000     PERFORM ADD-NUMBER-AND-DISPLAY.	
005100
005200* Set up and display line 5
005300     MOVE "And the smile on the face of the tiger."	
005400         TO THE-MESSAGE.
005500     PERFORM ADD-NUMBER-AND-DISPLAY.	
005600
005700* LEVEL 3 ROUTINES
005800* This paragraph is PERFORMED 5 times from within
005900* MAIN-LOGIC.
006000
006100 ADD-NUMBER-AND-DISPLAY.	
006200     ADD 1 TO THE-NUMBER.	
006300     DISPLAY
006400         THE-NUMBER
006500         A-SPACE	
006600         THE-MESSAGE.
006700

ANALYSIS: The "main" stream of the program runs from line 001800 to line 002400 and is quite short. All the work of the program is accomplished by requesting PERFORMs of other paragraphs. Some of these in turn request other PERFORMs. You should look over this listing and compare it carefully to Listing 3.9. You will see that the effect of the two programs is identical, and both of them use paragraphs to isolate repetitive logic. The version in eiger06.cbl additionally uses paragraphs to break out and document which parts of the code are for initializing (or setting up variables) before the main logic and which parts are the main logic of the code.

Summary

Today, you learned about the structure of the PROCEDURE DIVISION, including the following basics:

Q&A

Q Are there other limits on COBOL paragraph names?

A Paragraphs (and variables) each should have a unique name. There actually is a way around this limit, but its explanation is beyond the scope of this book. With 30 characters for a paragraph name, you should have no problem coming up with different names for each paragraph.

There is another limit that you should place on yourself for practical purposes. Paragraph names should be descriptive of what is done in the paragraph.

Q How many paragraphs can be included in the PROCEDURE DIVISION?

A This is limited only by the COBOL compiler that you are using. The number always is large enough to support large and fairly complex programs because COBOL is a language designed to handle such problems.

Q How many PERFORMs can be included in a program?

A There is no limit on PERFORMs other than the limits imposed by your compiler on the overall size of programs. See the next question.

Q If one paragraph can PERFORM another paragraph, which in turn can PERFORM another paragraph, how many levels of this nesting (PERFORMs within PERFORMs) are possible?

A This again depends entirely on your COBOL compiler. The number usually is large. Levels of 250 are not uncommon. You would have to write something very complex to nest PERFORMs 250 levels deep.

Q Can a paragraph PERFORM itself as in the following example?
DO-SOMETHING.
     PERFORM DO-SOMETHING.
A No. This is allowed in some languages, but not in COBOL.

Workshop

Quiz

1. If the code in a paragraph is designed to locate overdue customers, which of the following would be the best name for the paragraph?
a. LOCATE-CUSTOMERS.

b. FIND-SOME-STUFF.

c. LOCATE-OVERDUE-CUSTOMERS.
2. Number the lines of msg01.cbl to show the sequence in which the lines would be executed:
000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. MSG01.
000300
000400 ENVIRONMENT DIVISION.
000500 DATA DIVISION.
000600
000700 WORKING-STORAGE SECTION.
000800
000900 PROCEDURE DIVISION.
001000
001100 PROGRAM-BEGIN.
001200
001300     PERFORM MAIN-LOGIC.
001400
001500 PROGRAM-DONE.
001600     STOP RUN.
001700
001800 MAIN-LOGIC.
001900     PERFORM DISPLAY-MSG-1.
002000     PERFORM DISPLAY-MSG-2.
002100
002200 DISPLAY-MSG-1.
002300     DISPLAY "This is message 1.".
002400
002500 DISPLAY-MSG-2.
002600     DISPLAY "This is message 2.".
002700

Exercises

1. What would be the effect of omitting the PROGRAM-DONE paragraph and STOP RUN sentence from hello04.cbl in Listing 3.6? Copy hello04.cbl to hello06.cbl and edit it to remove lines 001400 and 001500. Compile and run the program. What does the display look like? The display effect should be the same as the output of Listing 3.7, hello05.cbl.

2. Trace the flow of hello06.cbl step by step and work out what is happening. What must appear before any paragraphs that are PERFORMed?

3. Work out where to place a STOP RUN in hello06.cbl to prevent the situation in Exercise 2.

4. Study the following listing, add07.cbl:
000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. ADD07.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500
000600 WORKING-STORAGE SECTION.
000700
000800 01  FIRST-NUMBER      PIC 99.
000900 01  SECOND-NUMBER     PIC 99.
001000 01  THE-RESULT        PIC 999.
001100
001200 PROCEDURE DIVISION.
001300
001400 PROGRAM-BEGIN.
001500
001600     PERFORM ADVISE-THE-USER.
001700     PERFORM GET-FIRST-NUMBER.
001800     PERFORM GET-SECOND-NUMBER.
001900     PERFORM COMPUTE-AND-DISPLAY.
002000
002100 PROGRAM-DONE.
002200     STOP RUN.
002300
002400 ADVISE-THE-USER.
002500     DISPLAY "This program will add 2 numbers.".
002600
002700 GET-FIRST-NUMBER.
002800
002900     DISPLAY "Enter the first number.".
003000     ACCEPT FIRST-NUMBER.
003100
003200 GET-SECOND-NUMBER.
003300
003400     DISPLAY "Enter the second number.".
003500     ACCEPT SECOND-NUMBER.
003600
003700 COMPUTE-AND-DISPLAY.
003800
003900     COMPUTE THE-RESULT = FIRST-NUMBER + SECOND-NUMBER.
004000     DISPLAY "The result is " THE-RESULT.
004100
Copy this to add08.cbl and modify the program so that it adds three numbers instead of two.

Hint: You can add three numbers just by continuing the COMPUTE statement:
004600     COMPUTE THE-RESULT = FIRST-NUMBER +
004700                          SECOND-NUMBER +
004800                          THIRD-NUMBER.
5. Using add02.cbl (Listing 2.6 from Day 2), redesign the program to use a logic flow similar to eiger06.cbl, with the main stream of the program being a series of PERFORMs.

Hint: Listing 3.3 provides some clues about the natural paragraphs in the program.


Previous chapterNext chapterContents


© Copyright, Macmillan Computer Publishing. All rights reserved.