CHAPTER 4

image

Procedure Division Basics

The three preceding chapters covered much of the background material you need before you can write useful programs. Chapter 1 was motivational, Chapter 2 dealt with the structure of COBOL programs, and in Chapter 3 you learned how to define the data storage that dynamic programs require to be useful.

The PROCEDURE DIVISION contains the code used to manipulate data described in the DATA DIVISION. This chapter examines some of the basic PROCEDURE DIVISION commands. You learn how to get data from the user, how to use the COBOL arithmetic verbs to do calculations on the data, and how to display the results on the computer screen.

Input and Output with ACCEPT and DISPLAY

In COBOL, the ACCEPT and DISPLAY verbs are used to read from the keyboard and write to the screen. Input and output using these commands is somewhat primitive. The original purpose of these commands was not to communicate with the end user but for use in a batch-programming environment, to allow interaction with the computer operators. Because computer operators are expert users and the level of their interaction with the program was limited to viewing alerts and action prompts or entering the occasional file name, no great sophistication was required in the ACCEPT and DISPLAY commands.

In recent years, however, many implementers have found a need for more powerful versions of ACCEPT and DISPLAY in order to allow online systems to be created. These implementers have augmented the ACCEPT and DISPLAY syntax to allow such things as cursor positioning, character attribute control, and auto-validation of input. In some cases, they have even implemented a special SCREEN SECTION in the DATA DIVISION.

In a real environment, console-based (as opposed to Windows-based) input and output operations would be handled either by implementer-enhanced versions of ACCEPT and DISPLAY or by calls to forms-management or transaction-processing software such as Terminal Data Management System (TDMS), DECforms, and Customer Information Control System (CICS).

This book considers only the standard ACCEPT and DISPLAY syntax. If the vendor of your version of COBOL offers extended ACCEPT and DISPLAY syntax, you should read the manual to discover how these extensions work.

The DISPLAY Verb

The DISPLAY verb is used to send output to the computer screen or to a peripheral device. A single DISPLAY can be used to display several data items or literals or any combination of these. The concatenation required by some other languages is not required for the DISPLAY verb.

Metalanguage diagrams are used to describe the syntax of COBOL verbs and other elements. The metalanguage for the DISPLAY verb is given in Figure 4-1. In case you have forgotten how to interpret these diagrams, see “Metalanguage Reminder” for a brief refresher on the meaning of the symbols.

9781430262534_Fig04-01.jpg

Figure 4-1. Metalanguage for the DISPLAY verb

METALANGUAGE REMINDER

In the COBOL syntax diagrams (the COBOL metalanguage), uppercase words are keywords. If underlined, they are mandatory. In addition

  • { } brackets mean one of the options must be selected.
  • [ ] brackets mean the item is optional.
  • An ellipsis (...) means the item may be repeated at the programmer’s discretion.

The symbols used in the syntax diagram identifiers have the following significance:

  • $ indicates a string (alphanumeric) item.
  • # indicates a numeric item.
  • i indicates that the item can be a variable identifier.
  • l indicates that the item can be a literal.

Notes

As the ellipsis (...) in the metalanguage shows, a single DISPLAY can be used to display several data items or literals or any combination of these. The items displayed must be USAGE DISPLAY items. USAGE COMP or INDEX will not display correctly. USAGE IS DISPLAY is the default for COBOL data items; it means the data is held in a displayable format. For efficiency purposes, it is also possible to hold data in a binary format that is not displayable. The USAGE clause, which you examine later in the book, is used when you want to hold a data item in one of the more computationally efficient binary formats. For instance:

01 SaleValue       PIC 9(5)V99 USAGE IS COMP.
01 TableSubscript   USAGE IS INDEX.

The default display device is the computer screen, but you can use other devices for output by specifying a mnemonic-name with the UPON clause. Mnemonic-names are used to make programs more readable and more maintainable; they are devised by programmers to represent peripheral devices (such as serial ports). A name is connected to an actual device by an entry in the SPECIAL-NAMES paragraph of the CONFIGURATION SECTION in the ENVIRONMENT DIVISION. The actual device to which the mnemonic-name is connected is defined by the language implementer. Consult your COBOL manual to learn what devices your implementer supports.

Ordinarily, after data is displayed on the computer screen, the onscreen cursor moves to the next row. Sometimes, however, you want the cursor to remain on the same row. In these cases, you can use the WITH NO ADVANCING clause to ensure that the cursor does not move to the next row.

DISPLAY Examples

This section gives some illustrative DISPLAY examples. The DISPLAY in eg1 sends the data in PrinterSetupCodes to the device represented by the mnemonic-name PrinterPort1. The output from the remaining examples is shown in the Display Results diagram. Note that in eg4, the separator spaces inserted between the statement operands have no effect on the output. In a COBOL statement, you can insert separator commas, spaces or semicolons wherever you want to make a statement more readable. Also note that in eg5, the figurative constants SPACE and SPACES are synonyms; they both insert only a single space. Note too that no concatenation operator is required to bind the data items and figurative constants into a single string

eg1.  DISPLAY PrinterSetupCodes UPON PrinterPort1
 
eg2.  MOVE 3456 TO FinalTotal
      DISPLAY "The final total is " FinalTotal
 
eg3.  DISPLAY "One, "   WITH NO ADVANCING
      DISPLAY "two, "   WITH NO ADVANCING
      DISPLAY "three."
 
eg4.  DISPLAY 1 ","   2    "," 3 "."
 
eg5.  MOVE 10 TO DayOfBirth
      MOVE 12 TO MonthOfBirth
      MOVE 1975 TO YearOfBirth
      DISPLAY "Date of birth is - "
          DayOfBirth SPACES  MonthOfBirth SPACE YearOfBirth

9781430262534_unFig04-01.jpg

The ACCEPT Verb

There are two formats for the ACCEPT verb:

  • The first gets data from the keyboard or a peripheral device.
  • The second lets you access the system date and time (that is, the date and time held in the computer’s internal clock) by using certain system variables.

The metalanguage for the two formats of the ACCEPT are shown in Figure 4-2.

9781430262534_Fig04-02.jpg

Figure 4-2. Metalanguage for the ACCEPT verb

Rules

When you use the first format, ACCEPT inserts the data typed on the keyboard into the receiving data item. If the FROM option is used, the data inserted into the receiving data item comes from the device indicated by the mnemonic-name. Data is sent to the ReceivingItem according to the rules for alphanumeric moves. If the ReceivingItem is too small to hold the data, the rightmost characters that do not fit are lost. If the ReceivingItem is too large, there is space-filling on the right.

The default input device is the computer keyboard, but you can use other devices by specifying a mnemonic-name with the FROM clause. The mnemonic-name is connected to the actual device by an entry in the SPECIAL-NAMES paragraph, CONFIGURATION SECTION, ENVIRONMENT DIVISION.

When you use the second format, ACCEPT moves the data from one of the system variables (DATE, DAY, DAY-OF-WEEK, TIME) into the receiving data item. Two of the system variables also have optional syntactic elements that allow you to specify that the date be supplied with a four-digit year.

Required Format for System Variables

The declarations and comments that follow show the format required for the data items that ACCEPT values from each of the system variables:

01 CurrentDate        PIC 9(6).
* Receiving data item for DATE system variable: Format is YYMMDD
  
01 DayOfYear          PIC 9(5).
* Receiving data item for DAY system variable: Format is YYDDD
 
01 Day0fWeek          PIC 9.
* Receiving item for DAY-OF-WEEK: Format is D (1=Monday)
 
01 CurrentTime        PIC 9(8).
* Receiving item for TIME: Format is HHMMSSss   s = S/100
 
01 Y2KDate            PIC 9(8).
* Receiving item for DATE YYYYMMDD system variable: Format is YYYYMMDD
 
01 Y2KDayOfYear       PIC 9(7).
* Receiving item for DAY YYYYDDD system variable: Format is YYYYDDD

Example Program: ACCEPT and DISPLAY

Listing 4-1 gives some examples of how to use the ACCEPT and DISPLAY verbs. The examples use both formats of ACCEPT. The first form of ACCEPT is combined with DISPLAY to prompt for and receive a username. The second form gets data from some of the date and time system variables. Finally, all the gathered information is displayed on the computer screen. The results of running the program are shown in the results diagram.

Listing 4-1. ACCEPT and DISPLAY Examples

IDENTIFICATION DIVISION.
PROGRAM-ID.  Listing4-1.
AUTHOR.  Michael Coughlan.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  UserName           PIC X(20).
 
*> Receiving data item for DATE system variable: Format is YYMMDD
01 CurrentDate.
   02  CurrentYear     PIC 99.
   02  CurrentMonth    PIC 99.
   02  CurrentDay      PIC 99.
 
*> Receiving data item for DAY system variable: Format is YYDDD
01 DayOfYear.
   02  FILLER          PIC 99.
   02  YearDay         PIC 9(3).
 
*> Receiving item for TIME: Format is HHMMSSss   s = S/100
01 CurrentTime.
   02  CurrentHour     PIC 99.
   02  CurrentMinute   PIC 99.
   02  FILLER          PIC 9(4).
 
*> Receiving item for DATE YYYYMMDD system variable: Format is YYYYMMDD
01 Y2KDate.
   02 Y2KYear          PIC 9(4).
   02 Y2KMonth         PIC 99.
   02 Y2KDay           PIC 99.
    
*> Receiving item for DAY YYYYDDD system variable: Format is YYYYDDD
01 Y2KDayOfYear.
   02 Y2KDOY-Year      PIC 9(4).
   02 Y2KDOY-Day       PIC 999.
PROCEDURE DIVISION.
Begin.
    DISPLAY "Please enter your name - " WITH NO ADVANCING
    ACCEPT  UserName
    DISPLAY "**********************"
    ACCEPT CurrentDate  FROM DATE
    ACCEPT DayOfYear    FROM DAY
    ACCEPT CurrentTime  FROM TIME
    ACCEPT Y2KDate      FROM DATE YYYYMMDD
    ACCEPT Y2KDayOfYear FROM DAY YYYYDDD
    DISPLAY "Name is " UserName
    DISPLAY "Date is " CurrentDay "-"  CurrentMonth "-" CurrentYear
    DISPLAY "Today is day " YearDay " of the year"
    DISPLAY "The time is " CurrentHour ":" CurrentMinute
    DISPLAY "Y2KDate is " Y2kDay SPACE Y2KMonth SPACE Y2KYear
    DISPLAY "Y2K Day of Year is " Y2KDoy-Day " of " Y2KDOY-Year
    STOP RUN.

9781430262534_unFig04-02.jpg

image Note  The example programs in this book were compiled by using Micro Focus Visual COBOL and capturing the ­output results. In most cases, the programs were also compiled and run using the web-based open source COBOL ­compiler at www.compileonline.com/compile_cobol_online.php. If you want to use this compiler, be aware that ­interactivity is limited and you must enter keyboard input via the site’s STDIN Input box. Some tweaking may be required.

Arithmetic in COBOL

Most procedural programming languages perform computations by assigning the result of an arithmetic expression (or function) to a variable. In COBOL, the COMPUTE verb is used to evaluate arithmetic expressions, but there are also specific commands for adding (ADD), subtracting (SUBTRACT), multiplying (MULTIPLY), and dividing (DIVIDE).

Common Arithmetic Template

With the exception of COMPUTE, DIVIDE with REMAINDER, and some exotic formats of ADD and SUBTRACT, most COBOL arithmetic verbs conform to the template metalanguage shown in Figure 4-3. It is useful to review this metalanguage template because it allows me to discuss the clauses and issues that apply to all the arithmetic verbs.

9781430262534_Fig04-03.jpg

Figure 4-3. Metalanguage for a common arithmetic template

Arithmetic Template Notes

All the arithmetic verbs move the result of a calculation into a receiving data item according to the rules for a numeric move: that is, with alignment along the assumed decimal point and with zero-filling or truncation as necessary. In all the arithmetic verbs except COMPUTE, the result of the calculation is assigned to the rightmost data item(s).

All arithmetic verbs must use numeric literals or numeric data items (PIC 9) that contain numeric data. There is one exception: data items that receive the result of the calculation but are not themselves one of the operands (do not contribute to the result) may be numeric or edited numeric.

Where the GIVING phrase is used, the item to the right of the word giving receives the result of the calculation but does not contribute to it. Where there is more than one item after the word giving, each receives the result of the calculation.

Where the GIVING phrase is not used and there is more than one OperandResult#i, Operand#il is applied to each OperandResult#i in turn, and the result of each calculation is placed in each OperandResult#i.

The maximum size of each operand is 18 digits (31 in ISO 2002 COBOL).

Examples of COBOL Arithmetic Statements

Here are a number of examples, each followed by an explanation of the operation:

ADD Takings TO CashTotal
* Adds the value in Takings to the value in CashTotal and puts the result in CashTotal
 
ADD Males TO Females GIVING TotalStudents
* Adds the value in Males to the value in Females and overwrites
* the value in TotalStudents with the result.
 
ADD Sales TO ShopSales, CountySales, CountrySales
* Adds the value of Sales to ShopSales and puts the result in ShopSales.
* Adds the value of Sales to CountySales and puts the result in CountySales
* Adds the value of Sales to CountrySales and puts the result in CountrySales
 
SUBTRACT Tax FROM GrossPay
* Subtracts the value in Tax from the value in GrossPay and puts the result in GrossPay.
 
SUBTRACT Tax FROM GrossPay GIVING NetPay
* Subtracts the value in Tax from the value in GrossPay and puts the result in NetPay.
 
DIVIDE Total BY Members GIVING MemberAverage ROUNDED
* Divides the value in Total by the value in Members and puts
* the rounded result in MemberAverage.
 
DIVIDE Members INTO Total GIVING MemberAverage
* Divides the value in Members into the value in Total and puts the result in MemberAverage.
 
MULTIPLY 10 BY Magnitude
* Multiplies 10 by the value in Magnitude and puts the result in Magnitude.
 
MULTIPLY Members BY Subs GIVING TotalSubs
* Multiplies the value of Members by the value of Subs and puts the result in TotalSubs.

Note that when separating contiguous operands, you may insert commas for clarity. They have no semantic effect, as you will see if you use the following example:

DISPLAY "Date of birth = " DayOB, SPACE, MonthOB, SPACE, YearOB
ADD Sales TO ShopSales, CountySales, CountrySales

The ROUNDED Phrase

If you use the ROUNDED phrase, then, after decimal point alignment, if the result of the calculation must be truncated on the right side (least significant digits) and the leftmost truncated digit has an absolute value of five or greater, the rightmost digit is increased by one when rounded. That sounds complicated, but it isn’t. Let’s look at some examples, as shown in Table 4-1.

Table 4-1. ROUNDED Examples. Digits in the Actual Result column that will be truncated are not in bold

image

The ON SIZE ERROR

A size error occurs when the computed result is too large or too small to fit into the receiving field. When the ON SIZE ERROR phrase is used, it is followed by a block of COBOL statements that usually alert you that an error condition has occurred. For instance, in the following example, if FinalResult is too small to hold the result of all these multiplications, the ON SIZE ERROR activates and the alert message is displayed:

COMPUTE FinalResult = Num1 * Num2 * Num3 * Num4
    ON SIZE ERROR DISPLAY "Alert: FinalResult too small to hold result"
END-COMPUTE

The scope of the statement block is delimited by the appropriate END delimiter (END-ADD, END-SUBTRACT, END-MULTIPLY, END-DIVIDE, END-COMPUTE).

The ON SIZE ERROR acts like a specialized exception handler that comes into play if there is division by zero or if unexpected truncation occurs. When a computation is performed and decimal point alignment has occurred between the calculated result and the receiving data item, the result may be truncated on either the left side or the right. If the most significant digits are truncated, the size error activates. If there is truncation of the least significant digits, size error activation depends on whether the ROUNDED phrase is specified. If it is, then truncation of the least significant digits is ignored because using the ROUNDED phrase indicates that you know there will be truncation and have specified rounding to deal with it. Table 4-2 gives some ON SIZE ERROR examples.

Table 4-2. ON SIZE ERROR Examples. Digits in the Actual Result column that will be truncated are not in bold

image

Nonconforming Arithmetic Verbs

When the common arithmetic verb template was introduced, I mentioned that there are forms of some verbs that do not conform to the template. This section gives the full metalanguage for COMPUTE, ADD, SUBTRACT, MULTIPLY, and DIVIDE and discusses in more detail the versions of these verbs that do not conform to the template.

The COMPUTE Verb

COMPUTE assigns the result of an arithmetic expression to a data item. The arithmetic expression to the right of the equal sign is evaluated, and the result is assigned to the data item(s) on the left of the equal sign. The arithmetic expression is evaluated according to the normal arithmetic rules. That is, the expression is normally evaluated from left to right, but bracketing and precedence rules (see Table 4-3) can change the order of evaluation.

Table 4-3. Precedence Rules

Precedence

Symbol

Meaning

1

**

Power

2

*

Multiply

/

Divide

3

+

Add

-

Subtract

image Note  Unlike some other programming languages, COBOL provides the ** expression symbol to represent raising to a power.

COMPUTE is the COBOL verb most similar to assignment in other programming languages. For that reason, you may be tempted to use it for plain assignments of data items to data items. COMPUTE should never be used for that purpose; in COBOL, you have the MOVE verb for that.

The familiarity of COMPUTE may also cause you to use it in preference to the other arithmetic verbs. There is no major objection to doing so, but knowledge of the other arithmetic verbs is required if you will be working with legacy systems.

Figure 4-4 shows the metalanguage for the COMPUTE verb.

9781430262534_Fig04-04.jpg

Figure 4-4. COMPUTE metalanguage

COMPUTE Examples

Each example in this section is followed by a diagram that shows the value of the data items before and after COMPUTE executes.

Let’s start with some literal values:

COMPUTE Result = 90 - 7 * 3 + 50 / 2
 
01 Result PIC 9(4) VALUE 3333.

image

This is equivalent to

COMPUTE Result = 90 - (7 * 3) + (50 / 2)
 
01 Result PIC 9(4) VALUE 3333.

image

Here’s another example:

COMPUTE Euro ROUNDED = Dollar / ExchangeRate
01 Euro         PIC 9(5)V99 VALUE 3425.15.
01 Dollar       PIC 9(5)V99 VALUE 1234.75.
01 ExchangeRate PIC 9V9(4)  VALUE 1.3017.

image

The ADD Verb

The ADD verb is used for addition. You might think COMPUTE could be used for that, and of course it can, but sometimes it can be simpler to use ADD. For instance, to increment a counter, you need COMPUTE ItemCount = ItemCount + 1, whereas you could just use ADD 1 TO ItemCount.

The metalanguage for the ADD verb is given in Figure 4-5.

9781430262534_Fig04-05.jpg

Figure 4-5. ADD verb metalanguage

Notes

The ADD verb mostly conforms to the common template, but note the ellipsis after the first operand. This means you could have a statement like

ADD Num1, Num2, Num3 TO Num4 GIVING Result.

What are the semantics of this version of ADD? The items before TO are all added together, and then the result is applied to the operand or operands after TO.

Note also that in the GIVING version of the ADD verb, the word TO is optional (square brackets). This means you could have a statement like

ADD Num1, Num2, Num3 GIVING Result.

In this version, all the operands before GIVING are added together, and the result is placed in the Result data item.

ADD Examples

Each example in this section is followed by a figure that shows the value of the data items before and after ADD executes:

ADD Cash TO Total.
01 Cash  PIC 9(3) VALUE 364.
01 Total PIC 9(4) VALUE 1000.

image

ADD Cash, 20 TO Total.
01 Cash  PIC 9(3) VALUE 364.
01 Total PIC 9(4) VALUE 1000.

image

ADD Cash, Checks TO Total.
01 Cash  PIC 9(3) VALUE 364.
01 Total PIC 9(4) VALUE 1000.
01 Checks PIC (4) VALUE 1445.

image

The SUBTRACT Verb

The SUBTRACT verb is a specialized verb used for subtraction. It can be more convenient to use SUBTRACT to decrement a counter rather than COMPUTE. For instance, to decrement a counter you need COMPUTE ItemCount = ItemCount – 1, whereas you could just use SUBTRACT 1 FROM ItemCount.

The metalanguage for the SUBTRACT verb is given in Figure 4-6.

9781430262534_Fig04-06.jpg

Figure 4-6. Metalanguage for the SUBTRACT verb

Notes

The SUBTRACT verb mostly conforms to the common template, but just as with ADD, there is an ellipsis after the first operand. This means you could have statements like these:

SUBTRACT Num1, Num2 FROM Num3 GIVING Result.
SUBTRACT Num1, Num2 FROM NumResult1, NumResult2.

In the first example, all the items before the word FROM are added together, the combined result is subtracted from num3, and the result is placed in the Result data item.

In the second example, all the items before the word FROM are added together. The combined result is subtracted from NumResult1, and the result is placed in NumResult1. The combined result is also subtracted from NumResult2, and the result of that calculation is placed in NumResult2.

SUBTRACT Examples

Here are some examples of SUBTRACT:

SUBTRACT Num1, Num2 FROM Num3 GIVING Result.
01 Num1    PIC 9(4) VALUE 364.
01 Num2    PIC 9(4) VALUE 1000.
01 Num3    PIC 9(4) VALUE 5555.
01 Result  PIC 9(4) VALUE 1445.

image

SUBTRACT Num1, Num2 FROM NumResult1, NumResult2.
01 Num1       PIC 9(4) VALUE 364.
01 Num2       PIC 9(4) VALUE 1000.
01 NumResult1 PIC 9(4) VALUE 5555.
01 NumResult2 PIC 9(4) VALUE 1445.

image

SUBTRACT Tax, PRSI, Pension, Levy FROM GrossPay GIVING NetPay.
01 GrossPay PIC 9(4)V99 VALUE 6350.75.
01 Tax      PIC 9(4)V99 VALUE 2333.25.
01 PRSI     PIC 9(4)V99 VALUE 1085.45.
01 Pension  PIC 9(4)V99 VALUE 1135.74.
01 Levy     PIC 9(3)V99 VALUE 170.50.
01 NetPay   PIC 9(4)V99 VALUE ZEROS.

image

The MULTIPLY Verb

The MULTIPLY verb is one of the arithmetic verbs that fully conforms to the common template given in Figure 4-3. The metalanguage for the MULTIPLY verb is given in Figure 4-7.

9781430262534_Fig04-07.jpg

Figure 4-7. Metalanguage for the MULTIPLY verb

MULTIPLY Examples

Here are some examples of MULTIPLY:

Multiply Fees BY Members GIVING TotalFees
   DISPLAY "Alert: result to large for TotalFees"
01 Fees       PIC 9(3)V99 VALUE 052.24
01 Members    PIC 9(4)    VALUE 1024.
01 TotalFees  PIC 9(5)V99 VALUE ZEROS.

image

The DIVIDE Verb

The DIVIDE verb has two main formats. The metalanguage for the first format is given in Figure 4-8. This format is unremarkable in that it conforms to the common template. The metalanguage for the second format is given in Figure 4-9. This format does not conform to the common template, and it provides operations that cannot be done with COMPUTE. The second format of DIVIDE allows you to get the quotient and the remainder in one operation.

9781430262534_Fig04-08.jpg

Figure 4-8. Metalanguage for format 1 of the DIVIDE verb

9781430262534_Fig04-09.jpg

Figure 4-9. Metalanguage for format 2 of the DIVIDE verb

DIVIDE Examples

Following are some DIVIDE examples; the third example uses the second format.

In this example, 15 is divided into Amount1, and the result is placed in Amount1; 15 is also divided into Amount2, and result is placed in Amount2. The results calculated are not integer values, so there is truncation of the digits to the left of the decimal point:

DIVIDE 15 INTO Amount1, Amount2.
01 Amount1    PIC 9(4) VALUE 2444.
01 Amount2    PIC 9(3) VALUE 354.

image

In this example, the calculated result is not an integer value, so there is truncation of the digits to the left of the decimal point. But because rounding is requested, the result is rounded to 272 (from 271.7826086956522):

DIVIDE Qty By Units GIVING Average ROUNDED.
01 Qty      PIC 9(5)  VALUE 31255.
01 Units    PIC 9(3)  VALUE 115.
01 Average  PIC 9(4)  VALUE ZEROS.

image

This example uses the second format of DIVIDE. It shows how you can use DIVIDE to get both the quotient and the remainder in one operation:

DIVIDE 215 BY 10 GIVING Quotient REMAINDER Rem.
01 Quotient PIC 999  VALUE ZEROS.
01 Rem      PIC 9    VALUE ZEROS.

image

Let’s Write a Program

Listing 4-2 presents a very simple program that takes two single-digit numbers from the keyboard, multiplies them together, and then displays the result. This program uses only one of the three classic constructs of structured programming. These constructs are

  • Sequence
  • Selection
  • Iteration

In this program, execution starts in the PROCEDURE DIVISION paragraph CalculateResult and then continues through the program statements one by one, in sequence, until STOP RUN is reached.

Obviously, a program like this has limited usefulness. To make it really useful, you need to be able to selectively execute program statements (selection) and specify that others are to be executed over and over again (iteration). You revisit this program in the next two chapters when you are armed with the necessary selection and iteration constructs.

Listing 4-2. Example Program: ACCEPT, DISPLAY, and MULTIPLY

IDENTIFICATION DIVISION.
PROGRAM-ID.  Listing4-2.
AUTHOR.  Michael Coughlan.
*> Accepts two numbers from the user, multiplies them together
*> and then displays the result.

DATA DIVISION.
WORKING-STORAGE SECTION.
01  Num1         PIC 9  VALUE 5.
01  Num2         PIC 9  VALUE 4.
01  Result       PIC 99 VALUE ZEROS.

PROCEDURE DIVISION.
CalculateResult.
    DISPLAY "Enter a single digit number - " WITH NO ADVANCING
    ACCEPT Num1
    DISPLAY "Enter a single digit number - " WITH NO ADVANCING
    ACCEPT Num2
    MULTIPLY Num1 BY Num2 GIVING Result
    DISPLAY "Result is = ", Result
    STOP RUN.

Summary

In this chapter, you examined the operation of the arithmetic verbs COMPUTE, ADD, SUBTRACT, MULTIPLY, and DIVIDE. The ACCEPT and DISPLAY verbs, which allow you to get input from the keyboard and send output to the screen, were also explored.

The final example program consisted of a sequence of statements that are executed one after another. This kind of program is of limited usefulness. To be truly useful, a program must incorporate iteration and selection. These control structures are explored in the next chapter, along with the jewel in COBOL’s crown: condition names.

LANGUAGE KNOWLEDGE EXERCISES

Sharpen up the 2B pencil you used to answer the questions in the last chapter, and fill in the after positions for data items that have a before entry:

01 Num1   PIC 99.
01 Num2   PIC 99.
01 Num3   PIC 99.
01 Num4   PIC 99.

image

LANGUAGE KNOWLEDGE EXERCISES - ANSWERS

Sharpen up the 2B pencil you used to answer the questions in the last chapter, and fill in the after positions for data items that have a before entry:

01 Num1   PIC 99.
01 Num2   PIC 99.
01 Num3   PIC 99.
01 Num4   PIC 99.

image

..................Content has been hidden....................

You can't read the all page of ebook, please click here login for view all page.
Reset
3.147.242.204