Book Read Free

Michael Coughlan

Page 15

by Beginning COBOL for Programmers-Apress (2014) (pdf)


  PERFORM UNTIL EndOfStudentFile

  DISPLAY StudentName SPACE StudentId SPACE CourseCode

  READ StudentFile

  AT END SET EndOfStudentFile TO TRUE

  END-READ

  END-PERFORM

  CLOSE StudentFile

  STOP RUN.

  In Listing 5-6, the condition name EndOfStudentFile is associated with the group item (which also happens to be a record) StudentDetails. When EndOfStudentFile is set to true, the entire StudentDetails area of storage (38 characters) is flushed with highest possible character value.

  This arrangement has two major advantages:

  • The EndOfStudentFile condition name is kept with its associated file.

  • Flushing the record with HIGH-VALUES at the end of the file eliminates the need for an explicit

  condition when doing a key-matching update of a sequential file.

  Condition Name Tricks

  When you become aware that setting a condition name forces a value into the associated data item, it is tempting to see just how far you can take this idea. Listing 5-7 takes advantage of the way condition names work to automatically move an appropriate error message into a message buffer. The program is just a stub to test this error-messaging idea; it doesn’t actually validate the date. Instead, the user manually enters one of the codes that would be returned by the date-validation routine.

  Listing 5-7. Using Condition Names to Set Up a Date-Validation Error Message

  IDENTIFICATION DIVISION.

  PROGRAM-ID. Listing5-7.

  AUTHOR. Michael Coughlan.

  DATA DIVISION.

  WORKING-STORAGE SECTION.

  01 ValidationReturnCode PIC 9.

  88 DateIsOK VALUE 0.

  88 DateIsInvalid VALUE 1 THRU 8.

  88 ValidCodeSupplied VALUE 0 THRU 8.

  01 DateErrorMessage PIC X(35) VALUE SPACES.

  88 DateNotNumeric VALUE "Error - The date must be numeric".

  88 YearIsZero VALUE "Error - The year cannot be zero".

  88 MonthIsZero VALUE "Error - The month cannot be zero".

  88 DayIsZero VALUE "Error - The day cannot be zero".

  88 YearPassed VALUE "Error - Year has already passed".

  88 MonthTooBig VALUE "Error - Month is greater than 12".

  88 DayTooBig VALUE "Error - Day greater than 31".

  88 TooBigForMonth VALUE "Error - Day too big for this month".

  93

  Chapter 5 ■ Control StruCtureS: SeleCtion

  PROCEDURE DIVISION.

  Begin.

  PERFORM ValidateDate UNTIL ValidCodeSupplied

  EVALUATE ValidationReturnCode

  WHEN 0 SET DateIsOK TO TRUE

  WHEN 1 SET DateNotNumeric TO TRUE

  WHEN 2 SET YearIsZero TO TRUE

  WHEN 3 SET MonthIsZero TO TRUE

  WHEN 4 SET DayIsZero TO TRUE

  WHEN 5 SET YearPassed TO TRUE

  WHEN 6 SET MonthTooBig TO TRUE

  WHEN 7 SET DayTooBig TO TRUE

  WHEN 8 SET TooBigForMonth TO TRUE

  END-EVALUATE

  IF DateIsInvalid THEN

  DISPLAY DateErrorMessage

  END-IF

  IF DateIsOK

  DISPLAY "Date is Ok"

  END-IF

  STOP RUN.

  ValidateDate.

  DISPLAY "Enter a validation return code (0-8) " WITH NO ADVANCING

  ACCEPT ValidationReturnCode.

  EVALUATE

  In Listing 5-7, the EVALUATE verb is used to SET a particular condition name depending on the value in the ValidationReturnCode data item. You probably did not have much difficulty working out what the EVALUATE

  statement is doing because it has echoes of how the switch/case statement works in other languages. Ruby

  programmers, with their when-branched case statement, were probably particularly at home. But the resemblance of EVALUATE to the case/switch used in other languages is superficial. EVALUATE is far more powerful than these constructs. Even when restricted to one subject, EVALUATE is more powerful because it is not limited to ordinal types.

  When used with multiple subjects, EVALUATE is a significantly more powerful construct. One common use for the multiple-subject EVALUATE is the implementation of decision-table logic.

  Decision Tables

  A decision table is a way to model complicated logic in a tabular form. Decision tables are often used by systems analysts to express business rules that would be too complicated and/or too confusing to express in a textual form.

  94

  Chapter 5 ■ Control StruCtureS: SeleCtion

  For instance, suppose an amusement park charges different admission fees depending on the age and height of visitors, according to the following rules:

  • If the person is younger than 4 years old, admission is free.

  • If the person is between 4 and 7, admission is $10.

  • If between 8 and 12, admission is $15.

  • If between 13 and 64, admission is $25.

  • If 65 or older, admission is $10.

  • In addition, in view of the height restrictions on many rides, persons shorter than 48 inches

  who are between the ages of 8 and 64 receive a discount. Persons between 8 and 12 are

  charged a $10 admission fee, whereas those between the ages of 13 and 64 are charged $18.

  You can represent this textual specification using the decision table in Table 5-8.

  Table 5-8. Amusement Park Decision Table

  Age

  Height in inches

  Admission

  < 4

  NA

  $0

  4 - 7

  NA

  $10

  8 - 12

  Height >= 48

  $15

  8 - 12

  Height < 48

  $10

  13 - 64

  Height >= 48 inches

  $25

  13 - 64

  Height < 48

  $18

  >= 65

  NA

  $10

  EVALUATE Metalanguage

  The EVALUATE metalanguage (see Figure 5-8) looks very complex but is actually fairly easy to understand. It is, though, somewhat difficult to explain in words, so I mainly use examples to explain how it works.

  95

  Chapter 5 ■ Control StruCtureS: SeleCtion

  Figure 5-8. Metalanguage for the EVALUATE verb

  96

  Chapter 5 ■ Control StruCtureS: SeleCtion

  Notes

  The following are the WHEN branch rules:

  • Only one WHEN branch is chosen per execution of EVALUATE.

  • The order of the WHEN branches is important because checking of the branches is done from

  top to bottom.

  • If any WHEN branch is chosen, the EVALUATE ends. The break required in other languages to

  stop execution of the remaining branches is not required in COBOL.

  • If none of the WHEN branches can be chosen, the WHEN OTHER branch (if it exists) is executed.

  • If none of the WHEN branches can be chosen, and there is no WHEN OTHER phrase, the EVALUATE

  simply terminates.

  The items immediately after the word EVALUATE and before the first WHEN are called subjects. The items between the WHEN and its statement block are called objects.

  The number of subjects must equal the number of objects, and the objects must be compatible with the subjects.

  For instance, if the subject is a condition, then the object must be either TRUE or FALSE. If the subject is a data item, then the object must be either a literal value or a data item.

  Table 5-9 lists the combinations you may have. If there are four subjects, then each WHEN branch must list four objects. If the value of a particular object does not matter, the keyword ANY may be used.

  Table 5-9. EVALUATE Subject/Object Combinations

  Subject 1

  Subject 2

&nbs
p; Subject 3

  Subject 4

  Action

  EVALUATE

  Condition

  ALSO

  True

  ALSO

  Identifier

  ALSO

  Literal

  Statement

  False

  Block

  WHEN

  True

  ALSO

  Condition

  ALSO

  Literal

  ALSO

  Identifier

  Statement

  False

  Block

  WHEN

  ANY

  ALSO

  ANY

  ALSO

  Identifier

  ALSO

  Literal

  Statement

  Block

  WHEN

  OTHER

  Statement

  Block

  END-EVALUATE

  Object 1

  Object 2

  Object 3

  Object 4

  EVALUATE Examples

  This section looks at three examples of the EVALUATE verb.

  Payment Totals Example

  Shoppers choose the method of payment as Visa, MasterCard, American Express, Check, or Cash. A program totals the amount paid by each payment method. After a sale, the sale value is added to the appropriate total. Condition names (ByVisa, ByMasterCard, ByAmericanExpress, ByCheck, ByCash) have been set up for each of the payment

  methods.

  97

  Chapter 5 ■ Control StruCtureS: SeleCtion

  You could code this as follows:

  IF ByVisa ADD SaleValue TO VisaTotal

  ELSE

  IF ByMasterCard ADD SaleValue TO MasterCardTotal

  ELSE

  IF ByAmericanExpress ADD SaleValue TO AmericanExpressTotal

  ELSE

  IF ByCheck ADD SaleValue TO CheckTotal

  ELSE

  IF ByCash ADD SaleValue TO CashTotal

  END-IF

  END-IF

  END-IF

  END-IF

  END-IF

  You can replace these nested IF statements with the neater and easier-to-understand EVALUATE statement:

  EVALUATE TRUE

  WHEN ByVisa ADD SaleValue TO VisaTotal

  WHEN ByMasterCard ADD SaleValue TO MasterCardTotal

  WHEN ByAmericanExpress ADD SaleValue TO AmericanExpressTotal

  WHEN ByCheck ADD SaleValue TO CheckTotal

  WHEN ByCash ADD SaleValue TO CashTotal

  END-EVALUATE

  In this example, the objects must all be either conditions or condition names, because the subject is TRUE.

  Amusement Park Example

  EVALUATE can be used to encode a decision table. Listing 5-8 shows how the Amusement Park decision table from Table 5-8 might be encoded.

  Listing 5-8. Amusement Park Admission

  IDENTIFICATION DIVISION.

  PROGRAM-ID. Listing5-8.

  DATA DIVISION.

  WORKING-STORAGE SECTION.

  01 Age PIC 99 VALUE ZERO.

  88 Infant VALUE 0 THRU 3.

  88 YoungChild VALUE 4 THRU 7.

  88 Child VALUE 8 THRU 12.

  88 Visitor VALUE 13 THRU 64.

  88 Pensioner VALUE 65 THRU 99.

  98

  Chapter 5 ■ Control StruCtureS: SeleCtion

  01 Height PIC 999 VALUE ZERO.

  01 Admission PIC $99.99.

  PROCEDURE DIVISION.

  Begin.

  DISPLAY "Enter age :- " WITH NO ADVANCING

  ACCEPT Age

  DISPLAY "Enter height :- " WITH NO ADVANCING

  ACCEPT Height

  EVALUATE TRUE ALSO TRUE

  WHEN Infant ALSO ANY MOVE 0 TO Admission

  WHEN YoungChild ALSO ANY MOVE 10 TO Admission

  WHEN Child ALSO Height >= 48 MOVE 15 TO Admission

  WHEN Child ALSO Height < 48 MOVE 10 TO Admission

  WHEN Visitor ALSO Height >= 48 MOVE 25 TO Admission

  WHEN Visitor ALSO Height < 48 MOVE 18 TO Admission

  WHEN Pensioner ALSO ANY MOVE 10 TO Admission

  END-EVALUATE

  DISPLAY "Admission charged is " Admission

  STOP RUN.

  Acme Book Club Example

  The Acme Book Club is the largest online book club in the world. The book club sells books to both members and non-members all over the world. For each order, Acme applies a percentage discount based on the quantity of books in the current order, the value of books purchased in the last three months (last quarter), and whether the customer is a member of the Book Club.

  Acme uses the decision table in Table 5-10 to decide what discount to apply. Listing 5-9 is a small test program that uses EVALUATE to implement the decision table.

  99

  Chapter 5 ■ Control StruCtureS: SeleCtion

  Table 5-10. Acme Book Club Discount Decision Table

  QtyOfBooks

  QuarterlyPurchases (QP)

  ClubMember

  % Discount

  1–5

  < 500

  ANY

  0

  1–5

  < 2000

  Y

  7

  1–5

  < 2000

  N

  5

  1–5

  >= 2000

  Y

  10

  1–5

  >= 2000

  N

  8

  6–20

  < 500

  Y

  3

  6–20

  < 500

  N

  2

  6–20

  < 2000

  Y

  12

  6–20

  < 2000

  N

  10

  6–20

  >= 2000

  Y

  25

  6–20

  >= 2000

  N

  15

  21–99

  < 500

  Y

  5

  21–99

  < 500

  N

  3

  21–99

  < 2000

  Y

  16

  21–99

  < 2000

  N

  15

  21–99

  >= 2000

  Y

  30

  21–99

  >= 2000

  N

  20

  Listing 5-9. Acme Book Club Example

  IDENTIFICATION DIVISION.

  PROGRAM-ID. Listing5-9.

  AUTHOR. Michael Coughlan.

  DATA DIVISION.

  WORKING-STORAGE SECTION.

  01 Member PIC X VALUE SPACE.

  01 QP PIC 9(5) VALUE ZEROS.

  *> QuarterlyPurchases

  01 Qty PIC 99 VALUE ZEROS.

  01 Discount PIC 99 VALUE ZEROS.

  PROCEDURE DIVISION.

  Begin.

  DISPLAY "Enter value of QuarterlyPurchases - " WITH NO ADVANCING

  ACCEPT QP

  DISPLAY "Enter qty of books purchased - " WITH NO ADVANCING

  ACCEPT Qty

  100

  Chapter 5 ■ Control StruCtureS: SeleCtion

  DISPLAY "club member enter Y or N - " WITH NO ADVANCING

  ACCEPT Member

  EVALUATE Qty ALSO TRUE ALSO Member

  WHEN 1 THRU 5 ALSO QP < 500 ALSO ANY MOVE 0 TO Discount

  WHEN 1 THRU 5 ALSO QP < 2000 ALSO "Y" MOVE 7 TO Discount

  WHEN 1 THRU 5 ALSO QP < 2000 ALSO "N" MOVE 5 TO Discount

  WHEN 1 THRU 5 ALSO QP >= 2000 ALSO "Y" MOVE 10 TO Discount

  WHEN 1 THRU 5 ALSO QP >= 2000 ALSO "N" MOVE 8 TO Discount

  WHEN 6 THRU 20 ALSO QP < 500 ALSO "Y" MOVE 3 TO Discount

  WHEN 6 THRU 20 ALSO QP < 500 ALSO "N" MOVE 2 TO Discount

  WHEN 6 THRU 20 ALSO QP < 2000 ALSO "Y" MOVE 12 TO Discount

  WHEN 6 THRU 20 ALSO QP < 2000 ALSO "N" MOVE 10 TO Discount<
br />
  WHEN 6 THRU 20 ALSO QP >= 2000 ALSO "Y" MOVE 25 TO Discount

  WHEN 6 THRU 20 ALSO QP >= 2000 ALSO "N" MOVE 15 TO Discount

  WHEN 21 THRU 99 ALSO QP < 500 ALSO "Y" MOVE 5 TO Discount

  WHEN 21 THRU 99 ALSO QP < 500 ALSO "N" MOVE 3 TO Discount

  WHEN 21 THRU 99 ALSO QP < 2000 ALSO "Y" MOVE 16 TO Discount

  WHEN 21 THRU 99 ALSO QP < 2000 ALSO "N" MOVE 15 TO Discount

  WHEN 21 THRU 99 ALSO QP >= 2000 ALSO "Y" MOVE 30 TO Discount

  WHEN 21 THRU 99 ALSO QP >= 2000 ALSO "N" MOVE 20 TO Discount

  END-EVALUATE

  DISPLAY "Discount = " Discount "%"

  STOP RUN.

  Summary

  The three classic constructs of structured programming are sequence, selection, and iteration. You have already noted that a COBOL program starts execution with the first statement in the PROCEDURE DIVISION and then continues to execute the statements one after another in sequence until the STOP RUN or the end-of-the-program text is encountered, unless some other statement changes the order of execution. In this chapter, you examined the IF

  and EVALUATE statements. These statements allow a program to selectively execute program statements. In the next chapter, you discover how iteration, the final classic construct, is implemented in COBOL.

  References

  1. Tompkins HE. In defense of teaching structured COBOL as computer science (or, notes on

  being sage struck). ACM SIGPLAN Notices. 1983; 18(4): 86-94.

  2. Baldwin RR. A note on H.E. Tompkins’s minimum-period COBOL style. ACM SIGPLAN

  Notices. 1987; 22(5): 27-31. http://doi.acm.org/10.1145/25267.25273

  doi: 10.1145/25267.25273

  101

  Chapter 5 ■ Control StruCtureS: SeleCtion

  LaNGUaGe KNOWLeDGe eXerCISeS

  Getting out your 2B pencil once more, write answers to the following questions.

  1. For each of the following condition names, which do you consider to be inappropriately

  named? Suggest more suitable names for these only.

  01 Country-Code PIC XX.

  88 Code-Is-US VALUE "US".

  ____________________________________________________________

  01 Operating-System PIC X(15).

  88 Windows-Or-UNIX VALUE "WINDOWS".

  ____________________________________________________________

  01 Room-Type PIC X(20).

  88 Double-Room VALUE "DOUBLE".

 

‹ Prev