Teach Yourself COBOL in 21 days, Second Edition

Previous chapterNext chapterContents


- Day 4 -
Decision Making

A program must be able to make decisions about data and to execute different sections of code based on those decisions. Controlling the flow of programs by testing conditions with the IF statement lies at the heart of every program.

This lesson deals almost exclusively with the IF statement and the many options available with it--information critical to understanding programming in COBOL. Today, you learn about the following topics:

IF

The primary method of changing the flow of a program is by making decisions using the IF verb. The following example demonstrates the IF verb:

IF condition
    PERFORM DO-SOMETHING.

When COBOL sees an IF, it makes a decision about the condition, and then either requests a PERFORM of DO-SOMETHING or skips that line of the program.

The example in Listing 4.1 uses an IF to decide which message to display. In GET-THE-ANSWER, at line 002300, this program prompts the user to enter Y or N (Yes or No) and accepts a single character from the keyboard and places it in the variable YES-OR-NO. This is not a particularly good program because if the user enters a lowercase y or n, the program does nothing at all. The problem of handling the lowercase entry is addressed later in this chapter. The general problem of handling lowercase versus uppercase data entry is covered in Day 15, "Data Integrity." For now, just press the Caps Lock key on the left of your keyboard to force all data entry into uppercase.

TYPE: Listing 4.1. Testing values using IF.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. YESNO01.
000300*--------------------------------------------------
000400* This program asks for a Y or N answer, and then
000500* displays whether the user chose yes or no.
000600*--------------------------------------------------
000700 ENVIRONMENT DIVISION.
000800 DATA DIVISION.
000900 WORKING-STORAGE SECTION.
001000
001100 01  YES-OR-NO      PIC X.
001200
001300 PROCEDURE DIVISION.
001400 PROGRAM-BEGIN.
001500
001600     PERFORM GET-THE-ANSWER.
001700
001800     PERFORM DISPLAY-THE-ANSWER.
001900
002000 PROGRAM-DONE.
002100     STOP RUN.
002200
002300 GET-THE-ANSWER.
002400
002500     DISPLAY "Is the answer Yes or No? (Y/N)".
002600     ACCEPT YES-OR-NO.
002700
002800 DISPLAY-THE-ANSWER.
002900     IF YES-OR-NO IS EQUAL "Y"
003000         DISPLAY "You answered Yes.".
003100
003200     IF YES-OR-NO IS EQUAL "N"
003300         DISPLAY "You answered No.".
003400

This is the output of yesno01.cbl if you enter a Y:

OUTPUT:

Is the answer Yes or No? (Y/N)
Y
You answered Yes.

C>
C>

ANALYSIS: Edit, compile, and run this program; then try it, entering a few different answers. You will notice that it displays a message only if the entry is an uppercase Y or N. When you are comparing alphanumeric variables, the values are case-dependent, so y is not the same as Y, and n is not the same as N.


DO/DON'T:
DO
test for both uppercase and lowercase versions of an alphanumeric field, if either uppercase or lowercase values are valid.

DON'T ignore case differences in a variable if they are important in a program.


In DISPLAY-THE-ANSWER, at lines 002800 through 003300, one of two possible messages is displayed, based on whether the user entered a Y or an N.

At line 002900, the condition being tested is YES-OR-NO IS EQUAL "Y". IS EQUAL are COBOL reserved words used for testing whether two values are equal. The IF sentences in DISPLAY-THE-ANSWER at lines 002900 and 003200 are each two lines long; there is no period until the end of the second line.

When the criteria of a tested condition are met, the condition is considered to be true. When the criteria of a tested condition are not met, the condition is considered to be false. The DISPLAY statement at line 003000 is executed only when the condition being tested by the IF at line 002900 (YES-OR-NO IS EQUAL "Y") is true. When the IF at line 002900 is not true (any character but Y is entered), line 003000 is skipped. The DISPLAY statement at line 003300 is executed only when the condition being tested by the IF at line 003200 (YES-OR-NO IS EQUAL "N") is true. When the IF at line 003200 is not true (any character but N is entered), line 003300 is skipped. When a condition tested by an IF statement is not true, any statements controlled by the IF are not executed.

Depending on the user's input, there are three possible output results from this program:

Listing 4.2 adds the extra step of editing the user's answer to adjust for a lowercase y or n.

TYPE: Listing 4.2. Editing the answer.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. YESNO02.
000300*--------------------------------------------------
000400* This program asks for a Y or N answer, and then
000500* displays whether the user chose yes or no.
000600* The edit logic allows for entry of Y, y, N, or n.
000700*--------------------------------------------------
000800 ENVIRONMENT DIVISION.
000900 DATA DIVISION.
001000 WORKING-STORAGE SECTION.
001100
001200 01  YES-OR-NO      PIC X.
001300
001400 PROCEDURE DIVISION.
001500 PROGRAM-BEGIN.
001600
001700     PERFORM GET-THE-ANSWER.
001800
001900     PERFORM EDIT-THE-ANSWER.
002000
002100     PERFORM DISPLAY-THE-ANSWER.
002200
002300 PROGRAM-DONE.
002400     STOP RUN.
002500
002600 GET-THE-ANSWER.
002700
002800     DISPLAY "Is the answer Yes or No? (Y/N)".
002900     ACCEPT YES-OR-NO.
003000
003100 EDIT-THE-ANSWER.
003200
003300     IF YES-OR-NO IS EQUAL "y"
003400         MOVE "Y" TO YES-OR-NO.
003500
003600     IF YES-OR-NO IS EQUAL "n"
003700         MOVE "N" TO YES-OR-NO.
003800
003900 DISPLAY-THE-ANSWER.
004000     IF YES-OR-NO IS EQUAL "Y"
004100         DISPLAY "You answered Yes.".
004200
004300     IF YES-OR-NO IS EQUAL "N"
004400         DISPLAY "You answered No.".
004500

ANALYSIS: In EDIT-THE-ANSWER at line 003300, the program checks to see whether the user entered a y. If true, at line 003400 the program forces this to become a Y. In the same paragraph at lines 003600 and 003700, an n will be changed to an N.

The tests in DISPLAY-THE-ANSWER work correctly now, because the answer has been forced to uppercase Y or N by the EDIT-THE-ANSWER paragraph.

If you edit, compile, and run yesno02.cbl, you will find that uppercase and lowercase versions of y and n are now all valid entries. The program still displays no message if anything else is entered. (I will address this problem later in this chapter, in the section entitled IF-ELSE.)

Using IF to Control Multiple Statements

Listing 4.3 executes multiple statements under the control of the IF tests at lines 004000 and 004400. In each sequence, a PERFORM is requested to display an additional message before the main message is displayed. More than one statement can be executed when an IF tests true:

IF condition
    PERFORM DO-SOMETHING
    PERFORM DO-SOMETHING-ELSE.

An IF controls all statements under it until the sentence ends. When an IF tests true, all statements up to the next period are executed. When an IF tests false, all statements up to the next period are skipped.

TYPE: Listing 4.3. Controlling multiple statements with IF.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. YESNO03.
000300*--------------------------------------------------
000400* This program asks for a Y or N answer, and then
000500* displays whether the user chose yes or no.
000600* The edit logic allows for entry of Y, y, N, or n.
000700*--------------------------------------------------
000800 ENVIRONMENT DIVISION.
000900 DATA DIVISION.
001000 WORKING-STORAGE SECTION.
001100
001200 01  YES-OR-NO      PIC X.
001300
001400 PROCEDURE DIVISION.
001500 PROGRAM-BEGIN.
001600
001700     PERFORM GET-THE-ANSWER.
001800
001900     PERFORM EDIT-THE-ANSWER.
002000
002100     PERFORM DISPLAY-THE-ANSWER.
002200
002300 PROGRAM-DONE.
002400     STOP RUN.
002500
002600 GET-THE-ANSWER.
002700
002800     DISPLAY "Is the answer Yes or No? (Y/N)".
002900     ACCEPT YES-OR-NO.
003000
003100 EDIT-THE-ANSWER.
003200
003300     IF YES-OR-NO IS EQUAL "y"
003400         MOVE "Y" TO YES-OR-NO.
003500
003600     IF YES-OR-NO IS EQUAL "n"
003700         MOVE "N" TO YES-OR-NO.
003800
003900 DISPLAY-THE-ANSWER.
004000     IF YES-OR-NO IS EQUAL "Y"
004100         PERFORM IT-IS-VALID
004200         DISPLAY "You answered Yes.".
004300
004400     IF YES-OR-NO IS EQUAL "N"
004500         PERFORM IT-IS-VALID
004600         DISPLAY "You answered No.".
004700
004800 IT-IS-VALID.
004900     DISPLAY "Your answer is valid and".
005000

OUTPUT:

Is the answer Yes or No? (Y/N)
y
Your answer is valid and
You answered Yes.

C>
C>

ANALYSIS: When the IF at line 004400 tests true, lines 004100 and 004200 are executed, one after the other. Line 004100 is a PERFORM request that causes a message to be displayed at line 004900. A similar action happens when the IF at line 004000 tests true and lines 004500 and 004600 are executed.

What Can You Test with IF?

The condition in an IF verb is a test of one value against another for equality or inequality.

New Term: The symbols used to compare two values are called comparison operators. The short and long versions of these comparisons are all comparison operators. IS NOT EQUAL, NOT =, =, IS EQUAL, NOT <, >, GREATER THAN, and NOT GREATER THAN are all examples of comparison operators. Tables 4.1 and 4.2 list all of the comparison operators.

Table 4.1 lists the comparisons that can be made and describes their effects.

Table 4.1. COBOL comparison operators.

Comparison Operator Description
IF x IS EQUAL y True if x equals y
IF x IS LESS THAN y True if x is less than y
IF x IS GREATER THAN y True if x is greater than y
IF x IS NOT EQUAL y True if x does not equal y
IF x IS NOT LESS THAN y True if x is not less than y (or is equal to or greater than y)
IF x IS NOT GREATER THAN y True if x is not greater than y (or is equal to or less than y)

The word IS in a comparison is optional, and EQUAL, GREATER THAN, and LESS THAN can be shortened to =, >, and <, respectively. Table 4.2 compares the possible versions of comparisons.

Table 4.2. More COBOL comparison operators.

Optional Operator Shortest Version
IF x EQUAL y IF x = y
IF x LESS THAN y IF x < y
IF x GREATER THAN y IF x > y
IF x NOT EQUAL y IF x NOT = y
IF x NOT LESS THAN y IF x NOT < y
IF x NOT GREATER THAN y IF x NOT > y

Listing 4.4 repeats yesno03.cbl, using the shortened comparisons.

TYPE: Listing 4.4. yesno03.cbl with shorter comparisons.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. YESNO04.
000300*--------------------------------------------------
000400* This program asks for a Y or N answer, and then
000500* displays whether the user chose yes or no.
000600* The edit logic allows for entry of Y, y, N, or n.
000700*--------------------------------------------------
000800 ENVIRONMENT DIVISION.
000900 DATA DIVISION.
001000 WORKING-STORAGE SECTION.
001100
001200 01  YES-OR-NO      PIC X.
001300
001400 PROCEDURE DIVISION.
001500 PROGRAM-BEGIN.
001600
001700     PERFORM GET-THE-ANSWER.
001800
001900     PERFORM EDIT-THE-ANSWER.
002000
002100     PERFORM DISPLAY-THE-ANSWER.
002200
002300 PROGRAM-DONE.
002400     STOP RUN.
002500
002600 GET-THE-ANSWER.
002700
002800     DISPLAY "Is the answer Yes or No? (Y/N)".
002900     ACCEPT YES-OR-NO.
003000
003100 EDIT-THE-ANSWER.
003200
003300     IF YES-OR-NO = "y"
003400         MOVE "Y" TO YES-OR-NO.
003500
003600     IF YES-OR-NO = "n"
003700         MOVE "N" TO YES-OR-NO.
003800
003900 DISPLAY-THE-ANSWER.
004000     IF YES-OR-NO = "Y"
004100         PERFORM IT-IS-VALID
004200         DISPLAY "You answered Yes.".
004300
004400     IF YES-OR-NO = "N"
004500         PERFORM IT-IS-VALID
004600         DISPLAY "You answered No.".
004700
004800 IT-IS-VALID.
004900     DISPLAY "Your answer is valid and".
005000

For numeric values, all these tests make sense. Less than and greater than are both conditions that easily can be established when you are testing two numbers. But what are you testing when you compare two alphanumeric variables?

When a condition test is performed on alphanumeric variables, the tests usually compare the characters in the two alphanumeric values on the left and right sides of the comparison operator, in ASCII order. (See Appendix B, "ASCII.")

New Term: The sequence in which the characters appear in the ASCII chart is known as the ASCII collating sequence. Collate means to assemble in some sort of order--in this case, ASCII order.

ASCII is not the only collating sequence. IBM mainframes use a collating sequence called EBCDIC. In the ASCII collating sequence, numbers appear before uppercase letters, and uppercase letters appear before lowercase letters. In the EBCDIC collating sequence, lowercase letters appear before uppercase letters and numbers appear last. Punctuation characters vary quite a bit in the EBCDIC and ASCII collating sequences. Collating sequences also vary for different spoken languages. Castillian Spanish treats the letter combinations ch and ll as single letters so that llanero sorts after luna and chico sorts after corazon. The examples in this book are based on the English ASCII collating sequence.

In ASCII order, A is less than B, AB is less than ABC, and the uppercase letters are less than the lowercase letters; so, ABC is less than abc. When an alphanumeric variable contains the digits 0 through 9, the digits are less than the characters, so 1BC is less than ABC. Spaces are the lowest of all, so three spaces are less than 00A. Refer to Appendix B for the complete set and sequence of ASCII characters.

Listing 4.5 will accept two words from a user and then display them in ASCII order. You can use this program any time you want to find out the actual ASCII order for two values. The testing is done in the paragraph DISPLAY-THE-WORDS, which starts at line 004100. The actual tests, at lines 004500 and 004900, use a greater than (>) and a not greater than (NOT >) comparison to decide which word to display first.

TYPE: Listing 4.5. Displaying two words in ASCII order.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. WRDSRT01.
000300*----------------------------------------------
000400* Accepts 2 words from the user and then displays
000500* them in ASCII order.
000600*----------------------------------------------
000700 ENVIRONMENT DIVISION.
000800 DATA DIVISION.
000900 WORKING-STORAGE SECTION.
001000
001100 01  WORD-1                 PIC X(50).
001200 01  WORD-2                 PIC X(50).
001300
001400 PROCEDURE DIVISION.
001500 PROGRAM-BEGIN.
001600
001700     PERFORM INITIALIZE-PROGRAM.
001800     PERFORM ENTER-THE-WORDS.
001900     PERFORM DISPLAY-THE-WORDS.
002000
002100 PROGRAM-DONE.
002200     STOP RUN.
002300
002400* Level 2 Routines
002500
002600 INITIALIZE-PROGRAM.
002700     MOVE " " TO WORD-1.
002800     MOVE " " TO WORD-2.
002900
003000 ENTER-THE-WORDS.
003100     DISPLAY "This program will accept 2 words,".
003200     DISPLAY "and then display them".
003300     DISPLAY "in ASCII order.".
003400
003500     DISPLAY "Please enter the first word.".
003600     ACCEPT WORD-1.
003700
003800     DISPLAY "Please enter the second word.".
003900     ACCEPT WORD-2.
004000
004100 DISPLAY-THE-WORDS.
004200
004300     DISPLAY "The words in ASCII order are:".
004400
004500     IF WORD-1 > WORD-2
004600         DISPLAY WORD-2
004700         DISPLAY WORD-1.
004800
004900     IF WORD-1 NOT > WORD-2
005000         DISPLAY WORD-1
005100         DISPLAY WORD-2.
005200

Here is the sample output of wrdsrt01.cbl when the words entered are beta and alpha:

OUTPUT:

This program will accept 2 words,
and then display them
in ASCII order.
Please enter the first word.
beta
Please enter the second word.
alpha
The words in ASCII order are:
alpha
beta

C>

ANALYSIS: Multiple statements are executed within the IF tests at lines 004500 and 004900. There are two DISPLAY statements under each of the IF tests. If WORD-1 is greater than WORD-2, or if WORD-1 occurs after WORD-2 in the ASCII sorting sequence, WORD-2 is displayed first.

You should edit, compile, and run wrdsrt01.cbl; then try it with various pairs of "words," such as ABC and abc, (space)ABC and ABC, or ABCD and ABC, to see how these are arranged in ASCII order.

Please note that many people, including experienced programmers, assume that the opposite of GREATER THAN is LESS THAN. However, testing for only these two conditions misses the case where the two entered words are identical. The complement of GREATER THAN is LESS THAN OR EQUAL which is correctly stated as NOT GREATER THAN.

You also can try a version of wrdsrt01.cbl that reverses the test in DISPLAY-THE-WORDS, as in Listing 4.6, which is just a listing of the DISPLAY-THE-WORDS paragraph. Try coding this one as wrdsrt02.cbl and satisfy yourself that the results are identical. Note that the test and display order are reversed.

TYPE: Listing 4.6. Reversing the test and display.

004100 DISPLAY-THE-WORDS.
004200
004300     DISPLAY "The words sorted in ASCII order are:".
004400     IF WORD-1 < WORD-2
004500         DISPLAY WORD-1
004600         DISPLAY WORD-2.
004700     IF WORD-1 NOT < WORD-2
004800         DISPLAY WORD-2
004900         DISPLAY WORD-1.

You should also try a version of wrdsrt01.cbl that tests incorrectly in DISPLAY-THE-WORDS, as in Listing 4.7. This version tests for LESS THAN and GREATER THAN. Try coding this one as badsrt.cbl and satisfy yourself that the results are identical unless you enter the exact string for WORD-1 and WORD-2, such as ABC and ABC. Note that the test fails to display anything for this condition.

TYPE: Listing 4.7. An incorrect version of the test.

004100 DISPLAY-THE-WORDS.
004200
004300     DISPLAY "The words sorted in ASCII order are:".
004400     IF WORD-1 < WORD-2
004500         DISPLAY WORD-1
004600         DISPLAY WORD-2.
004700     IF WORD-1 > WORD-2
004800         DISPLAY WORD-2
004900         DISPLAY WORD-1.

The indentation chosen for the IF is completely arbitrary. As long as the IF starts in and stays within Area B, the arrangement is up to you. Listing 4.8 and Listing 4.9 are equally valid, but in Listing 4.9 it is difficult to tell what is going on, and Listing 4.8 looks a bit sloppy.


DO/DON'T:
DO
indent IF conditions carefully. An IF controls all statements up to the period at the end of the sentence.

DON'T use sloppy indenting on an IF. Correct indentation gives a good visual clue of which parts of the program are controlled by the IF.


TYPE: Listing 4.8. Sloppy indenting of an IF.

004100 DISPLAY-THE-WORDS.
004200
004300     DISPLAY "The words sorted in ASCII order are:".
004400     IF WORD-1 < WORD-2
004500      DISPLAY WORD-1
004600            DISPLAY WORD-2.
004700     IF WORD-1 NOT < WORD-2
004800             DISPLAY WORD-2
004900         DISPLAY WORD-1.

TYPE: Listing 4.9. Failing to indent an IF.

004100 DISPLAY-THE-WORDS.
004200
004300     DISPLAY "The words sorted in ASCII order are:".
004400     IF WORD-1 < WORD-2
004500     DISPLAY WORD-1
004600     DISPLAY WORD-2.
004700     IF WORD-1 NOT < WORD-2
004800     DISPLAY WORD-2
004900     DISPLAY WORD-1.

Testing Multiple Conditions

An IF test also can be used to test more than one condition. Conditions can be combined by using AND, OR, or combinations of both. Listing 4.10 is a short menu program. A menu program is designed to display a series of options on the screen and let the user pick one option to execute. In this menu program, the user has a choice of displaying one of three possible messages.

TYPE: Listing 4.10. Combining tests using OR.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. MENU01.
000300*------------------------------------------------
000400* THIS PROGRAM DISPLAYS A THREE CHOICE MENU OF
000500* MESSAGES THAT CAN BE DISPLAYED.
000600* THE USER ENTERS THE CHOICE, 1, 2 OR 3, AND
000700* THE APPROPRIATE MESSAGE IS DISPLAYED.
000800* AN ERROR MESSAGE IS DISPLAYED IF AN INVALID
000900* CHOICE IS MADE.
001000*------------------------------------------------
001100 ENVIRONMENT DIVISION.
001200 DATA DIVISION.
001300 WORKING-STORAGE SECTION.
001400
001500 01  MENU-PICK       PIC 9.
001600
001700 PROCEDURE DIVISION.
001800 PROGRAM-BEGIN.
001900
002000     PERFORM GET-THE-MENU-PICK.
002100
002200     PERFORM DO-THE-MENU-PICK.
002300
002400 PROGRAM-DONE.
002500     STOP RUN.
002600
002700* LEVEL 2 ROUTINES
002800 GET-THE-MENU-PICK.
002900
003000     PERFORM DISPLAY-THE-MENU.
003100     PERFORM GET-THE-PICK.
003200
003300 DO-THE-MENU-PICK.
003400     IF MENU-PICK < 1 OR
003500        MENU-PICK > 3
003600         DISPLAY "Invalid selection".
003700
003800     IF MENU-PICK = 1
003900         DISPLAY "One for the money.".
004000
004100     IF MENU-PICK = 2
004200         DISPLAY "Two for the show.".
004300
004400     IF MENU-PICK = 3
004500         DISPLAY "Three to get ready.".
004600
004700* LEVEL 3 ROUTINES
004800 DISPLAY-THE-MENU.
004900     DISPLAY "Please enter the number of the message".
005000     DISPLAY "that you wish to display.".
005100* Display a blank line
005200     DISPLAY " ".
005300     DISPLAY "1.  First Message".
005400     DISPLAY "2.  Second Message".
005500     DISPLAY "3.  Third Message".
005600* Display a blank line
005700     DISPLAY " ".
005800     DISPLAY "Your selection (1-3)?".
005900
006000 GET-THE-PICK.
006100     ACCEPT MENU-PICK.
006200

Here are sample output results from menu01.cbl for a valid and an invalid response:

OUTPUT:

Please enter the number of the message
that you wish to display.

1.  First Message
2.  Second Message
3.  Third Message

Your selection (1-3)?
2
Two for the show.

C>
C>

Please enter the number of the message
that you wish to display.

1.  First Message
2.  Second Message
3.  Third Message

Your selection (1-3)?
5
Invalid selection

C>
C>

ANALYSIS: The valid menu selections are 1, 2, and 3. The test that the value entered is in a range at lines 003400 through 003500, ending with a display of an invalid entry message at line 003600. If the entered MENU-PICK is less than 1 or greater than 3, it is invalid. Note that the OR on line 003400 combines the two tests within one IF. An OR test is true if either of the tests is true.

Read the comments in the program, because they explain some of the options used to improve the look of the displayed menu. The levels in the comments relate to the level of PERFORM. Routines in level 2 are being performed from the top level of the program, PROGRAM-BEGIN. Routines in level 3 are performed from within routines at level 2.

An AND test is true only if both conditions being tested are true. Listing 4.11 asks the user to enter a number between 10 and 100, excluding 10 and 100. Therefore, the valid range of entries for this program is 011 through 099. Remember that ACUCOBOL will require that you enter the leading zero.

TYPE: Listing 4.11. Combining tests with AND.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. RANGE01.
000300*------------------------------------------------
000400* ASKS USER FOR A NUMBER BETWEEN 10 AND 100
000500* EXCLUSIVE AND PRINTS A MESSAGE IF THE ENTRY
000600* IS IN RANGE.
000700*------------------------------------------------
000800 ENVIRONMENT DIVISION.
000900 DATA DIVISION.
001000 WORKING-STORAGE SECTION.
001100
001200 01  THE-NUMBER           PIC 999.
001300
001400 PROCEDURE DIVISION.
001500 PROGRAM-BEGIN.
001600
001700     PERFORM GET-THE-NUMBER.
001800
001900     PERFORM CHECK-THE-NUMBER.
002000
002100 PROGRAM-DONE.
002200     STOP RUN.
002300
002400 GET-THE-NUMBER.
002500     DISPLAY "Enter a number greater than 10".
002600     DISPLAY "and less than 100. (011-099)".
002700     ACCEPT THE-NUMBER.
002800
002900 CHECK-THE-NUMBER.
003000     IF THE-NUMBER > 10 AND
003100        THE-NUMBER < 100
003200         DISPLAY "The number is in range.".
003300

ANALYSIS: At lines 003000 and 003100, THE-NUMBER must be greater than 10 and less than 100 to be valid.

IF-ELSE

When an IF test fails, none of the statements controlled by the IF test are executed. The program continues to the next sentence and skips all the logic. In Listing 4.5 (wrdsrt0103.cbl), at lines 004500 through 005100, two IF tests are done to check the correct order for displaying WORD-1 and WORD-2. In these two comparisons, the second IF test is the exact opposite of the first IF test:

WORD-1 > WORD-2
WORD-1 NOT > WORD-2.

If you refer to Listing 4.7, you will recall that I had you deliberately create an error in the two tests by testing LESS THAN followed by GREATER THAN. It is entirely possible to make this exact error by accident. Rather than worrying about testing the complementary condition, you can use the ELSE clause of an IF to do it for you. If you are testing a condition and you want to do one set of commands if the condition or conditions are true and another set if they are false, it is easier to use ELSE than to try to word an IF with the opposite condition.

An ELSE has the following form:


IF condition
    statement
    statement
ELSE
    statement
    statement.

The following is an example of an ELSE statement:

IF A < B
    PERFORM ACTION-A
    PERFORM ACTION-B
ELSE
    PERFORM ACTION-C
    PERFORM ACTION-D.

ELSE can be used in an IF test to specify what to do when the IF condition does not test as true. An ELSE also can execute multiple statements. In an IF-ELSE statement, when the IF condition is true, all statements up to the ELSE are executed. Otherwise, all statements from the ELSE to the closing period are executed. The period is placed at the end of the last statement in the ELSE.

Listing 4.12 is a slightly improved version of wrdsrt01.cbl. The two IF tests have been replaced by an IF-ELSE. You should be able to copy wrdsrt01.cbl to wrdsrt03.cbl and make the two changes needed easily. Remove the period at the end of line 004700, and change the second IF test to an ELSE.

TYPE: Listing 4.12. Using IF-ELSE.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. WRDSRT03.
000300*----------------------------------------------
000400* Accepts 2 words from the user and then displays
000500* them in ASCII order.
000600*----------------------------------------------
000700 ENVIRONMENT DIVISION.
000800 DATA DIVISION.
000900 WORKING-STORAGE SECTION.
001000
001100 01  WORD-1                 PIC X(50).
001200 01  WORD-2                 PIC X(50).
001300
001400 PROCEDURE DIVISION.
001500 PROGRAM-BEGIN.
001600
001700     PERFORM INITIALIZE-PROGRAM.
001800     PERFORM ENTER-THE-WORDS.
001900     PERFORM DISPLAY-THE-WORDS.
002000
002100 PROGRAM-DONE.
002200     STOP RUN.
002300
002400* Level 2 Routines
002500
002600 INITIALIZE-PROGRAM.
002700     MOVE " " TO WORD-1.
002800     MOVE " " TO WORD-2.
002900
003000 ENTER-THE-WORDS.
003100     DISPLAY "This program will accept 2 words,".
003200     DISPLAY "and then display them".
003300     DISPLAY "in ASCII order.".
003400
003500     DISPLAY "Please enter the first word.".
003600     ACCEPT WORD-1.
003700
003800     DISPLAY "Please enter the second word.".
003900     ACCEPT WORD-2.
004000
004100 DISPLAY-THE-WORDS.
004200
004300     DISPLAY "The words in ASCII order are:".
004400
004500     IF WORD-1 > WORD-2
004600         DISPLAY WORD-2
004700         DISPLAY WORD-1
004800     ELSE
004900         DISPLAY WORD-1
005000         DISPLAY WORD-2.
005100

The IF-ELSE construction is useful when you are working with combined tests.

Look at Listing 4.11 again and try to work out the opposite test to the test at lines 003000 and 003100. It should be something like the lines in Listing 4.13.

TYPE: Listing 4.13. The original test and its opposite.

003000     IF THE-NUMBER > 10 AND
003100        THE-NUMBER < 100
003200         DISPLAY "The number is in range.".
003300
003400     IF THE-NUMBER NOT > 10 OR
003500        THE-NUMBER NOT < 100
000000         DISPLAY "The number is not in range.".

Listing 4.14 handles the problem by using ELSE, and it is simpler to code and easier to understand.

TYPE: Listing 4.14. Using ELSE.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. RANGE02.
000300*------------------------------------------------
000400* ASKS USER FOR A NUMBER BETWEEN 10 AND 100
000500* EXCLUSIVE AND PRINTS A MESSAGE IF THE ENTRY
000600* IS IN RANGE.
000700*------------------------------------------------
000800 ENVIRONMENT DIVISION.
000900 DATA DIVISION.
001000 WORKING-STORAGE SECTION.
001100
001200 01  THE-NUMBER           PIC 999.
001300
001400 PROCEDURE DIVISION.
001500 PROGRAM-BEGIN.
001600
001700     PERFORM GET-THE-NUMBER.
001800
001900     PERFORM CHECK-THE-NUMBER.
002000
002100 PROGRAM-DONE.
002200     STOP RUN.
002300
002400 GET-THE-NUMBER.
002500     DISPLAY "Enter a number greater than 10".
002600     DISPLAY "and less than 100. (011-099)".
002700     ACCEPT THE-NUMBER.
002800
002900 CHECK-THE-NUMBER.
003000     IF THE-NUMBER > 10 AND
003100        THE-NUMBER < 100
003200         DISPLAY "The number is in range."
003300     ELSE
003400         DISPLAY "The number is out of range.".
003500

Listing 4.15 is another version of the yes/no problem. In this listing, the answer is tested for Y or N, and a separate paragraph is performed if the answer is valid. Otherwise (ELSE), an invalid entry message is displayed. The code in the paragraph DISPLAY-YES-OR-NO can be written differently. See whether you can figure out what to change, and then look at the analysis after the listing.

TYPE: Listing 4.15. Using IF-ELSE.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. YESNO05.
000300*--------------------------------------------------
000400* This program asks for a Y or N answer, and then
000500* displays whether the user chose yes or no
000600* or an invalid entry.
000700* The edit logic allows for entry of Y, y, N, or n.
000800*--------------------------------------------------
000900 ENVIRONMENT DIVISION.
001000 DATA DIVISION.
001100 WORKING-STORAGE SECTION.
001200
001300 01  YES-OR-NO      PIC X.
001400
001500 PROCEDURE DIVISION.
001600 PROGRAM-BEGIN.
001700
001800     PERFORM GET-THE-ANSWER.
001900
002000     PERFORM EDIT-THE-ANSWER.
002100
002200     PERFORM DISPLAY-THE-ANSWER.
002300
002400 PROGRAM-DONE.
002500     STOP RUN.
002600
002700 GET-THE-ANSWER.
002800
002900     DISPLAY "Is the answer Yes or No? (Y/N)".
003000     ACCEPT YES-OR-NO.
003100
003200 EDIT-THE-ANSWER.
003300
003400     IF YES-OR-NO = "y"
003500         MOVE "Y" TO YES-OR-NO.
003600
003700     IF YES-OR-NO = "n"
003800         MOVE "N" TO YES-OR-NO.
003900
004000 DISPLAY-THE-ANSWER.
004100
004200     IF YES-OR-NO = "Y" OR
004300        YES-OR-NO = "N"
004400         PERFORM DISPLAY-YES-OR-NO
004500     ELSE
004600         DISPLAY "Your entry was invalid.".
004700
004800 DISPLAY-YES-OR-NO.
004900
005000     IF YES-OR-NO = "Y"
005100         DISPLAY "You answered Yes.".
005200
005300     IF YES-OR-NO = "N"
005400         DISPLAY "You answered No.".
005500

ANALYSIS: The paragraph DISPLAY-YES-OR-NO is performed only if YES-OR-NO is Y or N, so this paragraph could be simplified by using an ELSE:

DISPLAY-YES-OR-NO.

    IF YES-OR-NO = "Y"
        DISPLAY "You answered Yes."
    ELSE
        DISPLAY "You answered No.".


DO/DON'T:
DO
type IF and IF-ELSE constructions carefully. An IF controls all statements up to the next ELSE, or to the period at the end of the sentence if there is no ELSE. An ELSE controls all statements up to the period at the end of the sentence.

DON'T use sloppy indenting on IF and IF-ELSE verbs. Correct indentation gives a good visual clue of which parts of the program are controlled by the IF and which are controlled by the ELSE.

A final note in IF-ELSE indentation is that COBOL unfortunately uses the period as a sentence terminator. The period is almost invisible and can even get lost in a listing printed with a poor ribbon. This is another reason that source code should be kept as standardized as possible. Proper IF-ELSE indentations are one way of keeping your code easy to read.


Summary

Today's lesson explored controlling the flow of programs by testing conditions with the IF statement. You learned these basics:

Q&A

Q Can a numeric variable be tested against an alphanumeric variable?

A Some compilers let you get away with this, but it is a very bad habit. If THE-MESSAGE is a PIC X containing the character "2", and THE-NUMBER is a PIC 9 containing 2, the statement
IF THE-MESSAGE = THE-NUMBER
could produce the following different results:

Because only one of these possibilities is what you want, it isn't worth trying to work with a particular compiler's idiosyncrasies. It is also makes it hard to figure out what the program is doing when unlike data types are compared.

Workshop

Quiz

1. In the following paragraph DECIDE-WHAT-TO-DO, which lines are executed when THE-NUMBER equals 7?
005200 DECIDE-WHAT-TO-DO.
005300     IF THE-NUMBER = 7 OR
005400        THE-NUMBER < 4
005500         PERFORM ACTION-1
005600         PERFORM ACTION-2
005700     ELSE
005800         PERFORM ACTION-3.
005900
2. Which lines are executed when THE-NUMBER equals 6?

3. Which lines are executed when THE-NUMBER equals 2?

4. Which lines are executed when THE-NUMBER equals 4?

Exercises

1. Modify Listing 4.2 to allow Maybe as a third possible answer.

2. Modify Listing 4.4 to allow Maybe as a third possible answer.

Hint: You can test more than two conditions using AND or OR, as in the following example:
004400     IF YES-OR-NO = "Y" OR
004500        YES-OR-NO = "N" OR
004600        YES-OR-NO = "M"
004700         PERFORM DISPLAY-YES-NO-OR-MAYBE


Previous chapterNext chapterContents


© Copyright, Macmillan Computer Publishing. All rights reserved.