Teach Yourself COBOL in 21 days, Second Edition

Previous chapterNext chapterContents


- Day 6 -
Using Data and COBOL Operators

One truth about COBOL is that you will never learn everything about the data used by a program and the DATA DIVISION. Each day's lesson gives you enough of a grasp of the DATA DIVISION that you can work comfortably with data. Today, you dive back into the DATA DIVISION and learn about the following topics:

Initializing Variables

When you define a variable in WORKING-STORAGE, you also can assign it an initial value. This is a convenient method of setting variables to start with a known value.

Variables are initialized with a VALUE IS clause, as shown in lines 000900 and 001000 of Listing 6.1. Note that the period closing the variable definition is at the end of the initializer, so the sequence is the level number, the variable name, PICTURE IS (or PIC), the picture, VALUE IS, the initializer, and finally the period.

TYPE: Listing 6.1. Initializing a variable in WORKING-STORAGE.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. JACK04.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500
000600 WORKING-STORAGE SECTION.
000700
000800 01  THE-MESSAGE      PIC X(50).
000900 01  THE-NUMBER       PIC 9(2) VALUE IS 1.
001000 01  A-SPACE          PIC X    VALUE IS " ".
001100
001200 PROCEDURE DIVISION.
001300 PROGRAM-BEGIN.
001400
001500* Set up and display line 1
001600     MOVE "Jack be nimble," TO THE-MESSAGE.
001700     DISPLAY
001800         THE-NUMBER
001900         A-SPACE
002000         THE-MESSAGE.
002100
002200* Set up and Display line 2
002300     ADD 1 TO THE-NUMBER.
002400     MOVE "Jack be quick," TO THE-MESSAGE.
002500     DISPLAY
002600         THE-NUMBER
002700         A-SPACE
002800         THE-MESSAGE.
002900
003000* Set up and display line 3
003100     ADD 1 TO THE-NUMBER.
003200     MOVE "Jack jump over the candlestick." TO THE-MESSAGE.
003300     DISPLAY
003400         THE-NUMBER
003500         A-SPACE
003600         THE-MESSAGE.
003700
003800 PROGRAM-DONE.
003900     STOP RUN.
004000
004100

The word IS in a value clause is optional; the initialization could be written as the following:

01  THE-NUMBER            PIC 9(2) VALUE 1.

Compare Listing 6.1 to Listing 2.10 in Day 2, "Using Variables and Constants." Notice that using the initializers in WORKING-STORAGE has eliminated the need for two of the MOVE statements, at lines 001600 and 001900, in the PROCEDURE DIVISION.

If you want a variable to have a default value that will be used in the program, you must initialize it in WORKING-STORAGE. A variable that is not initialized has an undefined value until something is moved to it.

An undefined value is one that can contain any value.

For numeric variables, this can become a problem. If you attempt to use the DISPLAY (ADD 1) statement with a numeric variable that contains an undefined value, you probably will produce an error. This does not cause a compiler error, but usually causes an error while the program is running. The program usually aborts with a message such as this:

ATTEMPT TO PERFORM ARITHMETIC WITH NON-NUMERIC DATA

or

VARIABLE THE-NUMBER DOES NOT CONTAIN NUMERIC DATA

Initializing a variable in WORKING-STORAGE has the same effect as a MOVE to the variable. If the initializing value is shorter than the PICTURE of an alphanumeric field, the field is padded on the right with spaces. If the initializing value is too small for a numeric variable, the variable is padded on the left with zeroes.

Listing 6.2, jack05.cbl, takes initialization one step further by initializing all the variables ready to print the first line of the poem.

TYPE: Listing 6.2. Short initializers.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. JACK05.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500
000600 WORKING-STORAGE SECTION.
000700
000800 01  THE-MESSAGE      PIC X(50)
000900     VALUE "Jack be nimble,".
001000
001100 01  THE-NUMBER       PIC 9(2) VALUE IS 1.
001200 01  A-SPACE          PIC X    VALUE IS " ".
001300
001400 PROCEDURE DIVISION.
001500 PROGRAM-BEGIN.
001600
001700* Line 1 is set up, so just display it
001800     DISPLAY
001900         THE-NUMBER
002000         A-SPACE
002100         THE-MESSAGE.
002200
002300* Set up and Display line 2
002400     ADD 1 TO THE-NUMBER.
002500     MOVE "Jack be quick," TO THE-MESSAGE.
002600     DISPLAY
002700         THE-NUMBER
002800         A-SPACE
002900         THE-MESSAGE.
003000
003100* Set up and display line 3
003200     ADD 1 TO THE-NUMBER.
003300     MOVE "Jack jump over the candlestick." TO THE-MESSAGE.
003400     DISPLAY
003500         THE-NUMBER
003600         A-SPACE
003700         THE-MESSAGE.
003800
003900 PROGRAM-DONE.
004000     STOP RUN.
004100

The output from all three versions of JACK is identical.

OUTPUT:

C>

01 Jack be nimble,
02 Jack be quick,
03 Jack jump over the candlestick.

C>

ANALYSIS: The definition for the variable, THE-MESSAGE, is at lines 000800 and 000900. The definition is broken up into two lines. The 01 level starts in Area A, but only the level number of the variable is required to start in Area A. The remainder of the definition (the variable name, picture, and value) falls within Area B (columns 12 through 72).

The initializer for THE-MESSAGE--in this case, "Jack be nimble"--is clearly too short for the PICTURE, and the remainder of THE-MESSAGE is filled with spaces by the compiler when it encounters the VALUE clause. Similarly, THE-NUMBER is initialized with a 1, and the compiler fills the variable space with 01 when it encounters the VALUE IS clause.

Note that initializing a variable with a VALUE in WORKING-STORAGE is the same as using MOVE to give it a value. Thereafter, you can use MOVE to assign values to the variable later in the program. THE-MESSAGE, initialized at lines 000800 and 000900, is modified by a MOVE at line 002500 and again later at line 003300.

SPACES and ZEROES

Variables that are not initialized contain undefined values until a MOVE moves something to them. It is a good practice to initialize variables in WORKING-STORAGE. The usual practice is to initialize numeric variables to zero and alphanumeric variables to spaces. COBOL has provided reserved words for this, primarily to make clearer what is happening.

Both of the following initializations do the job. Remember that an initializer works like a MOVE, padding the remainder of the variable with spaces or zeroes. Therefore, moving a single space to an alphanumeric variable is the same as filling it with spaces, as you see here:

01  THE-MESSAGE     PIC X(50) VALUE " ".
01  THE-NUMBER      PIC 9(4)  VALUE 0.

Instead of a quoted space (which isn't clear), or a 0 (zero) that can be confused with the letter O, COBOL has reserved the words SPACE, SPACES, ZERO, ZEROS, and ZEROES to represent these values. This initialization is clearer:

01  THE-MESSAGE     PIC X(50) VALUE SPACES.
01  THE-NUMBER      PIC 9(4)  VALUE ZEROES.

SPACE and SPACES both mean "fill with spaces." ZERO, ZEROS, and ZEROES all mean "fill with zeroes." The singular and plural versions produce the identical effect. SPACE is the same as SPACES, and ZERO is the same as ZEROS and ZEROES.

SPACES and ZEROES also can be used in MOVE commands, like this:

MOVE SPACES TO THE-MESSAGE.
MOVE ZERO TO THE-NUMBER.


DO/DON'T:
DO
initialize variables in the DATA DIVISION when they are defined, or in the PROCEDURE DIVISION before they are used.

DON'T perform any arithmetic functions on an uninitialized numeric variable.


Truncated Values

A truncated value occurs when a value that is too large for a numeric variable is moved to the numeric variable, or when a value that is too long for an alphanumeric variable is moved to the alphanumeric variable.

The compiler conveniently fills variables with blanks or zeroes when short or small values are moved to them, or when short or small values are used to initialize them. What happens when a value that is too large or too long is moved to a variable or is used to initialize a variable?

The short answer is that you lose some data. What you lose depends on the type of variable that is the target of the MOVE. An alphanumeric variable truncates the right end of the value until the value fits in the variable. A numeric variable truncates the left end of the value until the value fits. (There is an exception to this for decimal values, which you will learn about in "Decimal Data," later in this chapter.)

Listing 6.3 illustrates the effect of truncation on variables. It moves a message to successively smaller alphanumeric variables, and a numeric value to successively smaller numeric variables. All the resulting values are displayed.

TYPE: Listing 6.3. Truncating variables.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. TRUNC01.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500 WORKING-STORAGE SECTION.
000600
000700 01  6-BYTES      PIC X(6).
000800 01  5-BYTES      PIC X(5).
000900 01  4-BYTES      PIC X(4).
001000 01  3-BYTES      PIC X(3).
001100 01  2-BYTES      PIC X(2).
001200 01  1-BYTE       PIC X(1).
001300
001400 01  5-DIGITS     PIC 9(5).
001500 01  4-DIGITS     PIC 9(4).
001600 01  3-DIGITS     PIC 9(3).
001700 01  2-DIGITS     PIC 9(2).
001800 01  1-DIGIT      PIC 9(1).
001900
002000 PROCEDURE DIVISION.
002100 PROGRAM-BEGIN.
002200
002300     MOVE "Hello" TO 6-BYTES.
002400     MOVE "Hello" TO 5-BYTES.
002500     MOVE "Hello" TO 4-BYTES.
002600     MOVE "Hello" TO 3-BYTES.
002700     MOVE "Hello" TO 2-BYTES.
002800     MOVE "Hello" TO 1-BYTE.
002900
003000     MOVE 2397 TO 5-DIGITS.
003100     MOVE 2397 TO 4-DIGITS.
003200     MOVE 2397 TO 3-DIGITS.
003300     MOVE 2397 TO 2-DIGITS.
003400     MOVE 2397 TO 1-DIGIT.
003500
003600     DISPLAY 6-BYTES.
003700     DISPLAY 5-BYTES.
003800     DISPLAY 4-BYTES.
003900     DISPLAY 3-BYTES.
004000     DISPLAY 2-BYTES.
004100     DISPLAY 1-BYTE.
004200
004300     DISPLAY 5-DIGITS.
004400     DISPLAY 4-DIGITS.
004500     DISPLAY 3-DIGITS.
004600     DISPLAY 2-DIGITS.
004700     DISPLAY 1-DIGIT.
004800
004900
005000 PROGRAM-DONE.
005100     STOP RUN.
005200

The output of trunc01.cbl shows characters being lopped off the right side of Hello and digits being lopped off the left side of 2397:

OUTPUT:

Hello
Hello
Hell
Hel
He
H
02397
2397
397
97
7


C>
C>

You might find when you compile trunc01.cbl that the compiler will return warnings about truncation. Many compilers will provide warnings on the numeric moves to 3-DIGITS, 2-DIGITS, and 1-DIGIT. This usually is something like the following:

HIGH ORDER DIGIT TRUNCATION MAY OCCUR IN MOVE AT LINE 003200

A few compilers give warnings on the alphanumeric truncation in the moves to 4-BYTES, 3-BYTES, 2-BYTES, and 1-BYTE:

VALUE MAY BE TRUNCATED IN MOVE AT LINE 002500

It is more common to warn about numeric truncation because it usually has more serious effects on the outcome of a program. Numeric values in a program are usually used somewhere in a calculation, and a truncation can produce errors that are not easily visible.

Listing 6.4, trunc02.cbl, demonstrates the truncation of values by initializing the variables with values that are too large or too long. You might find that trunc02.cbl will not even compile with your compiler. Truncation in initializers in WORKING-STORAGE is treated more severely than a truncation in a MOVE statement, and this listing might produce one or more errors and fail to compile. This program will not compile with the Microfocus Personal COBOL compiler and generates the error "VALUE literal too large. Literal truncated." for lines 000900 through 001200. It also generates the error "VALUE too long for data item or has too many decimal positions." for lines 001600 through 001800. The ACUCOBOL compiler provides the more general error "VALUE size error" for the same lines.

TYPE: Listing 6.4. Truncation in initializers.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. TRUNC02.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500 WORKING-STORAGE SECTION.
000600
000700 01  6-BYTES      PIC X(6) VALUE "Hello".
000800 01  5-BYTES      PIC X(5) VALUE "Hello".
000900 01  4-BYTES      PIC X(4) VALUE "Hello".
001000 01  3-BYTES      PIC X(3) VALUE "Hello".
001100 01  2-BYTES      PIC X(2) VALUE "Hello".
001200 01  1-BYTE       PIC X(1) VALUE "Hello".
001300
001400 01  5-DIGITS     PIC 9(5) VALUE 2397.
001500 01  4-DIGITS     PIC 9(4) VALUE 2397.
001600 01  3-DIGITS     PIC 9(3) VALUE 2397.
001700 01  2-DIGITS     PIC 9(2) VALUE 2397.
001800 01  1-DIGIT      PIC 9(1) VALUE 2397.
001900
002000 PROCEDURE DIVISION.
002100 PROGRAM-BEGIN.
002200
002300
002400     DISPLAY 6-BYTES.
002500     DISPLAY 5-BYTES.
002600     DISPLAY 4-BYTES.
002700     DISPLAY 3-BYTES.
002800     DISPLAY 2-BYTES.
002900     DISPLAY 1-BYTE.
003000
003100     DISPLAY 5-DIGITS.
003200     DISPLAY 4-DIGITS.
003300     DISPLAY 3-DIGITS.
003400     DISPLAY 2-DIGITS.
003500     DISPLAY 1-DIGIT.
003600
003700
003800 PROGRAM-DONE.
003900     STOP RUN.
004000

If trunc02.cbl does compile, its output is the same as the output of trunc01.cbl.

Multiple MOVE Statements

A MOVE verb can be used to move the same value to multiple targets. Here is the syntax:

MOVE source TO destination destination destination . . . .

Listing 6.5, trunc03.cbl, uses multiple moves to achieve the same result as trunc01.cbl. (Listing 6.5 only illustrates the convenience of using a multiple MOVE. It isn't a useful program.)

TYPE: Listing 6.5. Using multiple MOVE statements.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. TRUNC03.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500 WORKING-STORAGE SECTION.
000600
000700 01  6-BYTES      PIC X(6).
000800 01  5-BYTES      PIC X(5).
000900 01  4-BYTES      PIC X(4).
001000 01  3-BYTES      PIC X(3).
001100 01  2-BYTES      PIC X(2).
001200 01  1-BYTE       PIC X(1).
001300
001400 01  5-DIGITS     PIC 9(5).
001500 01  4-DIGITS     PIC 9(4).
001600 01  3-DIGITS     PIC 9(3).
001700 01  2-DIGITS     PIC 9(2).
001800 01  1-DIGIT      PIC 9(1).
001900
002000 PROCEDURE DIVISION.
002100 PROGRAM-BEGIN.
002200
002300     MOVE "Hello" TO 6-BYTES 5-BYTES
002400                     4-BYTES 3-BYTES
002500                     2-BYTES 1-BYTE.
002600
002700     MOVE 2397 TO 5-DIGITS
002800                  4-DIGITS
002900                  3-DIGITS
003000                  2-DIGITS
003100                  1-DIGIT.
003200
003300     DISPLAY 6-BYTES.
003400     DISPLAY 5-BYTES.
003500     DISPLAY 4-BYTES.
003600     DISPLAY 3-BYTES.
003700     DISPLAY 2-BYTES.
003800     DISPLAY 1-BYTE.
003900
004000     DISPLAY 5-DIGITS.
004100     DISPLAY 4-DIGITS.
004200     DISPLAY 3-DIGITS.
004300     DISPLAY 2-DIGITS.
004400     DISPLAY 1-DIGIT.
004500
004600
004700 PROGRAM-DONE.
004800     STOP RUN.
004900

Decimal Data

So far, all the numbers you've worked with have been positive whole numbers (integers), but COBOL is a business language, which should be able to deal with decimal numbers, dollars and cents, and percentages.

In order to put a decimal point in a number, you must put a decimal point in the PICTURE of a variable. The character in a numeric PICTURE that represents a decimal point is an uppercase V.

The following variable holds values ranging from 000.00 to 999.99.

01  THE-VALUE       PIC 999V99.

Any constant values that you move to a decimal variable or use to initialize a decimal variable are written in conventional format, as in these examples:

01  THE-VALUE       PIC 999V99 VALUE 19.24.
01  THE-VALUE       PIC 999V99 VALUE ZERO.
MOVE 26.15 TO THE-VALUE.

If you attempt to move a value containing too many decimals, the number is truncated on the right, and some of the decimal information will be lost. In this example, THE-VALUE ends up containing 467.23:

MOVE 467.237 TO THE-VALUE.

Truncation still takes place from the high end as well. In this example, THE-VALUE ends up containing 923.46 because the number is truncated on both the left and the right:

MOVE 6923.468 TO THE-VALUE.


WARNING: I have stressed truncation in numbers because of the effect it can have on calculations. It is important to plan the size of numeric variables so that they are large enough to hold the largest possible values that may occur during the program.

Positive and Negative Numbers

COBOL numbers can also contain a positive or negative sign. The PICTURE character for a sign is an initial S. The S must be the first character in the picture.

The following variable holds values ranging from -999.99 to +999.99.

01  THE-VALUE       PIC S999V99.

The following variable holds values ranging from -9999 to +9999.

01  THE-VALUE       PIC S9999.

The abbreviations used in a picture still can be used in a numeric picture containing a sign or a decimal. For example, the following two variable definitions will produce the same size and type of variable.

01   THE-VALUE      PIC S999999V9999.
01   THE-VALUE      PIC S9(6)V9(4).

It looks like some sort of strange code, but it is simple to decipher if you remember that any number in parentheses in a PICTURE is a signal to repeat the preceding character the number of times in parentheses. So 9(6) expands to 999999 and 9(4) expands to 9999.

Displaying Decimals and Signs

In COBOL, numbers that will be displayed are treated differently from numbers that are used for calculations. COBOL was designed to do a lot of number calculating (addition, subtraction, multiplication, and division). Numbers that contain an S for a sign (positive or negative) or a V for a decimal are stored in memory in a special format that speeds up calculations. However, this format does not display correctly.

The designers of COBOL recognized the need to include in the design of the language a way to display numeric values. After all, the output of a program isn't much good if a user can't understand it.

The idea behind the design is that all calculations are performed with numeric variables (variables whose pictures contain only numbers, an S for a sign, and a V for a decimal). After the calculations are complete, the resulting value is moved to a display variable, and the display variable is put on-screen through a DISPLAY statement.

A numeric variable stipulated by a DISPLAY statement uses different PICTURE characters for the sign and the decimal.

The PICTURE character for a sign in a numeric variable that will be used for a DISPLAY is the minus sign (-). The PICTURE character for a decimal in a numeric variable that will be used for DISPLAY is the decimal point or period.

The following variable holds the values -999.99 through 999.99 for display purposes:

01   DISPLAY-VALUE       PIC -999.99.

The display sign (-) displays only when the value is negative. If DISPLAY-VALUE contains -46.17, it displays as the following:

-046.17

However, the number 55.03 displays as follows:

055.03

A program performing calculation and display might contain WORKING-STORAGE and code as in Listing 6.6. In practice, a sales commission usually would not be negative (unless the salesperson generated a pile of refunds), but the example does show the difference between the PICTURE of a signed value used for calculation at line 000800 and the PICTURE of a signed value used for display at line 001300.

TYPE: Listing 6.6. Using numeric and display variables.

000700 WORKING-STORAGE SECTION.
000800 01    SALES-TOTAL             PIC S9(5)V99  VALUE 44707.66.
000900 01    COMMISSION-PERCENT      PIC 99        VALUE 11.
001000 01    PERCENT-AS-DECIMAL      PIC V99.
001100 01    THE-COMMISSION          PIC S9(5)V99  VALUE ZERO.
001200
001300 01    DISPLAY-COMMISSION      PIC -9(5).99.
......
002500* Divide commission by 100 to convert to decimal
002600     COMPUTE PERCENT-AS-DECIMAL =
002700       COMMISSION-PERCENT / 100.
002800
002900     COMPUTE THE-COMMISSION =
003000       PERCENT-AS-DECIMAL * SALES-TOTAL.
003100
003200     MOVE THE-COMMISSION TO DISPLAY-COMMISSION.
003300
003400     DISPLAY "The Commission is "
003500       DISPLAY-COMMISSION.

The - also can be placed at the end of the picture rather than at the beginning. It is fairly common in business programs to see display values specified as follows:

01   THE-DISPLAY-VALUE             PIC 999999.99-.

Suppressing Leading Zeroes

You can suppress leading zeroes to improve the display of a number. In the previous example, if -55.17 is moved to THE-DISPLAY-VALUE and then displayed, it appears on the screen as the following:

000055.17-

In a display variable, you can suppress the display of leading zeroes, using Z to replace 9 in the picture of the variable. Here is an example:

01   THE-DISPLAY-VALUE             PIC ZZZZZ9.99-.

When entered like this, a value of -54.27 moved to THE-DISPLAY-VALUE displays as the following:

54.27-

Leading zeroes are suppressed by the Z in the PICTURE statement.

Using a PICTURE of ZZZZZ9.99- enables the value 0 to display as this:

0.00

If you suppress all zeroes with a PICTURE of ZZZZZZ.ZZ-, a value of 0 displays as a blank because all zeroes are suppressed.

Commas can be inserted in the picture to provide commas in the final display, like this:

01   DISPLAY-COMMISSION       PIC ZZ,ZZ9.99-.

A value of 12345.67 moved to DISPLAY-COMMISSION displays as the following:

12,345.67

New Term: The minus sign (-), decimal point (.), comma (,) and the character Z are called editing characters. A numeric variable that contains an editing character is called an edited numeric variable. Edited numeric variables should be used only to display values and should not be used in calculations. There are other editing characters, but these are the main ones.


WARNING: Editing characters should never be mixed with S or V in a PICTURE. PIC S99.99 and PIC -ZZV99 are illegal PICTUREs, and your compiler will generate an error if you try to create a PICTURE that mixes the two types.

Before you leap into writing a program that uses decimal or signed data, you need to know how to enter signed and decimal data using ACCEPT. Numeric data that is entered into a computer probably will be entered by the user with editing characters, such as a plus sign or a minus sign, a decimal point, and commas.

If you ACCEPT values into a numeric field, such as a PIC 9(6)V99, characters such as signs and commas entered by the user will be invalid. In order to allow the user to enter digits and editing characters, it is necessary to use ACCEPT to accept values into an edited numeric variable.

The easiest way to create a PICTURE for a field into which this type of numeric data will be accepted is to make it as large as possible by including all possible editing characters. If you want to allow the user to enter a number as large as 999,999.99 with a sign, the picture for the field should be PIC -ZZZ,ZZZ.ZZ. This PICTURE allows the user to enter all possible editing characters including commas, a sign, and a decimal point. You also could use the following:

01  ENTRY-FIELD                    PIC ZZZ,ZZZ.ZZ-.

When a display variable is used as a data entry field with ACCEPT, the PICTURE of the variable does not control what the user can enter. For example, it doesn't matter whether the minus sign (-) is placed at the beginning or the end of the PICTURE statement. The user still can enter a minus in a leading or trailing position. When an ACCEPT of ENTRY-FIELD is used in a program, the ACCEPT verb uses the size of the PICTURE, 11 characters (eight characters, a comma, a minus sign, and a decimal point), to determine how many characters the user is allowed to enter and assumes that the user will be entering digits, and possibly a sign, commas and/or a decimal point as the input.

After the user enters data and presses Enter, the ACCEPT verb looks at the 11 (or fewer) characters and tries to sort out the digits, minus signs, commas, or decimal points. It turns the result into a number that can be moved to a true numeric variable.

Unfortunately, the following three different versions of ACCEPT can be used for numeric entry:

ACCEPT ENTRY-FIELD.
ACCEPT ENTRY-FIELD WITH CONVERSION.
ACCEPT ENTRY-FIELD CONVERT.

Micro Focus Personal COBOL uses the first version. ACUCOBOL uses the second and third versions; VAX COBOL use the second; and LPI COBOL uses the third. You have to consult your COBOL manual to check which one your version uses.


NOTE: The listings in today's lesson use ACCEPT ENTRY-FIELD because this code was compiled and tested using a Micro Focus compiler. The other versions are commented out in the code. You can change the one you use to fit your compiler.

Code, compile, and run Listing 6.7, entering various values to get an idea how the formatting works. You might want to try editing the program to add additional formats or to try out longer fields.

TYPE: Listing 6.7. Edited formats.

000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. NUMS01.
000300*------------------------------------------------
000400* Illustrates how decimal data is displayed
000500* when edited.
000600*------------------------------------------------
000700 ENVIRONMENT DIVISION.
000800 DATA DIVISION.
000900 WORKING-STORAGE SECTION.
001000
001100 01  ENTRY-FIELD    PIC -ZZZ,ZZZ.ZZ.
001200 01  THE-VALUE      PIC S999999V99.
001300
001400 01  EDITED-DISPLAY-1      PIC -999999.99.
001500 01  EDITED-DISPLAY-2      PIC ZZZZZ9.99-.
001600 01  EDITED-DISPLAY-3      PIC ZZZZZZ.ZZ-.
001700 01  EDITED-DISPLAY-4      PIC ZZZ,ZZZ.ZZ-.
001800
001900 PROCEDURE DIVISION.
002000 PROGRAM-BEGIN.
002100
002200     DISPLAY "PLEASE ENTER A VALUE".
002300     ACCEPT ENTRY-FIELD.
002400*or  ACCEPT ENTRY-FIELD CONVERT.
002500*or  ACCEPT ENTRY-FIELD WITH CONVERSION.
002600     MOVE ENTRY-FIELD TO THE-VALUE.
002700
002800     MOVE THE-VALUE TO EDITED-DISPLAY-1
002900                       EDITED-DISPLAY-2
003000                       EDITED-DISPLAY-3
003100                       EDITED-DISPLAY-4.
003200
003300     DISPLAY ENTRY-FIELD      "|"
003400             EDITED-DISPLAY-1 "|"
003500             EDITED-DISPLAY-2 "|"
003600             EDITED-DISPLAY-3 "|"
003700             EDITED-DISPLAY-4 "|".
003800
003900     IF THE-VALUE NOT = ZERO
004000         GO TO PROGRAM-BEGIN.
004100
004200 PROGRAM-DONE.
004300     STOP RUN.
004400

The output of nums01.cbl shows the results of various numeric entry values. The user input is shown in boldface type. Entry stops when you enter zero.

OUTPUT:

PLEASE ENTER A VALUE
-1
-      1.00|-000001.00|     1.00-|     1.00-|      1.00-|
PLEASE ENTER A VALUE
234,56
23,456.00| 023456.00| 23456.00 | 23456.00 | 23,456.00 |
PLEASE ENTER A VALUE
10606-
- 10,606.00|-010606.00| 10606.00-| 10606.00-| 10,606.00-|
PLEASE ENTER A VALUE
123.45
123.45| 000123.45|   123.45 |   123.45 |    123.45 |
PLEASE ENTER A VALUE
1234.5
1,234.50| 001234.50|  1234.50 |  1234.50 |  1,234.50 |
PLEASE ENTER A VALUE
-1678.98
-  1,678.98|-001678.98|  1678.98-|  1678.98-|  1,678.98-|
PLEASE ENTER A VALUE

ANALYSIS: The code in Listing 6.7 allows data entry to be accepted into a display variable field at line 002300 and then moves it to a calculation field. From there, it is moved to several different edited numeric fields. The original entry and the different versions of the edited numeric fields are displayed.

COBOL Numeric Operations

You already have worked with several COBOL numeric operators; now it is time to round them up in one section.

The COBOL COMPUTE verb is a general-purpose verb that can be used to calculate results. Arithmetic expressions in the COMPUTE verb use the arithmetic operators: + (addition), - (subtraction), * (multiplication), and / (division). You can use parentheses to affect the order in which operations are performed.

When parentheses appear in an expression, the value within the innermost parentheses is evaluated first. Assuming that THE-VALUE contains 100 and THE-PERCENT contains .25, these are the steps for evaluating the sample compute statement:

1. COMPUTE THE-RESULT = ( (THE-VALUE * THE-PERCENT) + 14) / 6

2. COMPUTE THE-RESULT = ( (25) + 14) /6

3. COMPUTE THE-RESULT = (39) / 6

4. COMPUTE THE-RESULT = 6.5

The COMPUTE verb has two optional clauses: ROUNDED and ON SIZE ERROR. ROUNDED rounds the result up or down as necessary, based on the results of the calculation. The ON SIZE ERROR logic is performed if the result is larger than the variable that is used to store the result.

The statement that follows ON SIZE ERROR also is executed if a COMPUTE statement attempts to do something impossible, such as divide by zero. Dividing by zero causes a lot of problems for a computer. It is an error that can occur in a COMPUTE statement that uses division (/), or one that uses the DIVIDE verb (which is covered later in today's lesson).

In the following syntax, clauses in brackets ([]) are optional. In a COMPUTE statement, the result is stored in the variable on the left of the equals (=) sign, like this:

COMPUTE numeric variable
    [ROUNDED] =
    arithmetic expression
    [ ON SIZE ERROR
      do something else ]

In the following examples, the first COMPUTE statement uses all of the options.

COMPUTE THE-RESULT
    ROUNDED =
    (BASE-VALUE * 10) +
    (A-VALUE / 50)
    ON SIZE ERROR
    DISPLAY "Warning Size error."

COMPUTE THE-RESULT = 12 * 15.
COMPUTE THE-RESULT
    ROUNDED =
    (BASE-VALUE * 10) / 1.5.

A divide-by-zero error might occur in a program that calculated the sales dollars generated per day per salesperson by dividing a salesperson's monthly total sales revenue by the number of days worked that month. If one of the sales staff were off all month because of a serious illness, but some income came in that month from a previous month's sale, trying to compute the dollars per day would cause a divide-by-zero error.

COMPUTE DOLLARS-PER-DAY = MONTH-DOLLARS / DAYS-WORKED.

A program containing this COMPUTE statement would crash if DAYS-WORKED equals 0. An ON SIZE ERROR traps this condition and displays an error, so that the program can continue:

002600     COMPUTE DOLLARS-PER-DAY =
002700       MONTH-DOLLARS / DAYS-WORKED
002800        ON SIZE ERROR
002900         DISPLAY "Division by zero error".

The ADD verb is available in two versions. Both versions have options similar to the COMPUTE verb. In the first, a value (which can be a constant or a variable) is added to second value (which must be a variable). The result is stored in the variable, like this:

ADD value TO variable
    [ROUNDED]
    [ ON SIZE ERROR
    do something ]

In each of the following examples, the result of the addition is stored in THE-VALUE:

ADD 1.17 TO THE-VALUE.
ADD A-VALUE TO THE-VALUE
    ROUNDED.
ADD 1.17 TO THE-VALUE
    ROUNDED
    ON SIZE ERROR
    DISPLAY "Add - overflow"

In the second version, two values are added together and the reserved word GIVING is used to indicate a variable into which the result is stored. The values can be constants or variables.

ADD value TO value
    GIVING variable [ROUNDED]
    [ ON SIZE ERROR
    do something ]

In each example, the result of the addition is stored in THE-SUM, as shown here:

ADD 17.5 TO THE-VALUE
    GIVING THE-SUM ROUNDED
    ON SIZE ERROR
    DISPLAY "Add - overflow"
ADD 17.5 TO 22.7
    GIVING THE-SUM
ADD A-VALUE TO THE-VALUE
    GIVING THE-SUM
    ON SIZE ERROR
    DISPLAY "Add - overflow"

Subtraction is handled by the SUBTRACT verb, and it comes in the following two versions that are similar to ADD. The second version of SUBTRACT also uses GIVING.

SUBTRACT value
    FROM variable [ROUNDED]
    [ ON SIZE ERROR
    do something ]
SUBTRACT value FROM value
    GIVING variable [ROUNDED]
    [ ON SIZE ERROR
    do something ]

The following are examples of subtraction with the SUBTRACT verb:

SUBTRACT  1.17
    FROM THE-VALUE ROUNDED
    ON SIZE ERROR
    DISPLAY "Subtract - overflow
SUBTRACT 17.5 FROM THE-VALUE
    GIVING THE-DIFFERENCE ROUNDED
    ON SIZE ERROR
    DISPLAY "Subtract-overflow"

Multiplication is handled by the MULTIPLY verb, and the following syntax for both versions of MULTIPLY is similar to ADD and SUBTRACT:

MULTIPLY value
    BY variable [ROUNDED]
    [ ON SIZE ERROR
    do something ]
MULTIPLY value BY value
    GIVING variable [ROUNDED]
    [ ON SIZE ERROR
    do something ]

The result is stored in the second value (for example, THE-VALUE) for the first version, and the second version uses GIVING to name a variable--in this case, THE-PRODUCT--to store the result:

MULTIPLY 1.17
    BY THE-VALUE ROUNDED
    ON SIZE ERROR
    DISPLAY "Multiply-overflow"
MULTIPLY 17.5 BY THE-VALUE
    GIVING THE-PRODUCT ROUNDED
    ON SIZE ERROR
    DISPLAY "Multiply-overflow"

Division with the DIVIDE verb comes in several versions, which follow. It has versions with and without the GIVING clause, and it also includes the capability of storing the remainder of a division in a separate variable. There also are versions that allow you to divide BY or divide INTO.

DIVIDE value
    INTO variable [ROUNDED]
    [ ON SIZE ERROR
    do something ]
DIVIDE value INTO value
    GIVING variable [ROUNDED]
    [ ON SIZE ERROR
    do something ]
DIVIDE value INTO value
    GIVING variable [ROUNDED]
    REMAINDER variable
    [ ON SIZE ERROR
    do something ]
DIVIDE value BY value
    GIVING variable [ROUNDED]
    [ ON SIZE ERROR
    do something ]
DIVIDE value BY value
    GIVING variable [ROUNDED]
    REMAINDER variable
    [ ON SIZE ERROR
    do something ]

The following are examples of division with the DIVIDE verb:

DIVIDE 56.2
    INTO THE-VALUE ROUNDED
    ON SIZE ERROR
    DISPLAY "Divide-error"
DIVIDE 56.2 INTO THE-VALUE
    GIVING THE-QUOTIENT ROUNDED
    ON SIZE ERROR
    DISPLAY "Divide-error"
DIVIDE 15 INTO THE-VALUE
    GIVING THE-QUOTIENT ROUNDED
    REMAINDER THE RE-REMAINDER
    ON SIZE ERRROR
    DISPLAY "Divide-error"
DIVIDE 56.2 BY THE-VALUE
    GIVING THE-QUOTINT ROUNDED
    ON SIZE ERROR
    DISPLAY "Divide-error"
DIVIDE 15 BY 7
    GIVING THE-QUOTIENT ROUNDED
    REMAINDER THE-REMAINDER
    ON SIZE ERROR
    DISPLAY "Divide-error"

Summary

Today, you learned more about COBOL's DATA DIVISION, including the following basics:

01   THE-VALUE      PIC S99V9.

Q&A

Q If I can use ZEROES and SPACES to initialize a variable, can I also move ZEROES and SPACES to a variable?

A Yes. Both of the following statements behave as you would expect them to by moving spaces or zeroes to variables:
MOVE SPACES TO THE-MESSAGE.
MOVE ZEROES TO THE-NUMBER.
Q Does truncation happen in signed (positive and negative) numbers?

A Yes. If you move -2371.16 to a PIC S999V99, the result is stored as -371.16. If you move a number with a negative sign to a picture that does not have a sign, the sign is truncated. If you move -456.78 to a PIC 999V99, the result is stored as 456.78.

Workshop

Quiz

1. What is the value in BIG-NUMBER after the MOVE?
01  BIG-NUMBER         PIC 9(5).
    MOVE 4976 TO BIG-NUMBER
2. What is the value in SMALL-NUMBER after the MOVE?
01  SMALL-NUMBER       PIC 9(2).
    MOVE 4976 TO SMALL-NUMBER.
Hint: Numbers are truncated from the left.

3. After the following move, THE-VALUE contains 000.00. Why?

01  THE-VALUE          PIC 999V99.
    MOVE 1000.001 TO THE-VALUE.

Exercises

1. If you haven't done so, compile trunc01.cbl and make a note of any warnings provided by your compiler. If your compiler has a manual that lists the meanings of warnings, look them up in the manual and become familiar with them.

2. Compile trunc02.cbl and look up any errors generated by the compiler.


Previous chapterNext chapterContents


© Copyright, Macmillan Computer Publishing. All rights reserved.