You can use the DATA DIVISION to organize your data and variables and improve the performance of your program. You also can use it to reduce the amount of code that you have to write.
Today, you learn about the following topics:
You might want to create a COBOL program that combines variables to improve the way they display.
New Term: A data structure, or record, in COBOL is a method of combining several variables into one larger variable.
The program jack02.cbl in Day 2, "Using Variables and Constants," used variables to display a poem with line numbers. Variables are defined and displayed as shown in List-ing 8.1.
000700 000800 01 THE-MESSAGE PIC X(50). 000900 01 THE-NUMBER PIC 9(2). 001000 01 A-SPACE PIC X. 001100 ...... 001700 001800* Set up and display line 1 001900 MOVE 1 TO THE-NUMBER. 002000 MOVE "Jack be nimble," TO THE-MESSAGE. 002100 DISPLAY THE-NUMBER A-SPACE THE-MESSAGE 002200
These three variables can be combined into one record (data structure) and used as a group for the DISPLAY statement. The grouping is done by defining the data as shown in Listing 8.2.
000700 000800 01 THE-WHOLE-MESSAGE. 000900 05 THE-NUMBER PIC 9(2) VALUE ZEROES. 001000 05 A-SPACE PIC X(1) VALUE SPACE. 001100 05 THE-MESSAGE PIC X(50) VALUE SPACES. 001200
New Term: In Listing 8.2, THE-WHOLE-MESSAGE is a structure variable or simply a structure. It is occasionally referred to as a compound variable or compound data.
In a structure variable, the highest-level variable (the one that includes all the individual variables) has the level number 01. The 01 level must appear in Area A (columns 8 through 12). The structure variable name appears in Area B (columns 12 through 72), and it does not have a PICTURE. The variables that fall within the structure begin with numbers higher than 01, and start in Area B (columns 12 through 72).
You can use the individual variables within a structure in the program as though they still were level 01 variables. In addition, you can use the structure variable as a variable. For example, if all the variables within a structure variable can be displayed, the structure variable itself can be displayed as a variable (see Listing 8.3).
000700 000800 01 THE-WHOLE-MESSAGE. 000900 05 THE-NUMBER PIC 9(2) VALUE ZEROES. 001000 05 A-SPACE PIC X(1) VALUE SPACE. 001100 05 THE-MESSAGE PIC X(50) VALUE SPACES. ...... 001700 001800* Set up and display line 1 001900 MOVE 1 TO THE-NUMBER. 002000 MOVE "Jack be nimble," TO THE-MESSAGE. 002100 DISPLAY THE-WHOLE-MESSAGE. 002200
ANALYSIS: The individual variables of the structure have higher level numbers than the structure variable. In the following code fragment, the elementary variables have the level number 05. This level number could have been 02, but it is a common practice to skip some numbers between levels.
Figure 8.1 illustrates the positioning of the parts of a structure variable within Area A and Area B.
Figure 8.1.
The layout of a structure in Area A and Area B.
One of the primary uses of a structure is to format information for display or printing. One quick way of seeing how structures work is to use one to format output data.
Listing 8.4, cmpint03.cbl, is similar to the compound interest programs in Day 7, "Basics of Design," but it uses a structured variable (a structure) to produce a formatted output.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. CMPINT03. 000300*------------------------------------------------ 000400* Calculates compound interest 000500*------------------------------------------------ 000600 ENVIRONMENT DIVISION. 000700 DATA DIVISION. 000800 WORKING-STORAGE SECTION. 000900 001000 01 YES-NO PIC X. 001100 01 ENTRY-OK PIC X. 001200 01 THE-INTEREST PIC 99V9. 001300 01 INTEREST-AS-DECIMAL PIC V999. 001400 01 THE-PRINCIPAL PIC 9(9)V99. 001500 01 WORKING-PRINCIPAL PIC 9(9)V99. 001600 01 THE-NEW-VALUE PIC 9(9)V99. 001700 01 EARNED-INTEREST PIC 9(9)V99. 001800 01 THE-PERIOD PIC 9999. 001900 01 NO-OF-PERIODS PIC 999. 002000 002100 01 ENTRY-FIELD PIC ZZZ,ZZZ,ZZZ.ZZ. 002200 002300 01 THE-WHOLE-MESSAGE. 002400 05 DISPLAY-PRINCIPAL PIC ZZZ,ZZZ,ZZ9.99. 002500 05 MESSAGE-PART-01 PIC X(4) VALUE " at ". 002600 05 DISPLAY-INTEREST PIC Z9.9. 002700 05 MESSAGE-PART-02 PIC X(6) VALUE "% for ". 002800 05 DISPLAY-PERIODS PIC ZZ9. 002900 05 MESSAGE-PART-03 PIC X(16) 003000 VALUE " periods yields ". 003100 05 DISPLAY-VALUE PIC ZZZ,ZZZ,ZZ9.99. 003200 003300 PROCEDURE DIVISION. 003400 PROGRAM-BEGIN. 003500 003600 MOVE "Y" TO YES-NO. 003700 PERFORM GET-AND-DISPLAY-RESULT 003800 UNTIL YES-NO = "N". 003900 004000 PROGRAM-DONE. 004100 STOP RUN. 004200 004300 GET-AND-DISPLAY-RESULT. 004400 PERFORM GET-THE-PRINCIPAL. 004500 PERFORM GET-THE-INTEREST. 004600 PERFORM GET-THE-PERIODS. 004700 PERFORM CALCULATE-THE-RESULT. 004800 PERFORM DISPLAY-THE-RESULT. 004900 PERFORM GO-AGAIN. 005000 005100 GET-THE-PRINCIPAL. 005200 MOVE "N" TO ENTRY-OK. 005300 PERFORM ENTER-THE-PRINCIPAL 005400 UNTIL ENTRY-OK = "Y". 005500 005600 ENTER-THE-PRINCIPAL. 005700 DISPLAY "Principal (.01 TO 999999.99)?". 005800 ACCEPT ENTRY-FIELD WITH CONVERSION. 005900 MOVE ENTRY-FIELD TO THE-PRINCIPAL. 006000 IF THE-PRINCIPAL < .01 OR 006100 THE-PRINCIPAL > 999999.99 006200 DISPLAY "INVALID ENTRY" 006300 ELSE 006400 MOVE "Y" TO ENTRY-OK. 006500 006600 GET-THE-INTEREST. 006700 MOVE "N" TO ENTRY-OK. 006800 PERFORM ENTER-THE-INTEREST 006900 UNTIL ENTRY-OK = "Y". 007000 007100 ENTER-THE-INTEREST. 007200 DISPLAY "Interest (.1% TO 99.9%)?". 007300 ACCEPT ENTRY-FIELD WITH CONVERSION. 007400 MOVE ENTRY-FIELD TO THE-INTEREST. 007500 IF THE-INTEREST < .1 OR 007600 THE-INTEREST > 99.9 007700 DISPLAY "INVALID ENTRY" 007800 ELSE 007900 MOVE "Y" TO ENTRY-OK 008000 COMPUTE INTEREST-AS-DECIMAL = 008100 THE-INTEREST / 100. 008200 008300 GET-THE-PERIODS. 008400 MOVE "N" TO ENTRY-OK. 008500 PERFORM ENTER-THE-PERIODS 008600 UNTIL ENTRY-OK = "Y". 008700 008800 ENTER-THE-PERIODS. 008900 DISPLAY "Number of periods (1 TO 999)?". 009000 ACCEPT ENTRY-FIELD WITH CONVERSION. 009100 MOVE ENTRY-FIELD TO NO-OF-PERIODS. 009200 IF NO-OF-PERIODS < 1 OR 009300 NO-OF-PERIODS > 999 009400 DISPLAY "INVALID ENTRY" 009500 ELSE 009600 MOVE "Y" TO ENTRY-OK. 009700 009800 CALCULATE-THE-RESULT. 009900 MOVE THE-PRINCIPAL TO WORKING-PRINCIPAL. 010000 PERFORM CALCULATE-ONE-PERIOD 010100 VARYING THE-PERIOD FROM 1 BY 1 010200 UNTIL THE-PERIOD > NO-OF-PERIODS. 010300 010400 CALCULATE-ONE-PERIOD. 010500 COMPUTE EARNED-INTEREST ROUNDED = 010600 WORKING-PRINCIPAL * INTEREST-AS-DECIMAL. 010700 COMPUTE THE-NEW-VALUE = 010800 WORKING-PRINCIPAL + EARNED-INTEREST. 010900 MOVE THE-NEW-VALUE TO WORKING-PRINCIPAL. 011000 011100 GO-AGAIN. 011200 DISPLAY "GO AGAIN?". 011300 ACCEPT YES-NO. 011400 IF YES-NO = "y" 011500 MOVE "Y" TO YES-NO. 011600 IF YES-NO NOT = "Y" 011700 MOVE "N" TO YES-NO. 011800 011900 DISPLAY-THE-RESULT. 012000 MOVE THE-PRINCIPAL TO DISPLAY-PRINCIPAL. 012100 MOVE THE-INTEREST TO DISPLAY-INTEREST. 012200 MOVE NO-OF-PERIODS TO DISPLAY-PERIODS. 012300 MOVE THE-NEW-VALUE TO DISPLAY-VALUE. 012400 DISPLAY THE-WHOLE-MESSAGE. 012500
OUTPUT:
Principal (.01 TO 999999.99)? 14000 Interest (.1% TO 99.9%)? 12.7 Number of periods (1 TO 999)? 14 14,000.00 at 12.7% for 14 periods yields 74,655.69 GO AGAIN?
ANALYSIS: The structure is defined at lines 002300 to 003100. In DISPLAY-THE-RESULT, at lines 0011900 to 0012400, values are moved to each of the individual elements of the structure, and the whole structure is displayed, rather than the separate parts.
The structure THE-WHOLE-MESSAGE is considered to be one long variable containing subparts. By using it for the DISPLAY, you cut down on the amount of code you have to write to display the same formatted data one piece at a time.
Listing 8.5 is the message data structure extracted from cmpint03.cbl. All parts of the message appear as variables with level 05 numbers within THE-WHOLE-MESSAGE. Even parts of the message that do not vary, such as MESSAGE-PART-01, MESSAGE-PART-02, and MESSAGE-PART-03, have been given data names.
002300 01 THE-WHOLE-MESSAGE. 002400 05 DISPLAY-PRINCIPAL PIC ZZZ,ZZZ,ZZ9.99. 002500 05 MESSAGE-PART-01 PIC X(4) VALUE " at ". 002600 05 DISPLAY-INTEREST PIC Z9.9. 002700 05 MESSAGE-PART-02 PIC X(6) VALUE "% for ". 002800 05 DISPLAY-PERIODS PIC ZZ9. 002900 05 MESSAGE-PART-03 PIC X(16) 003000 VALUE " periods yields ". 003100 05 DISPLAY-VALUE PIC ZZZ,ZZZ,ZZ9.99. 003200
ANALYSIS: Three of the variables within THE-WHOLE-MESSAGE are never used in the main program. They are MESSAGE-PART-01, MESSAGE-PART-02, and MESSAGE-PART-03 at lines 002500, 002700, and 002900, respectively. They are used to format part of the display and are assigned values in the definition, but nothing is ever moved to these values in the program.
MESSAGE-PART-01, MESSAGE-PART-02, and MESSAGE-PART-03 really do not need to exist as variables with data names because they are never used in the PROCEDURE DIVISION. They exist only to fill out THE-WHOLE-MESSAGE.
In COBOL, this type of value in a structure variable can be defined as a filler by using the COBOL reserved word FILLER. Listing 8.6 uses FILLER in the definition of the same structure variable.
002300 01 THE-WHOLE-MESSAGE. 002400 05 DISPLAY-PRINCIPAL PIC ZZZ,ZZZ,ZZ9.99. 002500 05 FILLER PIC X(4) VALUE " at ". 002600 05 DISPLAY-INTEREST PIC Z9.9. 002700 05 FILLER PIC X(6) VALUE "% for ". 002800 05 DISPLAY-PERIODS PIC ZZ9. 002900 05 FILLER PIC X(16) 003000 VALUE " periods yields ". 003100 05 DISPLAY-VALUE PIC ZZZ,ZZZ,ZZ9.99. 003200
A FILLER cannot be treated as a variable. It is used to reserve space in a structure variable. You can assign a PICTURE and a VALUE to a FILLER when it is defined, but you cannot use MOVE with FILLER.
A data structure is actually a series of individual variables, laid end to end in memory. The length of a simple data structure, such as this one used to create a displayable message, is the sum of all the lengths of the individual parts.
Table 8.1 shows how to calculate the length of THE-WHOLE-MESSAGE by adding the lengths of the parts. THE-WHOLE-MESSAGE is 61 bytes (characters) long.
Variable | Length |
05 DISPLAY-PRINCIPAL PIC ZZZ,ZZZ,ZZ9.99. | 14 |
05 FILLER PIC X(4) VALUE " at ". | 4 |
05 DISPLAY-INTEREST PIC Z9.9. | 4 |
05 FILLER PIC X(6) VALUE "% for ". | 6 |
05 DISPLAY-PERIODS PIC ZZ9. | 3 |
05 FILLER PIC X(16) VALUE " periods yields ". | 16 |
05 DISPLAY-VALUE PIC ZZZ,ZZZ,ZZ9.99. | 14 |
01 THE-WHOLE-MESSAGE | 61 |
A structure variable is treated as an alphanumeric variable. It has an implied PICTURE of X(nn), where nn is equal to the length of the structure variable. THE-WHOLE-MESSAGE has an implicit PICTURE of X(61).
You can move a value to a structure variable, but the move will affect the entire length of the variable. A structure variable and the variables that are the elements of a structure occupy the same memory area. When a variable is created by the compiler, it sets aside a number of bytes in memory that can be used to hold data.
Listing 8.7 shows a sample structure variable used to display an employee number and an hourly rate earned.
000900 01 EMPLOYEE-DATA. 001000 05 FILLER PIC X(4) 001100 VALUE "Emp ". 001200 05 EMP-NUMBER PIC 9999. 001300 05 FILLER PIC X(7) 001400 VALUE " earns ". 001500 05 EMP-HOURLY PIC Z9.99.
The output of this structure, if you move 234 to EMP-NUMBER and 13.50 to EMP-HOURLY and then DISPLAY EMPLOYEE-DATA, is the following:
OUTPUT:
Emp 0234 earns 13.50
Figure 8.2 represents how the bytes in this structure are filled in with these values (234 in EMP-NUMBER and 13.50 in EMP-HOURLY). The top row numbers the bytes from 1 to 20, which is the length of the entire structure. The second row contains the actual values in memory, where position 1 contains `E', position 2 contains `m', and so on.
Rows 3 and 4 are the variable names and the picture for each variable.
Figure 8.2.
The memory layout of a structure.
ANALYSIS: The two fillers, as well as EMP-NUMBER and EMP-HOURLY, occupy some bytes that are in the same space in memory as the structure variable EMPLOYEE-DATA.
When you use a command in COBOL to modify a variable in memory, the command looks at variables in memory as individual units. If you move a value to EMP-NUMBER, or use ADD 1 TO EMP-NUMBER, COBOL acts on EMP-NUMBER as if it were a single variable and ignores the fact that EMP-NUMBER is part of the structure EMPLOYEE-DATA.
Regarding a variable as an individual unit also applies to the complete structure. If you move a message to EMPLOYEE-DATA, the command treats EMPLOYEE-DATA as if it were a PIC X(20) (the implied picture) and ignores the fact that EMPLOYEE-DATA has smaller variables within it.
If the following command is executed in a COBOL program containing this same EMPLOYEE-DATA structure, EMPLOYEE-DATA is treated as if it were a single variable and the elements within EMPLOYEE-DATA are ignored (as shown in Figure 8.3):
004600 MOVE "No more employees." TO EMPLOYEE-DATA. 004700 DISPLAY EMPLOYEE-DATA.
Figure 8.3.
EMPLOYEE-DATA after moving a value to it.
The variables in EMPLOYEE-DATA do not disappear, but the MOVE affects all 20 bytes of memory, and the individual variables might no longer contain data that is correct for that variable type. Figure 8.4 adds back the variables in EMPLOYEE-DATA. EMP-NUMBER now contains ore, which certainly is not valid numeric data. This isn't a problem as long as you don't use a command on EMP-NUMBER, such as ADD 1 TO EMP-NUMBER. I'll return to this issue in a moment.
Figure 8.4.
EMPLOYEE-DATA with the variables added.
This use of a structure variable is fairly common in display and print programs that might use a structure to format and display information line by line, and then at the end of the program might move a message to the entire structure and display it. It is not necessarily good programming practice, but you will encounter this use of structure variables in many programs.
Any structure can contain another structure. In Listing 8.8, THE-MESSAGE is a structure that, in turn, contains two alphanumeric variables--JACKS-NAME and JACKS-TASK. In addition, it uses a VALUE to initialize JACKS-NAME to reduce the size of the message that must be moved for each line of the display. Indenting JACKS-NAME and JACKS-TASK is a matter of style. The indention makes it clear that these variables are subordinate to THE-MESSAGE.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. JACK06. 000300 ENVIRONMENT DIVISION. 000400 DATA DIVISION. 000500 000600 WORKING-STORAGE SECTION. 000700 000800 01 THE-WHOLE-MESSAGE. 000900 05 THE-NUMBER PIC 9(2) VALUE 1. 001000 05 A-SPACE PIC X VALUE SPACE. 001100 05 THE-MESSAGE. 001200 10 JACKS-NAME PIC X(5) VALUE "Jack". 001300 10 JACKS-TASK PIC X(45). 001400 001500 PROCEDURE DIVISION. 001600 PROGRAM-BEGIN. 001700 001800* Set up and display line 1 001900 MOVE "be nimble," TO JACKS-TASK. 002000 DISPLAY THE-WHOLE-MESSAGE. 002100 002200* Set up and Display line 2 002300 MOVE "be quick," TO JACKS-TASK. 002400 ADD 1 TO THE-NUMBER. 002500 DISPLAY THE-WHOLE-MESSAGE. 002600 002700* Set up and display line 3 002800 MOVE "jump over the candlestick." TO JACKS-TASK. 002900 ADD 1 TO THE-NUMBER. 003000 DISPLAY THE-WHOLE-MESSAGE. 003100 003200* Display a closing message 003300 MOVE "That's all folks" TO THE-WHOLE-MESSAGE. 003400 DISPLAY THE-WHOLE-MESSAGE. 003500 003600 PROGRAM-DONE. 003700 STOP RUN. 003800
The following is the output of jack06.cbl.
OUTPUT:
01 Jack be nimble, 02 Jack be quick, 03 Jack jump over the candlestick. That's all folks C> C>
ANALYSIS: The last action of the program, at line 003300, is to move a value to THE-WHOLE-MESSAGE and then display it at line 003400. This wipes out the previous contents of THE-WHOLE-MESSAGE and overwrites the whole variable structure as though it were a single alphanumeric variable. This effect can be seen in the output of jack06.cbl.
To calculate the length of a structure variable containing one or more other structure variables, apply what you already know about structure variables. Work out the length of the internal structure variables and add them to the length of the level 01 structure. Table 8.2 calculates the size of the structure by turning the structure upside down and calculating a sub- total for THE-MESSAGE and adding that result to the lengths of the other variables in THE-WHOLE-MESSAGE.
Variable | Length | |
10 JACKS-TASK | PIC X(45). | 45 |
10 JACKS-NAME | PIC X(5) VALUE "Jack". | + 5 |
05 THE-MESSAGE. | = 50 (subtotal) | |
05 A-SPACE | PIC X VALUE SPACE. | + 1 |
05 THE-NUMBER | PIC 9(2) VALUE 1. | + 2 |
01 THE-WHOLE-MESSAGE. | = 53 (grand total) |
The maximum level number for a variable within a structure is 49. In practice, it is unusual to find a variable structure that uses all 49 levels. You'll rarely go beyond 25 even when you increment by 5.
The last steps of jack06.cbl are to move "That's all folks" to THE-WHOLE-MESSAGE and then display it. This raises an interesting problem. By moving "That's all folks" to THE-WHOLE-MESSAGE, you move values into the areas occupied by THE-NUMBER, A-SPACE, and THE-MESSAGE. For A-SPACE and THE-MESSAGE, this is no problem because they are alphanumeric variables. THE-NUMBER, however, is a numeric variable that occupies the first two bytes of THE-WHOLE-MESSAGE. After the MOVE, it contains the value "Th", the first two characters of "That's all folks", and the value moved to THE-MESSAGE. This is certainly not numeric data.
If you attempt to perform some sort of calculation with THE-NUMBER, your program usually fails with an error because THE-NUMBER contains invalid data. Some versions of COBOL let you display the variable using DISPLAY THE-NUMBER and it actually displays as "Th". Very few versions of COBOL let you perform anything that resembles a mathematical operation with the variable. Listing 8.9 is a deliberate effort to cause the program to crash by attempting to use ADD 1 TO THE-NUMBER when it contains "Th".
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. JACK07. 000300 ENVIRONMENT DIVISION. 000400 DATA DIVISION. 000500 000600 WORKING-STORAGE SECTION. 000700 000800 01 THE-WHOLE-MESSAGE. 000900 05 THE-NUMBER PIC 9(2) VALUE 1. 001000 05 A-SPACE PIC X VALUE SPACE. 001100 05 THE-MESSAGE. 001200 10 JACKS-NAME PIC X(5) VALUE "Jack". 001300 10 JACKS-TASK PIC X(45). 001400 001500 PROCEDURE DIVISION. 001600 PROGRAM-BEGIN. 001700 001800* Set up and display line 1 001900 MOVE "be nimble," TO JACKS-TASK. 002000 DISPLAY THE-WHOLE-MESSAGE. 002100 002200* Set up and Display line 2 002300 MOVE "be quick," TO JACKS-TASK. 002400 ADD 1 TO THE-NUMBER. 002500 DISPLAY THE-WHOLE-MESSAGE. 002600 002700* Set up and display line 3 002800 MOVE "jump over the candlestick." TO JACKS-TASK. 002900 ADD 1 TO THE-NUMBER. 003000 DISPLAY THE-WHOLE-MESSAGE. 003100 003200* Display a closing message 003300 MOVE "That's all folks" TO THE-WHOLE-MESSAGE. 003400 DISPLAY THE-WHOLE-MESSAGE. 003500 003600* A deliberate attempt to blow up the program 003700 DISPLAY THE-NUMBER. 003800 ADD 1 TO THE-NUMBER. 003900 DISPLAY THE-NUMBER. 004000 004100 PROGRAM-DONE. 004200 STOP RUN. 004300
The following output and error message produced by Micro Focus Personal COBOL indicates that an error occurred while trying to ADD 1 TO THE-NUMBER. Note that the first DISPLAY at line 003700 of the program worked and displayed "Th".
OUTPUT:
C>pcobrun jack07 Personal COBOL version 2.0 from Micro Focus PCOBRUN V2.0.02 Copyright (C) 1983-1993 Micro Focus Ltd. 01 Jack be nimble, 02 Jack be quick, 03 Jack jump over the candlestick. That's all folks Th JACK07 Segment RT : Error 163 at COBOL PC 009A Description : Illegal Character in Numeric Field C> C>
The following output for the same program was compiled and run using ACUCOBOL. This produces no error. The program displays "Th" and then adds 1 to THE-NUMBER and displays it again as "Tg". This obviously nutty result is caused by the fact that THE-NUMBER doesn't contain valid data. If you encounter errors such as non-numeric data in a numeric field, or illegal characters in a numeric field, there are two possible causes that you could investigate. The variable might never have been correctly initialized or the program might have used a MOVE statement to fill a structure variable with information that is invalid for one or more numeric variables that are a part of the structure variable. You would never code a program to take advantage of quirky behavior such as "Th" becoming "Tg" in the preceding example. No one would be able to understand what your program was really trying to do because it relies on possibly unpredictable behavior by some brand of compiler and the behavior might disappear when a new version of the compiler was released by the manufacturer.
OUTPUT:
01 Jack be nimble, 02 Jack be quick, 03 Jack jump over the candlestick. That's all folks Th Tg C> C>
If you have moved a value to the structure and need to use THE-NUMBER again as a numeric value, you must reset the value in THE-NUMBER by moving a number to it, like this:
MOVE 1 TO THE-NUMBER.
Moving a number to reset the value is the only action you should attempt on a numeric variable that contains invalid data.
DO/DON'T:
DO move values to numeric variables that have undefined or invalid contents before using numeric variables in calculations.DON'T perform calculations with numeric variables that have undefined values or that have been modified because they are elements of a structure and some value has been moved to the structure.
It is common to find programs that define data structures in WORKING-STORAGE that never are used as structures. Variables of one type might be clumped together into a data structure as a form of documentation. Perhaps this is an effort to be tidy.
Grouping variables together under a structure variable because they are similar or to keep things tidy isn't a good practice. It is better to use comments in WORKING-STORAGE to separate groups of variables used for different purposes. The existence of a structure variable implies that it is used somewhere in the program as a variable. It can be misleading to see a structure in WORKING-STORAGE that is not really a structure but is a grab bag of variables. (See Listing 8.10.) Only THE-WHOLE-MESSAGE is actually used as a structure in the program. Be aware of this when you are trying to understand a program that you are reading. The following example is one you are familiar with, and you will recognize immediately what is going on; recognition is harder in an unfamiliar program.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. CMPINT04. 000300*------------------------------------------------ 000400* Calculates compound interest 000500*------------------------------------------------ 000600 ENVIRONMENT DIVISION. 000700 DATA DIVISION. 000800 WORKING-STORAGE SECTION. 000900 001000 01 SOME-FLAGS. 001100 05 YES-NO PIC X. 001200 05 ENTRY-OK PIC X. 001300 001400 01 CALCULATION-FIELDS. 001500 05 THE-INTEREST PIC 99V9. 001600 05 INTEREST-AS-DECIMAL PIC V999. 001700 05 THE-PRINCIPAL PIC 9(9)V99. 001800 05 WORKING-PRINCIPAL PIC 9(9)V99. 001900 05 THE-NEW-VALUE PIC 9(9)V99. 002000 05 EARNED-INTEREST PIC 9(9)V99. 002100 05 THE-PERIOD PIC 9999. 002200 05 NO-OF-PERIODS PIC 999. 002300 002400 01 ENTRY-FIELD PIC ZZZ,ZZZ,ZZZ.ZZ. 002500 002600 01 THE-WHOLE-MESSAGE. 002700 05 DISPLAY-PRINCIPAL PIC ZZZ,ZZZ,ZZ9.99. 002800 05 MESSAGE-PART-01 PIC X(4) VALUE " at ". 002900 05 DISPLAY-INTEREST PIC Z9.9. 003000 05 MESSAGE-PART-02 PIC X(6) VALUE "% for ". 003100 05 DISPLAY-PERIODS PIC ZZ9. 003200 05 MESSAGE-PART-03 PIC X(16) 003300 VALUE " periods yields ". 003400 05 DISPLAY-VALUE PIC ZZZ,ZZZ,ZZ9.99. 003500 003600 PROCEDURE DIVISION. 003700 PROGRAM-BEGIN. 003800 003900 MOVE "Y" TO YES-NO. 004000 PERFORM GET-AND-DISPLAY-RESULT 004100 UNTIL YES-NO = "N". 004200 004300 PROGRAM-DONE. 004400 STOP RUN. 004500 004600 GET-AND-DISPLAY-RESULT. 004700 PERFORM GET-THE-PRINCIPAL. 004800 PERFORM GET-THE-INTEREST. 004900 PERFORM GET-THE-PERIODS. 005000 PERFORM CALCULATE-THE-RESULT. 005100 PERFORM DISPLAY-THE-RESULT. 005200 PERFORM GO-AGAIN. 005300 005400 GET-THE-PRINCIPAL. 005500 MOVE "N" TO ENTRY-OK. 005600 PERFORM ENTER-THE-PRINCIPAL 005700 UNTIL ENTRY-OK = "Y". 005800 005900 ENTER-THE-PRINCIPAL. 006000 DISPLAY "Principal (.01 TO 999999.99)?". 006100 ACCEPT ENTRY-FIELD WITH CONVERSION. 006200 MOVE ENTRY-FIELD TO THE-PRINCIPAL. 006300 IF THE-PRINCIPAL < .01 OR 006400 THE-PRINCIPAL > 999999.99 006500 DISPLAY "INVALID ENTRY" 006600 ELSE 006700 MOVE "Y" TO ENTRY-OK. 006800 006900 GET-THE-INTEREST. 007000 MOVE "N" TO ENTRY-OK. 007100 PERFORM ENTER-THE-INTEREST 007200 UNTIL ENTRY-OK = "Y". 007300 007400 ENTER-THE-INTEREST. 007500 DISPLAY "Interest (.1% TO 99.9%)?". 007600 ACCEPT ENTRY-FIELD WITH CONVERSION. 007700 MOVE ENTRY-FIELD TO THE-INTEREST. 007800 IF THE-INTEREST < .1 OR 007900 THE-INTEREST > 99.9 008000 DISPLAY "INVALID ENTRY" 008100 ELSE 008200 MOVE "Y" TO ENTRY-OK 008300 COMPUTE INTEREST-AS-DECIMAL = 008400 THE-INTEREST / 100. 008500 008600 GET-THE-PERIODS. 008700 MOVE "N" TO ENTRY-OK. 008800 PERFORM ENTER-THE-PERIODS 008900 UNTIL ENTRY-OK = "Y". 009000 009100 ENTER-THE-PERIODS. 009200 DISPLAY "Number of periods (1 TO 999)?". 009300 ACCEPT ENTRY-FIELD WITH CONVERSION. 009400 MOVE ENTRY-FIELD TO NO-OF-PERIODS. 009500 IF NO-OF-PERIODS < 1 OR 009600 NO-OF-PERIODS > 999 009700 DISPLAY "INVALID ENTRY" 009800 ELSE 009900 MOVE "Y" TO ENTRY-OK. 010000 010100 CALCULATE-THE-RESULT. 010200 MOVE THE-PRINCIPAL TO WORKING-PRINCIPAL. 010300 PERFORM CALCULATE-ONE-PERIOD 010400 VARYING THE-PERIOD FROM 1 BY 1 010500 UNTIL THE-PERIOD > NO-OF-PERIODS. 010600 010700 CALCULATE-ONE-PERIOD. 010800 COMPUTE EARNED-INTEREST ROUNDED = 010900 WORKING-PRINCIPAL * INTEREST-AS-DECIMAL. 011000 COMPUTE THE-NEW-VALUE = 011100 WORKING-PRINCIPAL + EARNED-INTEREST. 011200 MOVE THE-NEW-VALUE TO WORKING-PRINCIPAL. 011300 011400 GO-AGAIN. 011500 DISPLAY "GO AGAIN?". 011600 ACCEPT YES-NO. 011700 IF YES-NO = "y" 011800 MOVE "Y" TO YES-NO. 011900 IF YES-NO NOT = "Y" 012000 MOVE "N" TO YES-NO. 012100 012200 DISPLAY-THE-RESULT. 012300 MOVE THE-PRINCIPAL TO DISPLAY-PRINCIPAL. 012400 MOVE THE-INTEREST TO DISPLAY-INTEREST. 012500 MOVE NO-OF-PERIODS TO DISPLAY-PERIODS. 012600 MOVE THE-NEW-VALUE TO DISPLAY-VALUE. 012700 DISPLAY THE-WHOLE-MESSAGE. 012800
There are some instances when grouping variables together might be useful. Some compilers make a more efficient use of memory if numeric variables are grouped together under a structure variable. Unfortunately, this is not true of all compilers.
When you see data in a structure in a program, you assume that the structure is used somewhere in the program as a structure, and you can be confused if it is not.
A variable that is not a structure can be given a level number of 77 instead of 01:
002600 77 YES-NO PIC X.
A level 77 variable uses the same syntax as a level 01 variable and must also begin in Area A, but a level 77 may not be used for a structure variable.
A level number of 77 indicates to the compiler that the variable named after the 77 is a simple elementary variable and not a structure. This change sometimes speeds up the compiler, and it might improve the memory use of a program. You don't have to worry about using level 77, but you will see it in some programs and you should know what it means when you see it.
Listing 8.11 shows an alternative way of defining the variables in cmpint04.cbl.
000800 WORKING-STORAGE SECTION. 000900 001000 001100 77 YES-NO PIC X. 001200 77 ENTRY-OK PIC X. 001300 001400 001500 77 THE-INTEREST PIC 99V9. 001600 77 INTEREST-AS-DECIMAL PIC V999. 001700 77 THE-PRINCIPAL PIC 9(9)V99. 001800 77 WORKING-PRINCIPAL PIC 9(9)V99. 001900 77 THE-NEW-VALUE PIC 9(9)V99. 002000 77 EARNED-INTEREST PIC 9(9)V99. 002100 77 THE-PERIOD PIC 9999. 002200 77 NO-OF-PERIODS PIC 999. 002300 002400 77 ENTRY-FIELD PIC ZZZ,ZZZ,ZZZ.ZZ. 002500 002600 01 THE-WHOLE-MESSAGE. 002700 05 DISPLAY-PRINCIPAL PIC ZZZ,ZZZ,ZZ9.99. 002800 05 MESSAGE-PART-01 PIC X(4) VALUE " at ". 002900 05 DISPLAY-INTEREST PIC Z9.9. 003000 05 MESSAGE-PART-02 PIC X(6) VALUE "% for ". 003100 05 DISPLAY-PERIODS PIC ZZ9. 003200 05 MESSAGE-PART-03 PIC X(16) 003300 VALUE " periods yields ". 003400 05 DISPLAY-VALUE PIC ZZZ,ZZZ,ZZ9.99. 003500
Level 88 is a special level number used to improve the readability of COBOL programs and to improve IF tests.
A level 88 looks like a level under another variable, but it's not. It does not have a PICTURE, but it does have a value. A level 88 is always associated with another variable and is a condition name for that variable. Here is an example:
002500 002600 01 YES-NO PIC X. 002700 88 ANSWER-IS-YES VALUE "Y". 002800
Both of the following conditions test whether YES-NO is equal to "Y":
003700 IF YES-NO = "Y" 003700 IF ANSWER-IS-YES
The condition name at line 002700 is another way of saying YES-NO = "Y" and can be used in IF and UNTIL conditions. A level 88 condition name can be used for an alphanumeric or numeric variable.
Listing 8.12, menu02.cbl, is a menu program that displays a message based on a menu pick of 1, 2, or 3, and exits on a 0.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. MENU02. 000300*------------------------------------------------ 000400* THIS PROGRAM DISPLAYS A THREE CHOICE MENU OF 000500* MESSAGES THAT CAN BE DISPLAYED. 000600* THE USER ENTERS THE CHOICE, 1, 2 OR 3, AND 000700* THE APPROPRIATE MESSAGE IS DISPLAYED. 000800* AN ERROR MESSAGE IS DISPLAYED IF AN INVALID 000900* CHOICE IS MADE. 001000*------------------------------------------------ 001100 ENVIRONMENT DIVISION. 001200 DATA DIVISION. 001300 WORKING-STORAGE SECTION. 001400 001500 01 MENU-PICK PIC 9. 001600 88 PICK-IS-EXIT VALUE 0. 001700 001800 PROCEDURE DIVISION. 001900 PROGRAM-BEGIN. 002000 002100 MOVE 1 TO MENU-PICK. 002200 PERFORM GET-AND-DO-PICK 002300 UNTIL PICK-IS-EXIT. 002400 002500 DISPLAY "Thank you. Exiting". 002600 002700 PROGRAM-DONE. 002800 STOP RUN. 002900 003000 GET-AND-DO-PICK. 003100 PERFORM GET-THE-MENU-PICK. 003200 003300 PERFORM DO-THE-MENU-PICK. 003400 003500 GET-THE-MENU-PICK. 003600 003700 PERFORM DISPLAY-THE-MENU. 003800 PERFORM GET-THE-PICK. 003900 004000 DO-THE-MENU-PICK. 004100 IF MENU-PICK > 3 004200 DISPLAY "Invalid selection". 004300 004400 IF MENU-PICK = 1 004500 DISPLAY "One for the money.". 004600 004700 IF MENU-PICK = 2 004800 DISPLAY "Two for the show.". 004900 005000 IF MENU-PICK = 3 005100 DISPLAY "Three to get ready.". 005200 005400 DISPLAY-THE-MENU. 000000* Includes the display of some blank lines to 000000* improve the appearance 005500 DISPLAY "Please enter the number of the message". 005600 DISPLAY "that you wish to display.". 005800 DISPLAY " ". 005900 DISPLAY "1. First Message". 006000 DISPLAY "2. Second Message". 006100 DISPLAY "3. Third Message". 006300 DISPLAY " ". 006400 DISPLAY "0. EXIT". 006500 DISPLAY " ". 006600 DISPLAY "Your selection (1-3)?". 006700 006800 GET-THE-PICK. 006900 ACCEPT MENU-PICK.
Line 001600 defines a condition name of PICK-IS-EXIT when MENU-PICK = 0. At line 002100, MENU-PICK is set to 1 so that it does not have a value of 0. If you start MENU-PICK with a value of 0, GET-AND-DO-PICK never will be performed. Instead, GET-AND-DO-PICK is performed until the PICK-IS-EXIT. The UNTIL condition at line 002300 is exactly equivalent to the following:
002300 UNTIL MENU-PICK = 0.
You also can set up a level 88 condition to test more than one condition. Here's a situation that could use an 88 to sort out a knotty IF test. In Listing 8.12, menu02.cbl, the menu selections are conveniently arranged to be valid if they are 0 through 3. The test for a valid selection at line 004100 is fairly simple because anything above 3 is invalid:
004000 004100 IF MENU-PICK > 3 004200 DISPLAY "Invalid selection". 004300
If you change your design so that 9 is used to exit, the test for a valid pick becomes complicated. Listing 8.13 and Listing 8.14 show two ways of performing this test. They are both awkward and a little confusing to read.
004100 IF MENU-PICK < 1 OR 004200 ( MENU-PICK < 9 AND MENU-PICK > 3) 004300 DISPLAY "Invalid selection". 004400
004100 IF MENU-PICK NOT = 1 AND 004200 MENU-PICK NOT = 2 AND 004300 MENU-PICK NOT = 3 AND 004400 MENU-PICK NOT = 9 004500 DISPLAY "Invalid selection". 004600
You can set up a level 88 to test for more than one value. The values can be a list of individual values as in Listing 8.15 (commas are optional), a range of values as in Listing 8.16, or a combination of list and range values as in Listing 8.17. Each listing includes comments showing the equivalent tests that must be used when not using an 88.
002500 002600 01 MENU-PICK PIC 9. 002700 88 PICK-IS-VALID VALUES 1, 2, 3, 9. 002800* MENU-PICK = 1 OR 002900* MENU-PICK = 2 OR 003000* MENU-PICK = 3 OR 003100* MENU-PICK = 9 003200
002500 002600 01 MENU-PICK PIC 9. 002700 88 PICK-IS-VALID VALUES 0 THROUGH 3. 002800* MENU-PICK = 0 OR 002900* MENU-PICK = 1 OR 003000* MENU-PICK = 2 OR 003100* MENU-PICK = 3 003200
002500 002600 01 MENU-PICK PIC 9. 002700 88 PICK-IS-VALID VALUES 8, 9, 0 THROUGH 3 002800* MENU-PICK = 8 OR 002900* MENU-PICK = 9 OR 003000* MENU-PICK = 0 OR 003100* MENU-PICK = 1 OR 003200* MENU-PICK = 2 OR 003300* MENU-PICK = 3 003400
A variable also can have more than one level 88 condition name associated with it, as shown in Listing 8.18.
002500 002600 01 MENU-PICK PIC 9. 002700 88 PICK-IS-VALID VALUES 8, 9, 0 THROUGH 3 002800 88 PICK-IS-EXIT VALUE 9. 002900
Listing 8.19 uses a level 88 to create a condition of PICK-IS-VALID when MENU-PICK equals 1, 2, 3, or 9. Then, another level 88 is used to set up a condition name of PICK-IS-EXIT when MENU-PICK equals 9.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. MENU03. 000300*------------------------------------------------ 000400* THIS PROGRAM DISPLAYS A THREE CHOICE MENU OF 000500* MESSAGES THAT CAN BE DISPLAYED. 000600* THE USER ENTERS THE CHOICE, 1, 2 OR 3, AND 000700* THE APPROPRIATE MESSAGE IS DISPLAYED. 000800* AN ERROR MESSAGE IS DISPLAYED IF AN INVALID 000900* CHOICE IS MADE. 001000*------------------------------------------------ 001100 ENVIRONMENT DIVISION. 001200 DATA DIVISION. 001300 WORKING-STORAGE SECTION. 001400 001500 01 MENU-PICK PIC 9. 001600 88 PICK-IS-EXIT VALUE 9. 001700 88 PICK-IS-VALID VALUES 1 THRU 3, 9. 001800 001900 PROCEDURE DIVISION. 002000 PROGRAM-BEGIN. 002100 002200 MOVE 1 TO MENU-PICK. 002300 PERFORM GET-AND-DO-PICK 002400 UNTIL PICK-IS-EXIT. 002500* MENU-PICK = 9 002600 002700 DISPLAY "Thank you. Exiting". 002800 002900 PROGRAM-DONE. 003000 STOP RUN. 003100 003200 GET-AND-DO-PICK. 003300 PERFORM GET-THE-MENU-PICK. 003400 003500 PERFORM DO-THE-MENU-PICK. 003600 003700 GET-THE-MENU-PICK. 003800 003900 PERFORM DISPLAY-THE-MENU. 004000 PERFORM GET-THE-PICK. 004100 004200 DO-THE-MENU-PICK. 004300* NOT ( MENU-PICK = 1 OR 2 OR 3 OR 9 ) 004400 IF NOT PICK-IS-VALID 004500 DISPLAY "Invalid selection". 004600 004700 IF MENU-PICK = 1 004800 DISPLAY "One for the money.". 004900 005000 IF MENU-PICK = 2 005100 DISPLAY "Two for the show.". 005200 005300 IF MENU-PICK = 3 005400 DISPLAY "Three to get ready.". 005500 005600* LEVEL 3 ROUTINES 005700 DISPLAY-THE-MENU. 005800 DISPLAY "Please enter the number of the message". 005900 DISPLAY "that you wish to display.". 006000* Display a blank line 006100 DISPLAY " ". 006200 DISPLAY "1. First Message". 006300 DISPLAY "2. Second Message". 006400 DISPLAY "3. Third Message". 006500* Display a blank line 006600 DISPLAY " ". 006700 DISPLAY "9. EXIT". 006800 DISPLAY " ". 006900 DISPLAY "Your selection (1-3)?". 007000 007100 GET-THE-PICK. 007200 ACCEPT MENU-PICK. 007300
The conditions are set up at lines 001600 and 001700. The condition name PICK-IS-VALID is set up when MENU-PICK equals 1, 2, 3, or 9. At lines 002300 and 002400, GET-AND-DO-PICK is performed UNTIL PICK-IS-EXIT (MENU-PICK = 9).
At lines 004300 and 004400, NOT is used to test for an invalid menu pick IF NOT PICK-IS-VALID (if MENU-PICK is not one of the values in the condition name list). You can see how much tidier, and easier to understand, the logic is at line 004400.
Today, you used the DATA DIVISION to organize your data and variables, improve the performance of your program, and reduce the amount of code that you have to write. You also learned the following basics:
000800 01 THE-WHOLE-MESSAGE. 000900 05 THE-NUMBER PIC 9(2) VALUE 1. 001000 05 A-SPACE PIC X VALUE SPACE. 001100 05 THE-MESSAGE. 001200 10 JACKS-NAME PIC X(5) VALUE "Jack". 001300 10 JACKS-TASK PIC X(45). 001400
001800 01 YES-NO PIC X. 001900 88 ANSWER-IS-YES VALUE "Y". 004600 IF YES-NO = "Y" 004700 PERFORM DO-SOMETHING.
001800 01 YES-NO PIC X. 001900 88 ANSWER-IS-VALID VALUES "Y","N". 004600 IF YES-NO = "Y" OR 004700 YES-NO = "N" 004800 PERFORM DO-SOMETHING.
001800 01 YES-NO PIC X. 004600 IF YES-NO = "Y" OR 004700 YES-NO = "y" OR 004800 YES-NO = "N" OR 004900 YES-NO = "n" 005000 PERFORM DO-SOMETHING.
001100 01 CUST-DATA. 001200 05 CUST-NUMBER PIC 9(3). 001300 05 CUST-NAME PIC X(10).
© Copyright, Macmillan Computer Publishing. All rights reserved.