Chapter 7. COMPUTING IN COBOL: THE ARITHMETIC VERBS

CHAPTER OBJECTIVES

Upon completion of this chapter, you should be able to

  • Demonstrate the various formats of the ADD, SUBTRACT, MULTIPLY, and DIVIDE operations.

  • Demonstrate the various options that are available with the arithmetic operations.

  • Demonstrate the use of scope terminators.

  • Demonstrate the use of the COMPUTE statement.

  • Demonstrate the use of the INITIALIZE statement.

  • Demonstrate the use of the LIKE clause.

THE FOUR BASIC ARITHMETIC OPERATIONS

All the basic arithmetic operations, ADD, SUBTRACT, MULTIPLY, and DIVIDE, require that the fields operated on (1) have numeric PICTURE clauses and (2) actually have numeric data when the program is executed. Keep in mind that the data-fields specified in any arithmetic statement must be defined in the DATA DIVISION, either in an input or output area of the FILE SECTION, or in the WORKING-STORAGE SECTION. Let us consider each of these arithmetic operations.

ADD STATEMENT

A simple ADD statement has the following instruction formats.

Instruction Format 1 (ADD . . . TO)

Examples:

ADD STATEMENT

Instruction Format 2 (ADD . . . GIVING)

Examples:

ADD STATEMENT

Instruction Format 3 (ADD..TO..GIVING)

Examples:

ADD STATEMENT

Let us review some rules for interpreting instruction formats that will help in evaluating the instruction formats of the ADD statement just specified.

FIELDS USED IN AN ADD

The specified fields or operands of an ADD operation must be numeric. Thus, in the examples above, all literals are numeric, and all data-fields or identifiers defined in the DATA DIVISION have numeric PICTURE clauses.

The result, or sum, of an ADD operation is always placed in the last field mentioned. The only field that is altered as a result of the ADD operation is this last field, which is the one directly following the word TO, when using Format 1, or GIVING, when using Format 2 or Format 3. Thus, in ADD CUSTOMER-PURCHASE TO NEW-BALANCE, the sum of CUSTOMER-PURCHASE and NEW-BALANCE is placed in the NEW-BALANCE field. CUSTOMER-PURCHASE remains unchanged.

In all cases, the resultant field must be a data-field, not a literal. The statement ADD HOURS-WORKED TO 40, for example, is incorrect because 40, which immediately follows the word TO, would be the resultant field, and resultant fields may not be literals.

USING FORMAT 1 OF THE ADD STATEMENT

When using the TO format in an ADD statement, all the data-fields and literals are added together, and the result is placed in the last field specified.

ADD HOURS-WORKED TO WEEKLY-HOURS.

The field HOURS-WORKED is added to WEEKLY-HOURS. Thus, WEEKLY-HOURS contains a new value; HOURS-WORKED remains unchanged.

Suppose we wish to count the number of input records contained within an inventory file and store that number in a counter field. The following program excerpt could be used:

USING FORMAT 1 OF THE ADD STATEMENT

WS-COUNTER could be a field defined in WORKING-STORAGE. It is incremented by one each time a record is read; hence, after all records have been read, it contains a sum equal to the total number of records read as input. One method of defining WS-COUNTER is to define it as part of WS-WORK-AREAS in WORKING-STORAGE:

USING FORMAT 1 OF THE ADD STATEMENT

USING FORMAT 2 OF THE ADD STATEMENT

When using the GIVING format in Format 2 of the ADD statement, all fields and literals preceding the word GIVING are added together and the sum is placed in the field following the word GIVING. Thus, when using the GIVING format, the last data-field is not part of the ADD operation. Because it is not part of the arithmetic operation, it can be a report-item with edit symbols.

Consider this example of a Format 2 ADD operation:

USING FORMAT 2 OF THE ADD STATEMENT

The REGULAR-HOURS-WORKED and OVERTIME-HOURS-WORKED fields are summed and the result is placed in TOTAL-HOURS. The original contents of TOTAL-HOURS do not in any way affect the arithmetic operation. TOTAL-HOURS may be a report-item that contains a decimal point and dollar sign if it is to be printed.

Commas followed by at least one space may be used to separate operands, but they are optional. Thus, the following is also correct.

USING FORMAT 2 OF THE ADD STATEMENT

Tip

DEBUGGING TIP

Consider: ADD 40, OVERTIME-HOURS

GIVING TOTAL-HOURS.

A comma can be used anywhere in an instruction, as shown here, as long as at least one space follows it. We recommend that you omit commas, however, because they are added characters that can cause errors. You should separate entries instead by placing them on individual lines, as in this example:

ADD 40
OVERTIME-HOURS
GIVING TOTAL-HOURS.

This will reduce the risk of errors and help identify any syntax errors that may occur, because syntax errors are specified by line numbers.

USING FORMAT 3 OF THE ADD STATEMENT

The COBOL words TO and GIVING may be used in the same ADD operation. Like Format 2, the fields and literals preceding the word GIVING are added together and the sum is placed in the field following the word GIVING. Again, the last data-field is not part of the ADD operation. It is the field where the result of the ADD operation will be placed. Consider the following example.

ADD AMOUNT1 TO AMOUNT2 GIVING TOTAL-AMOUNT.

This same ADD operation could also have been stated with Format 2 as

USING FORMAT 3 OF THE ADD STATEMENT

In both examples, AMOUNT1 and AMOUNT2 are added together and the result is placed in the TOTAL-AMOUNT field. AMOUNT1 and AMOUNT2 are unchanged as a result of the ADD operation.

DECIDING WHETHER TO USE THE TO OR GIVING FORMAT

The ADD . . . TO format of the ADD operation is used to accumulate totals, usually column totals. For example, if we wanted to know the total hours worked for all employees, the ADD . . . TO operation would be used. As each employee record is read into the program, the hours-worked field would be added to a total hours field. So, the program would calculate a column total of the hours worked by all employees.

The ADD . . . GIVING is usually used to calculate a detail result. For example, if an employee record contains the regular hours and overtime hours, the ADD . . . GIVING operation could be used to add the two fields together and place (GIVING) the result in a total hours field.

All arithmetic statements may have a GIVING clause. When the contents of the operands are to be retained during an arithmetic operation, use the GIVING option. If operands need not be retained and are large enough to store the answer, the GIVING option is not required. In either case, the resultant field must always be a data-field or identifier and never a literal.

Use the GIVING format with the ADD statement when the contents of operands are to be retained. When you will no longer need the original contents of an operand after the addition, the TO format may be used.

ADDING MORE THAN TWO FIELDS

You are not restricted to two operands when using an ADD operation. Consider the following two examples.

Example 1 (Using GIVING):

ADDING MORE THAN TWO FIELDS

Note that the original contents of TOTAL-AMOUNT, the resultant field, are destroyed and have no effect on the ADD operation. The three operands AMOUNT1, AMOUNT2, and AMOUNT3 are unchanged.

Example 2 (Using TO):

ADDING MORE THAN TWO FIELDS

AMOUNT1, AMOUNT2, and AMOUNT3 are added to the original contents of TOTAL-AMOUNT. The result here, too, is placed in TOTAL-AMOUNT; the other three fields remain the same.

PRODUCING MORE THAN ONE SUM

It is also possible to perform several ADD operations with a single statement, using the TO format. Thus, the following is a valid ADD statement.

PRODUCING MORE THAN ONE SUM

This results in the same series of operations as this example:

PRODUCING MORE THAN ONE SUM

The rules for addition are

  1. All literals and fields that are part of the addition must be numeric. After the word GIVING, however, the field may be a report-item.

  2. The resultant field, following the word TO or the word GIVING, must be a data-name, not a literal.

  3. When using the TO format, the data-name following the word TO is the receiving field. This receiving field is part of the ADD; that is, its initial contents are summed along with the other fields. The receiving field must be a numeric field when using this format and not a report-item.

  4. When using the GIVING format, the data-name following the word GIVING is the receiving field. It will contain the sum, but its original contents will not be part of the ADD. It may be either a numeric field or a report-item.

  5. The words TO and GIVING may be specified in the same ADD statement.

SUBTRACT STATEMENT

The SUBTRACT statement has the following instruction formats.

Instruction Format 1 (SUBTRACT . . . FROM) Examples:

Examples:

SUBTRACT STATEMENT

Notice the placement of ellipses or dots in Format 1. The first set after identifier-1 means that two or more operands may be subtracted from identifier-2. In addition, operands may be subtracted from more than one identifier.

Instruction Format 2 (SUBTRACT . . . FROM GIVING) Examples:

Examples:

SUBTRACT STATEMENT

With Format 2, any number of identifiers can follow the word SUBTRACT or the word GIVING; but after the word FROM, only one identifier or literal is permitted.

The rules for the SUBTRACT operation are similar to those for an ADD:

  1. All literals and data-names that are part of the subtraction must be numeric; the field specified after the word GIVING, however, may be a report-item.

  2. The receiving field, which is the one that will hold the result, must be a data-name and not a literal. The following statement is incorrect: SUBTRACT TAX FROM 100.00. If you want to subtract a quantity from a literal (e.g., 100.00), you must use the GIVING format: SUBTRACT TAX FROM 100.00 GIVING NET.

  3. All fields and literals preceding the word FROM will be added together and the sum subtracted from the field following the word FROM. The result, or difference, will be placed in this same field if no GIVING option is used. All other fields will remain unchanged.

  4. When using the GIVING option, the operation performed is the same as in Rule 3, but the result, or difference, is placed in the field following the word GIVING. The initial content of the resultant field after the word GIVING does not take part in the arithmetic operation.

You are not restricted to two operands when using a SUBTRACT operation. Consider the following two examples.

Example 1 (Using FROM):

SUBTRACT STATEMENT
 

TOTAL-TAXES

PENSION

GROSS-PAY

Contents (Before SUBTRACT)

30ˆ00

10ˆ00

100ˆ00

Contents (After SUBTRACT)

30ˆ00

10ˆ00

044ˆ60

Example 2 (Using FROM and GIVING):

SUBTRACT STATEMENT
 

TOTAL-TAXES

PENSION

GROSS-PAY

NET-PAY

Contents (Before SUBTRACT)

30ˆ00

10ˆ00

100ˆ00

87ˆ00

Contents (After SUBTRACT)

30ˆ00

10ˆ00

100ˆ00

044ˆ60

These two examples produce the same result but in different storage areas. In example 2, the original contents of NET-PAY are replaced with the result and do not affect the calculation.

DECIDING WHICH FORMAT TO USE

As a rule, when the contents of an operand are not needed after the SUBTRACT operation, the FROM format may be used. When the contents of all operands are to be retained, the GIVING format is used.

As in ADD operations, all commas are optional. A space must, however, follow each comma.

As noted, it is possible to perform several SUBTRACT operations with a single statement using the FROM format. Therefore, the following is a valid statement.

DECIDING WHICH FORMAT TO USE

The preceding results in the same series of operations as this example:

DECIDING WHICH FORMAT TO USE

MULTIPLY STATEMENT

The MULTIPLY statement has the following two instruction formats.

Instruction Format 1 (MULTIPLY . . . BY)

Examples:

MULTIPLY STATEMENT

Instruction Format 2 (MULTIPLY . . . BY GIVING)

Examples:

MULTIPLY STATEMENT

All arithmetic operations can have more than one resultant field. Although ADD and SUBTRACT instructions can operate on numerous fields, the MULTIPLY and DIVIDE instructions are limited in the number of operations performed. For example, suppose we wish to obtain the product of PRICE × QUANTITY × DISCOUNT. Two operations would be used to obtain the desired product.

MULTIPLY STATEMENT

In the first MULTIPLY operation, the result, or product, is placed in WS-AMOUNT. Then, after the second MULTIPLY operation is completed, the product of the three numbers is in DISCOUNT. Hence, with each MULTIPLY statement specified, only two operands can be multiplied. Always make sure the receiving field is large enough to store the result.

Note that one operand can be multiplied by numerous fields. That is, MULTIPLY AMOUNT BY WS-TOTAL1, WS-TOTAL2 is valid.

EXAMPLE OF ARITHMETIC OPERATIONS THAT USE THE MULTIPLY OPERATION

Find C = A2 + B2 where A, B, and C are fields defined in the DATA DIVISION.

EXAMPLE OF ARITHMETIC OPERATIONS THAT USE THE MULTIPLY OPERATION

Note that to multiply A by itself places A × A or A2 in the field called A.

STORING INTERMEDIATE RESULTS

Consider the following input and output layouts.

Record description layout for customer purchase file

Field Description

Type

Size

COBOL Field-name

Customer Number

S

5,0

CP-CUSTOMER-NUMBER

Unit Price

P

7,2

CP-UNIT-PRICE

Quantity Ordered

P

5,0

CP-QUANTITY-ORDERED

Discount Amount

P

7,2

CP-DISCOUNT-AMOUNT

Record description layout for customer billing file

Field Description

Type

Size

COBOL Field-name

Customer Number

S

5,0

CB-CUSTOMER-NUMBER

Balance Due

A

7,2

CB-BALANCE-DUE

To obtain the output CB-BALANCE-DUE field, the following would be coded.

STORING INTERMEDIATE RESULTS

CP-UNIT-PRICE, CP-QUANTITY-ORDERED, and CP-DISCOUNT-AMOUNT are input fields defined for the CUSTOMER-PURCHASE-FILE. CB-BALANCE-DUE is a field in the CUSTOMER-BILLING-FILE. WS-GROSS-AMOUNT, however, is an intermediate result field necessary for calculating CB-BALANCE-DUE; it is not part of either the input or the output areas. As an intermediate result field, it is stored in a work area defined with an appropriate PICTURE clause in WORKING-STORAGE and defined as follows:

STORING INTERMEDIATE RESULTS

DIVIDE STATEMENT

The DIVIDE statement has the following instruction formats.

Instruction Format 1 (DIVIDE . . . INTO)

Examples:

DIVIDE STATEMENT

Instruction Format 2 (DIVIDE . . . INTO GIVING)

Examples:

DIVIDE STATEMENT

Instruction Format 3 (DIVIDE . . . BY GIVING)

Examples:

DIVIDE STATEMENT

As with the MULTIPLY statement, only two operands can be divided in a DIVIDE statement. Always make sure the receiving field is large enough to store the result.

DIVIDE STATEMENT

Either the word INTO or BY may be used with a DIVIDE statement. The GIVING clause is optional with INTO but required with BY.

In the DIVIDE operation, the preposition is either BY or INTO. To say DIVIDE QUANTITY INTO WS-TOTAL places in the resultant field, WS-TOTAL, the quotient of WS-TOTAL divided by QUANTITY.

Note that the following two statements produce the same results.

DIVIDE STATEMENT

Examples of Arithmetic Operations Using the DIVIDE Statement

Assume that all fields used in the following examples have the proper numeric PICTURE clauses. Keep in mind that the solution indicated for each example is only one method of solving the problem.

Example 1

Compute the average of three fields: EXAM1, EXAM2, EXAM3. Place the answer in AVERAGE, and do not alter the contents of the three fields.

One solution may be specified as

DIVIDE STATEMENT

Example 2

Celsius temperatures are to be converted to Fahrenheit temperatures according to the following formula.

FAHRENHEIT-OUT = (9 / 5) CELSIUS-IN + 32

CELSIUS-IN is a field in the input area, and FAHRENHEIT-OUT is a field in the output area. Both have numeric PICTURE clauses in the DATA DIVISION.

One solution may be specified as

DIVIDE STATEMENT

If CELSIUS-IN had an initial value of 20, its contents at the end of the operation would be 36 [i.e., (9 * CELSIUS-IN) / 5] and FAHRENHEIT-OUT would be equal to 68 (36 + 32).

You may have realized that 9/5 CELSIUS-IN = 1.8 CELSIUS-IN. Thus, the preceding solution may be reduced to two steps:

DIVIDE STATEMENT

USE OF THE REMAINDER CLAUSE IN THE DIVIDE OPERATION

When performing a division operation, the result will be placed in the receiving field according to the PIC specifications of that field. Consider the following.

USE OF THE REMAINDER CLAUSE IN THE DIVIDE OPERATION

Let us assume that the field MINUTES-IN contains a value of 402 and WS-HOURS has a PICTURE of 9 (2). After the operation is performed, 6 is placed in WS-HOURS:

402 / 60 = 6

It is sometimes useful to store the remainder of a division operation for additional processing. The DIVIDE can be used for this purpose by including a REMAINDER clause.

USING REMAINDER CLAUSE WITH DIVIDE STATEMENT

Instruction Format 4 (DIVIDE . . . INTO GIVING REMAINDER)

Examples:

USING REMAINDER CLAUSE WITH DIVIDE STATEMENT

Instruction Format 5 (DIVIDE . . . BY GIVING REMAINDER)

Examples:

USING REMAINDER CLAUSE WITH DIVIDE STATEMENT

To retain the remainder for future processing in the preceding example, we have

USING REMAINDER CLAUSE WITH DIVIDE STATEMENT

The use of the REMAINDER clause is optional; it does not change, in any way, the results of the original divide operation. We may use the REMAINDER clause, for example, to determine if a DIVIDE operation produces a quotient with no remainder at all. That is, we could test the REMAINDER field to see if it is zero. Figure 7.1 summarizes the arithmetic operations we have discussed.

Summary of arithmetic operations.

Figure 7.1. Summary of arithmetic operations.

OPTIONS AVAILABLE WITH ARITHMETIC VERBS

ROUNDED OPTION

Consider the following example.

ROUNDED OPTION

AMOUNT1

AMOUNT2

AMOUNT3

PICTURE

Contents

PICTURE

Contents

PICTURE

Contents After ADD

12.857

9 (2) V999

12ˆ857

9 (2) V9 (3)

25ˆ142

9 (2) V9 (2)

37ˆ99

+25.142/37.999

Performing arithmetic operations on fields that have different numbers of decimal positions is not uncommon in programming. In the preceding example, two fields, each with three decimal positions, are added together, and the resultant field contains only two decimal places. The program adds the two fields AMOUNT1 and AMOUNT2, with the sum 37ˆ999 placed in an accumulator. It attempts to move this result to AMOUNT3, a field with only two decimal positions. The effect is the same as coding MOVE 37.999 TO AMOUNT3. The low-order decimal position is truncated. Thus, AMOUNT3 is replaced with 37ˆ99.

A more desirable result would be 38ˆ00. since 38 is closer to the sum of 37.999 than is 37.99. Generally, we consider results more accurate if they are rounded to the nearest decimal position.

To obtain rounded results, the ROUNDED option may be specified with any arithmetic statement. In all cases, it directly follows the resultant data-name. The following examples serve as illustrations.

ROUNDED OPTION

If AMOUNT1 and AMOUNT2 had contents of 12.8576 and 25.142 in examples 5 and 6, and TOTAL1 had a PIC of 9 (2) V9 (2), the result would be rounded to 38ˆ00.

HOW ROUNDING IS ACCOMPLISHED

ROUNDED is optional with all arithmetic operations. If the ROUNDED option is not specified, truncation of decimal positions will occur if the resultant field cannot accommodate all the decimal positions in the answer. With the ROUNDED option, the

program will always round the result to the PICTURE specification of the receiving field. Consider the following example.

HOW ROUNDING IS ACCOMPLISHED

DISCOUNT

TOTAL

AMOUNT

PICTURE

Contents

PICTURE

Contents

PICTURE

Contents After SUB

9 (2) V99

87ˆ23

9 (2) V99

99ˆ98

9 (2)

12

In this case, 87.23 is subtracted from 99.98, and the result, 12.75, is placed in an accumulator. The computer moves this result to AMOUNT. Since AMOUNT has no decimal positions, truncation occurs and 12 is placed in AMOUNT.

Now consider the following SUBTRACT operation.

HOW ROUNDING IS ACCOMPLISHED

In this case, 12.75 is rounded to the PICTURE specification of the receiving field; that is, rounding to the nearest integer position will occur. 12.75 rounded to the nearest integer is 13, and thus, 13 is placed in AMOUNT. In practice, .5 is added to 12.75 producing 13.25, which is then truncated to an integer:

12.75 + .5 = 13.25, truncated to 13

If ROUNDED and REMAINDER are to be used in the same DIVIDE statement, ROUNDED must appear first.

Instruction Format (DIVIDE . . . ROUNDED REMAINDER)

Examples:

HOW ROUNDING IS ACCOMPLISHED

ON SIZE ERROR OPTION

Consider the following.

ADD AMOUNT1 AMOUNT2 TO AMOUNT3.

Before the ADD operation, the fields contain

AMOUNT1

AMOUNT2

AMOUNT3

PICTURE

Contents

PICTURE

Contents

PICTURE

Contents Before ADD

9 (3)

800

9 (3)

150

9 (3)

050

After the ADD operation, the content of AMOUNT3 is 000.

The program will add 800, 150, and 050 in an accumulator. It will attempt to place the sum, 1000, into AMOUNT3, which is a three-position field. The effect would be the same as coding MOVE 1000 TO AMOUNT3. Since numeric MOVE operations move integer data from right to left, 000 will be placed in AMOUNT3. In this case, the resultant field is not large enough to store the accumulated sum. We say that an overflow or size error condition has occurred.

Note that an overflow condition will produce erroneous results. The computer will not generally stop or terminate the program because of a size error condition; instead, it will truncate high-order or leftmost positions of the field. In our example, 000 will be placed in AMOUNT3.

AVOIDING SIZE ERRORS

The best way to avoid a size error condition is to be absolutely certain that the receiving field is large enough to accommodate any possible result. Sometimes, however, the software developer forgets to account for the rare occasion when an overflow might occur. COBOL has a built-in solution. Use an ON SIZE ERROR clause with any arithmetic operation:

Instruction Format

AVOIDING SIZE ERRORS

The word ON is optional; hence it is not underlined. By an imperative statement, we mean any COBOL statement that gives a direct command and does not perform a test. Statements beginning with the COBOL word IF are conditional statements and are not considered imperative. This concept will become clearer when we discuss conditional statements.

When using a separate clause such as ON SIZE ERROR, use a scope terminator to delimit or end the arithmetic operation. END-ADD, END-SUBTRACT, END-MULTIPLY, and END-DIVIDE are all permissible scope terminators.

Since ON SIZE ERROR is a separate clause, we place it on a separate line for ease of reading and debugging.

AVOIDING SIZE ERRORS

The computer performs the arithmetic and ignores the SIZE ERROR clause if there is no size error condition. If a size error occurs, the program does not perform the arithmetic but instead executes the statement(s) in the SIZE ERROR clause. In the first example above, the program will move zeros to TOTAL-OUT if it does not contain enough integer positions to accommodate the sum of AMOUNT1, AMOUNT2, and AMOUNT3. If TOTAL-OUT is large enough for the result, zeros will not be moved to it and execution will continue with the next sentence.

In the second example, the error message 'INVALID DIVIDE' is moved to the ERROR-MESSAGE field if the HOURS field is not large enough to accommodate the result of the divide operation.

DIVIDING BY ZERO CAUSES A SIZE ERROR

A size error, then, is a condition in which the receiving field does not have enough integer positions to hold the result of an arithmetic operation. In a divide, the size error condition has additional significance. If an attempt is made to divide by zero, a size error condition will occur. This is because division by zero yields a result of infinity, which makes it impossible to define a sufficiently large receiving field.

Consider the following.

DIVIDING BY ZERO CAUSES A SIZE ERROR

Assume that the fields contain the following data before the operation.

QUANTITY

TOTAL

PICTURE

Contents

PICTURE

Contents

9 (4)

0000

9 (2)

10

A size error occurs during the DIVIDE operation because QUANTITY = 0. When the SIZE ERROR clause is executed, TOTAL is set equal to 0. If a SIZE ERROR clause were not specified, the program would attempt to divide by zero. The results of such a division would be unpredictable or may even cause the program to terminate. When you specify ON SIZE ERROR, the program will make certain that the divisor is not zero before attempting to DIVIDE. You will see in a later chapter on conditional statements that you may also avoid errors by coding

DIVIDING BY ZERO CAUSES A SIZE ERROR

If the ON SIZE ERROR option is employed along with the ROUNDED option, the word ROUNDED always precedes ON SIZE ERROR.

Instruction Format

DIVIDING BY ZERO CAUSES A SIZE ERROR

When using a REMAINDER in a DIVIDE operation, we would have the following sequence of clauses:

Instruction Format

DIVIDING BY ZERO CAUSES A SIZE ERROR

NOT ON SIZE ERROR CLAUSE

Another permissible test that may be used with any arithmetic operation is NOT ON SIZE ERROR.

NOT ON SIZE ERROR CLAUSE

300-WRITE-RTN is executed only if the ADD operation results in a valid addition, that is, only if TOTAL-AMOUNT is large enough to hold the sum of AMOUNT1 and AMOUNT2.

Both ON SIZE ERROR and NOT ON SIZE ERROR can be specified with any arithmetic operation.

DETERMINING THE SIZE OF RECEIVING FIELDS

When performing arithmetic, you must make certain that the receiving field is large enough to accommodate the result. In an ADD, determine the largest quantity that can be stored in each field and manually perform an addition. Use the result to determine how large the receiving field should be. With a subtract, manually subtract the smallest possible number from the largest possible number to determine how large to make the receiving field.

As a general rule, the number of integer positions in the receiving field of a MULTIPLY operation should be equal to the sum of the integers of the operands being multiplied. Suppose we specify MULTIPLY QUANTITY BY PRICE GIVING TOTAL. If QUANTITY has a PIC of 9 (2) and PRICE has a PIC of 9 (3), then to ensure that TOTAL is large enough to accommodate the result, it should have a PIC of 9 (5), which is the sum of the two integers in QUANTITY plus the three integers in PRICE.

The number of decimal positions in the receiving field will depend on the decimal precision desired in the result.

For DIVIDE operations, the PIC clause of the quotient or receiving field is dependent on the type of divide. Consider the following.

DETERMINING THE SIZE OF RECEIVING FIELDS

If TOTAL-PRICE and QUANTITY have PIC 9, the receiving field may have PIC 9V99 or 9V9, to allow for decimal values (e.g., 3/6 = .5). But suppose TOTAL-PRICE has PIC 9V9 and contents of 9ˆ0, and QUANTITY has the same PIC clause with contents of .1. The result of the divide is 9/.1, which is equal to 90. Hence UNIT-COST would need a PIC of 9 (2). As a rule, determine the range of values that the fields can have and code the PIC clause of the receiving field accordingly.

DETERMINING THE SIZE OF RECEIVING FIELDS

USING SCOPE TERMINATORS

Consider the following coding.

USING SCOPE TERMINATORS

Suppose we intend to perform an error routine if a size error or an overflow occurs. In the next sentence, we wish to write a record. To accomplish this, a period or scope terminator should have been included on the third line of the program excerpt. When ON SIZE ERROR is used and a size error occurs, the program will execute all statements following the words ON SIZE ERROR until a period or END-ADD is reached. Because there is no period until after the WRITE statement, the computer assumes that both the PERFORM and the WRITE are to be executed only if a size error occurs. Thus, even though the WRITE is not indented, it is treated as part of the ON SIZE ERROR clause.

There are two ways to avoid this logic error:

  1. Be very careful about the placement of periods.

    USING SCOPE TERMINATORS
  2. Use a scope terminator to delimit the end of an arithmetic statement. In the following, END-ADD marks the end of the operation.

USING SCOPE TERMINATORS

Because END-ADD delimits the ADD, a period after END-ADD is optional. All arithmetic verbs may have scope terminators: END-ADD, END-SUBTRACT, END-MULTIPLY, END-DIVIDE. We recommend that you use arithmetic scope terminators whenever you use an ON SIZE ERROR or NOT ON SIZE ERROR clause. When you use scope terminators, periods can be omitted in statements except for the last one in a paragraph.

THE COMPUTE STATEMENT

If complex or extensive arithmetic operations are required in a program, the use of the four arithmetic verbs may prove cumbersome. The COMPUTE statement provides another method of performing arithmetic.

The COMPUTE statement uses arithmetic symbols rather than arithmetic verbs. The following symbols may be used in a COMPUTE statement.

Symbol

Meaning

+

ADD

-

SUBTRACT

*

MULTIPLY

/

DIVIDE

**

exponentiation (there is no corresponding COBOL verb)

The following examples illustrate the use of the COMPUTE verb.

THE COMPUTE STATEMENT

Note that the COMPUTE statement has a data-name to the left of, or preceding, the equal sign. The value computed in the arithmetic expression to the right of the equal sign is placed in the field preceding the equal sign.

Thus, if AMOUNT = 200 in the first example, TAX will be set to .05 * 200, or 10, at the end of the operation. The original contents of TAX, before the COMPUTE is executed, are not retained. The fields specified to the right of the equal sign remain unchanged.

Consider another example.

COMPUTE TOTAL = AMOUNT1 + AMOUNT2 - AMOUNT3.

Field

Contents (Before COMPUTE)

Contents (After COMPUTE)

TOTAL

100

95

AMOUNT1

80

80

AMOUNT2

20

20

AMOUNT3

5

5

AMOUNT1, AMOUNT2, and AMOUNT3 remain unchanged after the COMPUTE. TOTAL is set equal to the result of AMOUNT1 + AMOUNT2 - AMOUNT3. The previous contents of TOTAL do not affect the operation. TOTAL contains 95 after the COMPUTE operation.

The fields specified after the equal sign in a COMPUTE statement may be numeric literals or data-names with numeric PIC clauses.

The COMPUTE statement may include more than one operation. In COMPUTE DAILY-SALES = QUANTITY * UNIT-PRICE / 5, both multiplication and division operations are performed. The following two statements are equivalent to this single COMPUTE statement.

THE COMPUTE STATEMENT

The COMPUTE statement has the advantage of performing more than one arithmetic operation with a single verb. For this reason, it is often less cumbersome to use COMPUTE statements to code complex arithmetic.

ADD, SUBTRACT, MULTIPLY, and DIVIDE correspond to the arithmetic symbols +, -, *, and /, respectively. In addition, we may raise a number to a power with the use of the arithmetic symbol ** in a COMPUTE statement. No COBOL verb corresponds to this operation. Thus, COMPUTE B = A ** 2 is the same as multiplying A by A and placing the result in B. Remember, A ** 2 is expressed mathematically as A2. Likewise, A ** 3 is the same as A3 or A * A * A. To find B4 and place the results in C, we could specify: COMPUTE C = B ** 4.

SPACING RULES WITH A COMPUTE

You must follow precise spacing rules when using the COMPUTE statement. That is, the equal sign as well as the arithmetic symbols must be preceded and followed by a space. Thus, to calculate A = B + C + D2 and place the result in A, use the following COMPUTE statement:

COMPUTE A = B + C + D ** 2.

So far, we have used arithmetic expressions to the right of the equal sign. We may also have literals or data-names as the only entry to the right of the equal sign. To say COMPUTE AMOUNT1 = 10.3 is the same as saying MOVE 10.3 TO AMOUNT1. Similarly, to say COMPUTE AMOUNT2 = AMOUNT3 places the contents of AMOUNT3 in the field called AMOUNT2. This is the same as saying MOVE AMOUNT3 TO AMOUNT2. Thus, in a COMPUTE statement, we may have one of the following three entries after the equal sign:

  1. An arithmetic expression. For example,

    COMPUTE SALARY = HOURS * RATE.
  2. A literal. For example,

    COMPUTE TAX = .05.
  3. A data-name or identifier. For example,

    COMPUTE AMOUNT-OUT = AMOUNT-IN.

The ROUNDED, ON SIZE ERROR, and NOT ON SIZE ERROR options may also be used with the COMPUTE. The rules governing the use of these clauses in ADD, SUBTRACT, MULTIPLY, and DIVIDE operations apply to COMPUTE statements as well.

To round the results in a COMPUTE statement to the specifications of the receiving field, we use the ROUNDED option directly following the receiving field. If we need to test for a size error condition, we may use the ON SIZE ERROR or NOT ON SIZE ERROR clause as the last one in the statement. The instruction format for the COMPUTE follows.

Instruction Format

SPACING RULES WITH A COMPUTE

THE COMPUTE WITH AND WITHOUT ROUNDING

Consider the following examples.

  1. COMPUTE A = B + C + D.

  2. COMPUTE A ROUNDED = B + C + D.

B

C

D

PICTURE

Contents

PICTURE

Contents

PICTURE

Contents

9V99

1ˆ05

9V99

2ˆ10

9V99

6ˆ84

 

Result in A

 

PICTURE

Contents

Example 1 without rounding

9 (2) V9

09ˆ9

Example 2 with rounding

9 (2) V9

10ˆ0

Consider the following example.

COMPUTE AMOUNT1 = 105 - 3.

This COMPUTE statement would result in an overflow condition if AMOUNT1 has a PICTURE of 9 (2). The computed result should be 102. However, placing 102 in AMOUNT1, a two-position numeric field, results in the truncation of the most significant digit, the hundreds' position. Thus 02 will be placed in AMOUNT1. To protect against this type of truncation of high-order integer positions, we use an ON SIZE ERROR test:

THE COMPUTE WITH AND WITHOUT ROUNDING

END-COMPUTE may be used as a scope terminator to mark the end of a COMPUTE statement. We recommend you use END-COMPUTE if you use ON SIZE ERROR or NOT ON SIZE ERROR.

In summary, the primary advantage of a COMPUTE statement is that several arithmetic operations may be performed with one instruction. The data-name preceding the equal sign is made equal to the literal, identifier, or arithmetic expression to the right of the equal sign. Thus, ADD 1 TO TOTAL is equivalent to COMPUTE TOTAL = TOTAL + 1.

A COMPUTE statement often requires less coding than if the arithmetic verbs such as ADD or SUBTRACT were used. The expression C = A2 + B2, for example, is more easily coded with only one COMPUTE statement:

COMPUTE C = A ** 2 + B ** 2

There is no COBOL arithmetic symbol to perform a square root operation. Mathematically, however, the square root of any number is that number raised to the ½ or .5 power. √25 = 255 = 5. Thus, the square root of any number will be represented as the number raised to the .5 power. To calculate C = √A in COBOL, we code COMPUTE C = A **.5.

ORDER OF EVALUATION

The result of a COMPUTE statement is determined by the order in which arithmetic operations are performed. The sequence in which operations are performed in a COMPUTE statement is

  1. ( ) Operations within parentheses are performed first.

  2. **.

  3. * or / (whichever appears first from left to right).

  4. + or - (whichever appears first from left to right).

Without parentheses, exponentiation operations are performed first. Multiplication and division operations follow any exponentiation and precede addition or subtraction operations. If there are two or more multiplication or division operations, they are evaluated from left to right in the expression. Addition and subtraction are evaluated last, also from left to right.

Consider the following example.

COMPUTE UNIT-PRICE-OUT = AMOUNT1-IN + AMOUNT2-IN / QUANTITY-IN.

In accordance with the order of evaluation of arithmetic operations, the following would be the mathematical equivalent of the preceding.

Equation 7.1. 

ORDER OF EVALUATION

UNIT-PRICE-OUT is calculated as

  1. AMOUNT2-IN / QUANTITY-IN

  2. AMOUNT1-IN + AMOUNT2-IN

To divide QUANTITY-IN into the sum of AMOUNT1-IN and AMOUNT2-IN, we code

COMPUTE UNIT-PRICE-OUT = (AMOUNT1-IN + AMOUNT2-IN) / QUANTITY-IN.

Consider another example.

COMPUTE A = C + D ** 2.

  1. D ** 2 Exponentiation is performed first

  2. C + D Addition is performed next

The result, then, is A = C + D2, not A = (C + D)2.

The statement, COMPUTE S = T × D + E / F, results in the following order of evaluation:

  1. T * D Multiplication is performed first

  2. E / F Division is performed next

  3. (T * D) + (E / F) Addition is performed last

We may control the order of evaluation in a COMPUTE statement with the use of parentheses because operations within parentheses are always evaluated first.

Suppose we wish to compute AVERAGE-SALES by adding DAYTIME-SALES and EVENING-SALES and dividing the sum by two. To divide the sum of DAYTIME-SALES and EVENING-SALES by two, we must use parentheses:

COMPUTE AVERAGE-SALES = (DAYTIME-SALES + EVENING-SALES) / 2.

All operations within parentheses are evaluated first. Thus, we have

  1. (DAYTIME-SALES + EVENING-SALES).
    2. (DAYTIME-SALES + EVENING-SALES) / 2.

The following provides additional examples of the hierarchy rules.

Operation

Order of Evaluation

A / B + C

Divide A by B and add C.

A / (B + C)

Add B and C and divide A by the sum.

A + B * C

Multiply B by C and add A.

A * B / C

Multiply A by B and divide the result by C.

In this next example, we wish to obtain NET = GROSS - DISCOUNT, where DISCOUNT = GROSS * .03:

COMPUTE NET = GROSS - (GROSS * .03)

In this example, the parentheses are not really needed, since the standard hierarchy rules produce the correct results. Including parentheses for clarity, however, is not incorrect. The following would also be correct.

COMPUTE NET = GROSS - GROSS * .03.

COMPARING COMPUTE TO ARITHMETIC VERBS

As we have seen, any calculation can be performed using either the four arithmetic verbs or the COMPUTE statement. Exponentiation, which has no corresponding verb, is more easily handled with a COMPUTE but can be accomplished with a MULTIPLY statement as well.

Consider the following three examples where we compare the use of the four arithmetic verbs with the COMPUTE statement.

Example 1

Compute the average of three fields: EXAM1, EXAM2, EXAM3. Place the answer in AVERAGE, and do not alter the contents of the three fields.

COMPARING COMPUTE TO ARITHMETIC VERBS

Example 2

Celsius temperatures are to be converted to Fahrenheit temperatures using the following formula

FAHRENHEIT-OUT = (9 / 5) CELSIUS-IN + 32.

COMPARING COMPUTE TO ARITHMETIC VERBS

Example 3

Find C = A2 + B2 where A, B, and C are fields defined in the DATA DIVISION.

COMPARING COMPUTE TO ARITHMETIC VERBS

SIGNED NUMBERS IN ARITHMETIC OPERATIONS FOR FIELDS THAT CAN BE NEGATIVE

In our illustrations, we have assumed that numbers used in calculations are positive and that results of calculations produce positive numbers. If, however, a number may be negative or if a calculation may produce negative results, we must use an S in the PICTURE clause of the field. Thus, AMOUNT1 with a PIC of S9 (3) is a field that may have positive or negative contents. Remember from Chapter 1 that the sign of a numeric field is stored in the rightmost (low-order) byte. Fields that are defined in zone-decimal format store the sign in the zone portion of the rightmost byte, while fields defined in packed-decimal format store the sign in the digit portion of the rightmost byte. The S, like an implied decimal point, does not use a storage position; that is, S9 (3) represents a three-position signed field. If AMOUNT1 with a PIC of S9 (3) has an initial value of 010 and we subtract 15 from it, the result will be −5. But if we had defined AMOUNT1 with a PIC of 9 (3), then the result would have been incorrectly retained without the sign as 5.

In summary, if a field used in an arithmetic operation may contain a negative number, use an S in the PICTURE clause. Without an S in the PICTURE clause, the field will always be considered an unsigned or positive number.

You have seen that printing a negative number requires a minus sign in the PICTURE clause of the receiving field. Suppose AMOUNT1-IN has contents of −123. To print −123 correctly when we MOVE AMOUNT1-IN TO AMOUNT1-OUT, AMOUNT1-IN should have a PIC of S9 (3), and AMOUNT1-OUT should have a PICTURE of −9 (3).

RULES FOR PERFORMING ARITHMETIC WITH SIGNED NUMBERS

The following are rules for performing arithmetic using signed numbers.

Multiplication: Multiplicand * Multiplier = Product

Product is + if multiplicand and multiplier have the same sign.

Product is - if multiplicand and multiplier have different signs.

Examples:

Equation 7.2. 

RULES FOR PERFORMING ARITHMETIC WITH SIGNED NUMBERS

Division: Dividend / Divisor = Quotient

Quotient is + if dividend and divisor have the same sign. Quotient is - if dividend and divisor have different signs.

Examples:

  1. - 6 / - 3 = 2

  2. 5 / −1 = −5

Addition:

If signs of the fields being added are the same, add and use the sign.

Examples:

Equation 7.3. 

RULES FOR PERFORMING ARITHMETIC WITH SIGNED NUMBERS

If fields being added have different signs, add all fields with positive numbers, and add all fields with negative numbers separately. Then subtract the smaller total from the larger total and use the sign of the larger.

Examples:

Equation 7.4. 

RULES FOR PERFORMING ARITHMETIC WITH SIGNED NUMBERS

Subtraction:

Minuend - Subtrahend/Difference

Change the sign of the subtrahend and proceed as in addition.

Examples:

  1. 15 − 5 = 15 + (−5) = + 10

  2. − 3 − (+ 2) = − 3 + (− 2) = −5

ENTERING A SIGN SEPARATE FROM THE DATA

To enter a sign as a separate character, use the following clause after the PIC clause in the DATA DIVISION:

SIGN IS {TRAILING/LEADING} SEPARATE

That is, to enter −1234 in a field with PIC S9 (4), code the field as 05 AMOUNT PIC S9 (4) SIGN IS LEADING SEPARATE. Similarly, to enter 1234- in a field, code it as 05 AMOUNT PIC S9 (4) SIGN IS TRAILING SEPARATE. Note, however, that these SIGN clauses make AMOUNT a five-position field.

CLEARING FIELDS USING THE INITIALIZE STATEMENT

Individual fields or a series of elementary items contained within a group item can all be initialized with the INITIALIZE verb. A group field is a field that does not contain a PIC clause. Numeric fields are initialized at zero, and alphanumeric fields are initialized with blanks.

CLEARING FIELDS USING THE INITIALIZE STATEMENT

The first INITIALIZE statement will set WS-TOTAL-SALES to zeros because it is a numeric field defined as PIC 9 (7) v99. In the second INITIALIZE statement, WS-TEMP-NAME, an alphanumeric field defined as PIC X (25) is set to spaces. The third INITIALIZE statement sets WS-GROSS-PAY and WS-NET-PAY to zeros and also sets WS-EMPLOYEE-FULL-NAME to spaces.

We can initialize a numeric field to zeros by (1) using a VALUE clause of ZERO in WORKING-STORAGE, (2) moving zeros to it in the PROCEDURE DIVISION, or (3) initializing it to zero in the PROCEDURE DIVISION. If the content of a numeric field is changed during execution, the initial value of zero will be replaced.

CLEARING FIELDS USING THE INITIALIZE STATEMENT

After the ADD instruction is executed the first time, WS-SALES-TOTAL will contain the value of SALES-IN and not zero. If, however, we did not initialize WS-SALES-TOTAL at ZERO, the contents of WS-SALES-TOTAL after the ADD would be unpredictable. For example, if the numeric field contained non-numeric data such as spaces, it would cause a decimal data error, and the pro-

gram would terminate abnormally. We cannot assume a value of zero in a field that has not been initialized.

Tip

DFBUGGING TIP

Failure to initialize a numeric field used in an arithmetic operation will cause a decimal data error (abnormal end to the program). Be sure to initialize all numeric fields prior to processing.

Tip

DFBUGGING TIP

The software developer decides whether to use a WORKING-STORAGE data item to store a constant in a work area or to code the constant as a literal in the PROCEDURE DIVISION. As a general rule, however, any literal that will be used more than once in the PROCEDURE DIVISION should be given an assigned storage area and a data-name in WORKING-STORAGE. It is more efficient to use this data-name several times in the program than to redefine the same literal again and again in the PROCEDURE DIVISION.

LIKE CLAUSE

The LIKE clause allows the attributes of a data item to be defined by copying them from a previously defined data item. Two attributes include the PICTURE and USAGE clauses of the existing item.

Consider the following example in which a field called WS-NET-PAY is defined in the WORKING-STORAGE SECTION as having the same attributes as the field EMPLOYEE-GROSS-PAY defined in a data record using the LIKE clause.

LIKE CLAUSE

When the program is compiled, the compiler generates comments to identify the characteristics of the new WS-NET-PAY field. These comments appear after the statement containing the LIKE clause. Thus, in our example, the comment PICTURE 9 (7) V9 (2) is shown following WS-NET-PAY to indicate the attribute(s) that the field has acquired from EMPLOYEE-GROSS-PAY.

Alphanumeric fields can be defined with the LIKE clause as well. In the following example, GIVEN-NAME is defined to have the same attributes as FAMILY-NAME.

LIKE CLAUSE

Using the LIKE clause, the attributes of one data item can be copied to another data item and changes can be made to the length of the new data item. The following example shows how to define the new field WS-YEARLY-SALES and increase the field length by 2. In this example, an integer (+2) is used to increase the length of the new field WS-YEARLY-SALES:

LIKE CLAUSE

Similarly, an integer can be used to decrease the length of the new field. If a blank or a + precedes the integer, the new item is longer. If a – precedes the integer, the new item is shorter. Only the integer portion of the field length can be increased or decreased. You cannot change the number of decimal places in a field.

In this example, the compiler has added two comment lines following the new field WS-YEARLY-SALES that identify the attributes of the field. Two lines were added because the new field WS-YEARLY-SALES acquired two attributes (PICTURE and USAGE) from the original field WS-MONTHLY-SALES.

The LIKE clause can also be used with signed fields. Thus, if WS-MONTHLY-SALES were a signed field, PIC S9 (7) V9 (2), then WS-YEARLY-SALES would also be defined as a signed field.

DISPLAY STATEMENT

If logic errors occur that are difficult to find, the DISPLAY statement can be used for debugging purposes. It can be used while the program is executing to display a message along with intermediate results to the software developer. This helps isolate errors. Remember to eliminate the DISPLAY statements after the program has been fully debugged.

When invalid data is entered into a numeric field, a decimal data error occurs and the program terminates. The DISPLAY statement can be used to display the contents of fields while the program is running. The following code illustrates how two DISPLAY statements are used to display the current values of HOURLY-RATE-IN and HOURS-WORKED-IN.

DISPLAY STATEMENT

When the program reaches 210-CALCULATE-PAYROLL-RTN and the DISPLAY statements are executed, the following two lines are displayed on the screen.

HOURLY RATE IS01565

HOURLY WORKED IS365

A DISPLAY statement may be used to view any data item, even an entire record, on the screen. No corresponding file needs to be defined in the ENVIRONMENT DIVISION. Similarly, an OPEN or CLOSE statement is not required. We may also say DISPLAY FIELDA, where FIELDA is any field defined in the DATA DIVISION, or we may say DISPLAY RECORD-IN, where RECORD-IN is described in WORKING-STORAGE. In fact, any field or record defined in the

FILE or WORKING-STORAGE SECTIONs may be displayed. Similarly, we may say DISPLAY 'INVALID CODE', as a quick method of informing the software developer of an error before the program terminates. Finally, we can display more than one item using a single statement:

DISPLAY 'HOURLY-RATE ', EP-HOURLY-RATE, ' IS INVALID'.

In addition to displaying the contents of fields, you may wish to display a message to indicate that a certain step has been executed in the program. For example, DISPLAY 'THE PROGRAM HAS EXECUTED MODULE 210' could be placed as the first statement in 210-CALCULATE-PAYROLL-RTN. When the program reaches the 210-CALCULATE-PAYROLL-RTN module, the message is displayed on the screen to indicate that the program has begun to execute the 210-CALCULATE-PAYROLL-RTN module.

CASE PROBLEM # 1

The program in this case problem illustrates the use of arithmetic operations.

Problem Definition

The Payroll Manager of the Best Deal Stores Company needs a payroll report for all employees of the company.

The program specifications are illustrated below.

Systems flowchart

CASE PROBLEM # 1

Record description layout for employee pay file — EMPPAYPF

Field Description

Type

Size

Position

COBOL Field-name

Employee Number (K)

S

9,0

1 - 9

EP-EMPLOYEE-NUMBER

Store Number

S

4,0

10 - 13

EP-STORE-NUMBER

First Name

A

15

14 - 28

EP-FIRST-NAME

Middle Initial

A

1

29 - 29

EP-MIDDLE-INITIAL

Last Name

A

15

30 - 44

EP-LAST-NAME

Department Number

S

3,0

45 - 47

EP-DEPARTMENT-NUMBER

Hourly Rate

P

5,2

48 - 50

EP-HOURLY-RATE

Hours Worked

P

3,1

51 - 52

EP-HOURS-WORKED

Sales

P

5,0

53 - 55

EP-SALES

Calculations to Be Performed:

Hourly Pay = Hourly Rate * Hours Worked
Commission = Sales * 5.5% (.055)
Gross Pay = Hourly Pay + Commission
Federal Tax = Gross Pay * Federal Tax Rate (12.5%)

Federal Tax Rate is a flat tax of 12.5% (.125) for every employee

State Tax = Gross Pay * State Flat Tax (6%)

State Tax Rate is a flat tax of 6% (.06) for every employee

Pension Plan Contribution = Gross Pay * 3.0% (.030) for every employee

Health Insurance Premium = Gross Pay * 1.5% (.015) for every employee

Life Insurance Premium = Gross Pay * 1.5% (.015) for every employee

Total Deductions = Pension Plan Contribution + Health Insurance Premium + Life Insurance Premium + Federal Tax + State Tax

Net Pay = Gross Pay - Total Deductions

Printer spacing chart for employee hours worked report

CASE PROBLEM # 1
Solution for program CPCH07A.

Figure 7.2. Solution for program CPCH07A.

The report in Figure 7.3 is the output report produced from program CPCH07A.

Report produced by program CPCH07A.

Figure 7.3. Report produced by program CPCH07A.

CASE PROBLEM # 2

The program in this case problem illustrates

  • The use of the COMPUTE statement.

  • How totals are accumulated.

  • How totals are calculated and printed on a report.

Problem Definition

The Payroll Manager of the Best Deal Stores Company would like to improve the Employee Payroll Report by including totals at the end of the report.

The program specifications are illustrated below.

Systems flowchart

CASE PROBLEM # 2

Record description layout for employee pay file — EMPPAYPF

Field Description

Type

Size

Position

COBOL Field-name

Employee Number

S

9,0

1 - 9

EP-EMPLOYEE-NUMBER

Store Number

S

4,0

10 - 13

EP-STORE-NUMBER

First Name

A

15

14 - 28

EP-FIRST-NAME

Middle Initial

A

1

29 - 29

EP-MIDDLE-INITIAL

Last Name

A

15

30 - 44

EP-LAST-NAME

Department Number

S

3,0

45 - 47

EP-DEPARTMENT-NUMBER

Hourly Rate

P

5,2

48 - 50

EP-HOURLY-RATE

Hours Worked

P

3,1

51 - 52

EP-HOURS-WORKED

Sales

P

5,0

53 - 55

EP-SALES

Detail Calculations to Be Performed:

Gross Pay = (Hourly Rate * Hours Worked) + (Sales * 5.5% (.055))
Total Deductions = Gross Pay * Federal Tax Rate (12.5%)
+ Gross Pay * State Flat Tax (6%)
+ Gross Pay * Pension Plan Rate (4.5%)
+ Gross Pay * Health Insurance Rate (1.5%)
+ Gross Pay * Life Insurance Rate (1.5%)
Net Pay = Gross Pay – Total Deductions
Solution for program CPCH07B.

Figure 7.4. Solution for program CPCH07B.

Report produced by program CPCH07B.

Figure 7.5. Report produced by program CPCH07B.

END-OF-CHAPTER AIDS

CHAPTER SUMMARY

  1. The ADD, SUBTRACT, MULTIPLY, and DIVIDE verbs all have a GIVING format. With this GIVING format, the receiving field is not part of the arithmetic and can be a report-item.

  2. A COMPUTE statement can be used for performing multiplication, division, addition, subtraction, exponentiation, or a combination of these.

  3. The COMPUTE can save coding if used in place of the ADD, SUBTRACT, MULTIPLY, and DIVIDE verbs.

  4. The COMPUTE statement can use the following operations.

    + Addition

    - Subtraction

    * Multiplication.

    / Division

    ** Exponentiation

  5. If several operations are performed with one COMPUTE statement, the order of evaluation is

    1. ( ) (parentheses).

    2. ** (exponentiation).

    3. * or / (in sequence left to right).

    4. + or -(in sequence left to right).

  6. The ROUNDED, ON SIZE ERROR, and NOT ON SIZE ERROR options can be used with the four arithmetic verbs and the COMPUTE.

  7. When using ON SIZE ERROR or NOT ON SIZE ERROR with any arithmetic verb, use a scope terminator (END-ADD, END-SUBTRACT, END-MULTIPLY, END-DIVIDE, END-COMPUTE).

KEY TERMS

ADD

COMPUTE

Counter field

DIVIDE

Imperative statement

Intermediate result field

MULTIPLY

ON SIZE ERROR

Overflow

REMAINDER

ROUNDED

SUBTRACT

CHAPTER SELF-TEST

TRUE-OR-FALSE QUESTIONS

  1. 1. The following are valid instructions.

    ADD A TO B, C, D.

    ADD A, B GIVING C, D.

    COMPUTE A = A + 1.

    MULTIPLY A BY B BY C.

    SUBTRACT A FROM 150.

  2. 2. Unless parentheses are used, ** will always be performed first in a COMPUTE statement.

  3. 3. Anything that can be coded with a COMPUTE statement can be coded instead with the four arithmetic verbs.

  4. 4. The DIVIDE operation can produce a remainder as well as a quotient.

  5. 5. If both the ROUNDED and ON SIZE ERROR options are used, the ROUNDED always appears first.

FILL-IN-THE BLANKS

  1. If ADD 1 15 3 TO COUNTER is performed and COUNTER is initialized at 10, the value of COUNTER at the end of the operation is ___.

  2. If ADD 1 15 3 GIVING COUNTER is performed, the value of COUNTER at the end of the operation is ___.

  3. In the operation SUBTRACT 1500 FROM GROSS GIVING NET, the result, or difference, is placed in ___. What happens to the original contents of GROSS? If GROSS has an original value of 8500, and NET has an original value of 2000, the result in NET would be ___.

  4. The word directly following the verb COMPUTE must be a(n) ___.

  5. The word ROUNDED (precedes, follows) the ON SIZE ERROR clause in an arithmetic statement.

CHAPTER REVIEW QUESTIONS

GENERAL QUESTIONS

  1. Without using the word TO, write a statement equivalent to ADD 1 15 3 TO COUNTER.

  2. Indicate what, if anything, is wrong with the following arithmetic statements.

    1. ADD AMOUNT1 TO AMOUNT1-OUT, AMOUNT2-OUT.

    2. ADD AMOUNT1 TO AMOUNT2 GIVING TOTAL.

    3. MULTIPLY A BY B BY C.

    4. DIVIDE AMOUNT BY 5 REMAINDER REMAINDER-1.

    5. SUBTRACT AMOUNT1 AMOUNT2 FROM AMOUNT3 AMOUNT4.

  3. What is wrong with the following two statements?

    1. SUBTRACT $23.00 FROM AMOUNT.

    2. SUBTRACT AMOUNT FROM 900.00.

  4. Use one SUBTRACT statement to subtract three fields (TAX, CREDIT, DISCOUNT) from TOTAL and place the answer in WS-AMOUNT.

  5. DISTANCE is the distance traveled in a specific car trip, and GAS is the number of gallons of gas used. Calculate the average gas mileage and place it in a field called AVERAGE.

  6. What, if anything, is wrong with the following COMPUTE statements?

    1. COMPUTE TOTAL = AMOUNT1 + AMOUNT2 ROUNDED.

    2. COMPUTE AMOUNT-OUT = 10.5.

    3. COMPUTE OVERTIME-PAY = (HOURS – 40.) * 1.5.

    4. COMPUTE E = A * B /* C + D.

    5. COMPUTE X + Y = A.

    6. COMPUTE 3.14 = PI.

  7. Do the following pairs of operations perform the same function?

    1. COMPUTE SUM-1 = 0.

      MOVE ZEROS TO SUM-1.

    2. COMPUTE AMOUNT = AMOUNT - 2.

      SUBTRACT 2 FROM AMT.

    3. COMPUTE X = A * B − C * D.

      COMPUTE X = (A * B) -(C * D).

    4. COMPUTE Y = A − B * C - D.

      COMPUTE Y = (A − B) * (C − D).

  8. Using a COMPUTE statement, find the average of EXAM1, EXAM2, and EXAM3.

  9. Using a COMPUTE statement, find total wages = rate × 40 + (1.5 × rate × overtime hours). Two fields are supplied: RATE and HOURS-WORKED. Overtime hours are hours worked in excess of 40 hours. (Assume everyone works at least 40 hours.)

  10. Indicate the errors, if any, in the following two statements.

    1. ADD '12' TO TOTAL.

    2. ADD TAX TO TOTAL

      GIVING AMOUNT.

  11. Write a routine to find Y = (A + B)2 / X.

  12. Determine what, if anything, is wrong with the following statements.

    1. SUBTRACT A FROM 87.3 GIVING B.

    2. ADD A, 10.98, B TO 100.3.

    3. ADD AMT. TO TOTAL GIVING TAX.

    4. DIVIDE A BY B AND MULTIPLY B BY C.

    5. COMPUTE X = Y + Z ROUNDED.

  13. Use a COMPUTE statement to add 1 to A.

  14. Indicate whether the following is correct.

    SUBTRACT AMOUNT1 FROM AMOUNT2, AMOUNT3 GIVING AMOUNT4

  15. Determine the number of feet in X inches, placing the quotient in FEET and the remainder in INCHES.

  16. Add the values of FRI, SAT, and SUN, and place the sum in WEEK-END.

  17. Add the values of AMOUNT1, AMOUNT2, and AMOUNT3 to TOTAL.

  18. Decrease the value of AMOUNTX by 47.5.

  19. Divide the TOTAL-TUITION by 15 to determine TUITION-PER-CREDIT.

  20. Fill in the dashes for the following.

GENERAL QUESTIONS

DEBUGGING EXERCISES

Consider the following arithmetic statements.

  1. ADD AMOUNT1 TO FINAL-TOTAL.

  2. ADD AMOUNT1 TO AMOUNT2 GIVING AMOUNT3.

  3. COMPUTE AVERAGE = AMOUNT1 + AMOUNT2 / 2

  4. COMPUTE AMOUNT4 = AMOUNT1 + AMOUNT2 ROUNDED.

  5. MULTIPLY AMOUNT1 BY AMOUNT2.

  6. DIVIDE AMOUNT1 BY 2.

  7. MULTIPLY AMOUNT4 TIMES AMOUNT3.

  1. Which statements will produce syntax errors? Correct these.

  2. On line 4, will a correct average of AMOUNT1 and AMOUNT2 be computed? If your answer is no, make whatever changes you think are necessary to obtain the correct results.

  3. For line 5, suppose the PIC clause of AMOUNT1 is 99V99. AMOUNT2 has a PIC clause of 9 (4) V99. Under what conditions will a logic error result? What can you do to prevent such an error?

  4. Assume that all the syntax and logic errors have been corrected on lines 1 through 7 and that the preceding steps are executed in sequence. What will be the results in the following fields: AMOUNT1; AMOUNT2; AMOUNT3; AMOUNT4; and AVERAGE?

PRACTICE PROGRAM

The purpose of this program is to read each student's record from the Student Master File, calculate the student's average grade, and print a Class Grade Report. When calculating the average grade, round the results to the nearest integer (e.g., 89.5 = 90). Also, the report is to print the average grade for all students. The problem definition is presented below.

Systems flowchart

PRACTICE PROGRAM

Record description layout for student grade file

Field Description

Type

Size

COBOL Field-name

Student Number

S

5,0

SG-STUDENT-NUMBER

Student Name

A

20

SG-STUDENT-NAME

Exam 1 Mark

P

3,0

SG-EXAM-1-MARK

Exam 2 Mark

P

3,0

SG-EXAM-2-MARK

Exam 3 Mark

P

3,0

SG-EXAM-3-MARK

Exam 4 Mark

P

3,0

SG-EXAM-4-MARK

Printer spacing chart for student grade report

PRACTICE PROGRAM

Structured Pseudocode

PRACTICE PROGRAM

PROGRAMMING ASSIGNMENTS

  1. Write a program to read the Payroll Master File and print a Payroll Increases Report. The report is to show the employee increases as follows.

    1. Each employee's salary is to be increased by 7%.

    2. The union dues have increased by 4%.

    3. The insurance has increased by 3%.

      The problem definition is shown below.

    Systems flowchart

    PROGRAMMING ASSIGNMENTS

    Record description layout for payroll master file

    Field Description

    Type

    Size

    COBOL Field-name

    Employee Number

    S

    5,0

    PM-EMPLOYEE-NUMBER

    Employee Name

    A

    20

    PM-EMPLOYEE-NAME

    Annual Salary

    P

    7,0

    PM-ANNUAL-SALARY

    Union Dues

    P

    5,2

    PM-UNION-DUES

    Insurance

    P

    5,2

    PM-INSURANCE

    Printer spacing chart for payroll increases report

    PROGRAMMING ASSIGNMENTS
  2. For each customer loan approved at Dollars-and-Sense Bank, a record should be printed indicating the monthly payment for that customer. The program specifications are as follows.

    The monthly payment on an N-year loan with a principal of P at a yearly interest rate of R is

    Monthly Payment = P * (R/12) - (P * (R/12)/1–(1+R/12)12*n)

    For example, What are the monthly payments on a twenty-year loan of $20,000 at 12%?

    P = 20000

    R = .12

    N = 20 years

    Monthly payment = 20000 * (.12/12) − (20000 * (.12/12) / (1 − (1.01) ** 240))

    = 20000 * (.01) − (20000 − .01 / (1 − (1.01) ** 240))

    = 200 − (−20.22)

    = 220.22

    Round monthly payments to the nearest penny.

    Systems flowchart

    PROGRAMMING ASSIGNMENTS

    Record description layout for customer loan file

    Field Description

    Type

    Size

    COBOL Field-name

    Customer Name

    A

    20

    CL-CUSTOMER-NAME

    Loan Amount

    P

    5,0

    CL-LOAN-AMOUNT

    Yearly Interest Rate

    P

    4,4

    CL-YEARLY-INTEREST-RATE

    Length of Loan in Years

    P

    2,0

    CL-LENGTH-OF-LOAN

    Printer spacing chart for customer loan report

    PROGRAMMING ASSIGNMENTS
  3. The Smooth-Ride Taxi Company has a fleet of taxis. The manager wants to determine the energy efficiency of each taxi in the fleet as well as the efficiency of the entire fleet. Write the program that will read the Vehicle Efficiency file and print a report that indicates the miles per gallon for each taxi and for the fleet as a whole.

    Record description layout for vehicle efficiency file

    Field Description

    Type

    Size

    COBOL Field-name

    Vehicle Identification

    A

    10

    VE-VEHICLE-ID

    Vehicle Description

    A

    10

    VE-VEHICLE-DESCRIPTION

    Miles Traveled

    P

    5,0

    VE-MILES-TRAVELED

    Gallons of Gas Used

    P

    5,2

    VE-GALLONS-USED

    Printer spacing chart for vehicle efficiency report

    PROGRAMMING ASSIGNMENTS
  4. Write a program that will read the Item Inventory File and print a Selling Price Report. The program specifications are as follows.

Record description layout for item inventory file

Field Description

Type

Size

COBOL Field-name

Item Number

S

2,0

II-ITEM-NUMBER

Item Description

A

20

II-ITEM-DESCRIPTION

Item Cost

P

5,2

II-ITEM-COST

Quantity in Stock

P

3,0

II-QUANTITY-IN-STOCK

Calculations: Total Value = Item Cost * Quantity in Stock
Item Selling Price = Item Cost + (30% of Item Cost)

Printer spacing chart for item selling price report

PROGRAMMING ASSIGNMENTS
..................Content has been hidden....................

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