Introduction to arrays -- also called tables or dimensions.
-------------------------------------------------------------------------------------------
Repetitions of a field
01 MONTH-LIST.
05 NAME-OF-MONTH-01 PIC X(09) VALUE 'JANUARY'.
05 NAME-OF-MONTH-02 PIC X(09) VALUE 'FEBRUARY'.
05 NAME-OF-MONTH-03 PIC X(09) VALUE 'MARCH'.
05 NAME-OF-MONTH-04 PIC X(09) VALUE 'APRIL'.
05 NAME-OF-MONTH-05 PIC X(09) VALUE 'MAY'.
05 NAME-OF-MONTH-06 PIC X(09) VALUE 'JUNE'.
05 NAME-OF-MONTH-07 PIC X(09) VALUE 'JULY'.
05 NAME-OF-MONTH-08 PIC X(09) VALUE 'AUGUST'.
05 NAME-OF-MONTH-09 PIC X(09) VALUE 'SEPTEMBER'.
05 NAME-OF-MONTH-10 PIC X(09) VALUE 'OCTOBER'.
05 NAME-OF-MONTH-11 PIC X(09) VALUE 'NOVEMBER'.
05 NAME-OF-MONTH-12 PIC X(09) VALUE 'DECEMBER'.
01 MONTH-TABLE REDEFINES MONTH-LIST.
05 NAME-OF-MONTH PIC X(09)
OCCURS 12 TIMES.
01 PRINT-LINE.
05 PIC X.
05 PRINT-MONTH PIC X(09).
01 X PIC 99.
01 TODAYS-DATE.
05 TODAYS-YEAR PIC 99.
05 TODAYS-MONTH PIC 99.
05 TODAYS-DAY PIC 99.
------------------------------------------------------------------------------------------------------------------------------
COBOL code to display the 9th month of the year is
DISPLAY NAME-OF-MONTH-09 TO PRINT-MONTH.
------------------------------------------------------------------------------------------------------------------------------
The following COBOL code will display the name of the month
based on the current-date.
ACCEPT TODAYS-DATE FROM DATE.
EVALUATE TODAYS-MONTH
WHEN 1 DISPLAY
NAME-OF-MONTH-01
WHEN 2 DISPLAY
NAME-OF-MONTH-02
WHEN 3 DISPLAY
NAME-OF-MONTH-03
WHEN 4 DISPLAY
NAME-OF-MONTH-04
WHEN 5 DISPLAY
NAME-OF-MONTH-05
WHEN 6 DISPLAY
NAME-OF-MONTH-06
WHEN 7 DISPLAY
NAME-OF-MONTH-07
WHEN 8 DISPLAY
NAME-OF-MONTH-08
WHEN 9 DISPLAY
NAME-OF-MONTH-09
WHEN 10 DISPLAY NAME-OF-MONTH-10
WHEN 11 DISPLAY NAME-OF-MONTH-11
WHEN 12 DISPLAY NAME-OF-MONTH-12
END-EVALUATE
--------------------------------------------------------------------------------------------
Contiguous, repeating fields can be defined as an Array if the
fields have the same
The fields grouped under MONTH-LIST are all alphanumeric, with
the same length
and are in a contiguous series. The name, value and grouping
indicate they have the same meaning -- the names of the months in a year.
MONTH-LIST is redefined by MONTH-TABLE which has an OCCURS 12
TIMES clause.
----------------------------------------------------------------------------------------------------------------------------
Instead of COBOL code to display the 9th month of the year by
referring to the unique
name of the field as
DISPLAY NAME-OF-MONTH-09.
The COBOL code could use the NAME-OF-MONTH variable and a reference
to
the rank-order occurrence of the month.
DISPLAY NAME-OF-MONTH (9).
The 9 is a numeric constant referring to the 9th month of the
year or the 9th
occurrence of the array.
----------------------------------------------------------------------------------------------------------------------------
Tables contain information in serial order.
Serial ordering refers to the ordinal position of variables in
a series, 1 2 3 (…) etc.
1 refers to the first occurrence (JANUARY) NAME-OF-MONTH
(1),
2 refers to the second (FEBRUARY),
NAME-OF-MONTH (2)
etc.
----------------------------------------------------------------------------------------------------------------------------
Symbolic references
The COBOL code could use the NAME-OF-MONTH and an identifier
that
contains an integer specifying the serial position of the month.
MOVE 9 TO X
DISPLAY NAME-OF-MONTH (X)
X is a subscript
Subscripts can have their values modified by any COBOL computation
verb --
such as ADD, SUBTRACT, MULTIPLY, COMPUTE or the VARYING option
of the PERFORM..
----------------------------------------------------------------------------------------------------------------------------
The power of symbolic references with subscripts is the ability
to manipulate large amounts of information with a few COBOL instructions.
All the months of the year could be printed with the following
code.
PERFORM VARYING X FROM 1 BY 1 UNTIL X > 12
DISPLAY NAME-OF-MONTH (X)
END-PERFORM
----------------------------------------------------------------------------------------------------------------------------
Repetitions of multiple fields
01 MIXED-LIST.
05 NAME-OF-MONTH-01 PIC
X(09).
05 INCOME-FOR-MONTH-01 PIC 9(7)V99.
05 NAME-OF-MONTH-02 PIC
X(09).
05 INCOME-FOR-MONTH-02 PIC 9(7)V99.
05 NAME-OF-MONTH-03 PIC
X(09).
05 INCOME-FOR-MONTH-03 PIC 9(7)V99.
05 NAME-OF-MONTH-04 PIC
X(09).
05 INCOME-FOR-MONTH-04 PIC 9(7)V99.
05 NAME-OF-MONTH-05 PIC
X(09).
05 INCOME-FOR-MONTH-05 PIC 9(7)V99.
05 NAME-OF-MONTH-06 PIC
X(09).
05 INCOME-FOR-MONTH-06 PIC 9(7)V99.
05 NAME-OF-MONTH-07 PIC
X(09).
05 INCOME-FOR-MONTH-07 PIC 9(7)V99.
05 NAME-OF-MONTH-08 PIC
X(09).
05 INCOME-FOR-MONTH-08 PIC 9(7)V99.
05 NAME-OF-MONTH-09 PIC
X(09).
05 INCOME-FOR-MONTH-09 PIC 9(7)V99.
05 NAME-OF-MONTH-10 PIC
X(09).
05 INCOME-FOR-MONTH-10 PIC 9(7)V99.
05 NAME-OF-MONTH-11 PIC
X(09).
05 INCOME-FOR-MONTH-11 PIC 9(7)V99.
05 NAME-OF-MONTH-12 PIC
X(09).
05 INCOME-FOR-MONTH-12 PIC 9(7)V99.
01 MIXED-TABLE REDEFINES MIXED-LIST.
05 MIXED-GROUP OCCURS 12 TIMES.
10 NAME-OF-MONTH
PIC X(09).
10 INCOME-FOR-MONTH
PIC 9(7)V99.
There is a pattern of repetition in this data.
MIXED-LIST is redefined by MIXED-TABLE.
MIXED-TABLE contains MIXED-GROUP which OCCURS 12 TIMES.
An occurrence number can be used to specify a particular group such as
DISPLAY MIXED-GROUP (1)
Or each individual element within the group can be referred to
by the same occurrence number.
DISPLAY NAME-OF-MONTH
(1) INCOME-FOR-MONTH (1)
----------------------------------------------------------------------------------------------------------------------------
Instead of listing all the individual elements of a file, all
the fields could be defined by
01 MIXED-TABLE.
05 MIXED-GROUP OCCURS 12 TIMES.
10 NAME-OF-MONTH
PIC X(09).
10 INCOME-FOR-MONTH PIC 9(7)V99.
----------------------------------------------------------------------------------------------------------------------------
Initializing arrays
1) Use the INITIALIZE verb to set the value of all Numeric picture fields to zero and alphanumeric picture fields to spaces.
INITIALIZE MIXED-TABLE
2) Use the VALUE statement on elements and then redefine those elements as a group as was demonstrated with the examples of MONTH-LIST and MIXED-LIST.
3) Initialize the array with variables stored on records.
4) Combination of any of the above.
Given a file of
FD MONTH-NAME-FILE.
01 MONTH-NAME-RECORD.
05 MONTH-NAME PIC
X(9).
05 FILLER PIC X(21).
The following code will
----------------------------------------------------------------------------------------------------------------------------
Updating arrays
Given the following working-storage area
01 MIXED-TABLE.
05 MIXED-GROUP
OCCURS 12 TIMES.
10 NAME-OF-MONTH PIC X(09).
10 INCOME-FOR-MONTH PIC 9(7)V99.
01 SWITCH PIC
XXX VALUE SPACES.
Given a update file of
FD MONTHLY-PROFIT-FILE.
01 MONTHLY-RECORD.
05 STORE-IDENTIFER
PIC X(7).
05 MONTH
PIC 99.
05 MONTHS-PROFIT
PIC 9(6)V99.
The following code will
----------------------------------------------------------------------------------------------------------------------------
Printing data from arrays
It is possible to print just one of the elements of an array
or to cycle through
each occurrence and send it to output.
----------------------------------------------------------------------------------------------------------------------------
Given the following working-storage area
01 MIXED-TABLE.
05 MIXED-GROUP
OCCURS 12 TIMES.
10 NAME-OF-MONTH PIC X(09).
10 INCOME-FOR-MONTH PIC 9(7)V99.
01 SWITCH PIC
XXX VALUE SPACES.
01 X
PIC 99.
Given an output file of
FD MONTHLY-PROFIT-REPORT.
01 MONTHLY-PROFIT-OUT.
05
PIC X.
05 MONTH-OUT
PIC X(9).
05
PIC X(6) VALUE SPACES.
05 MONTHS-PROFIT-OUT
PIC $$,$$$,$$$.99.
The following code will
By using relative subscripting, the following code will display two months on each line
PERFORM VARYING X
FROM 1 BY 1 UNTIL X > 6
DISPLAY NAME-OF-MONTH (X)
INCOME-FOR-MONTH(X)
' '
NAME-OF-MONTH (X + 6)
INCOME-FOR-MONTH(X + 6)
END-PERFORM
----------------------------------------------------------------------------------------------------------------------------
Search for data stored in arrays (serial search / sequential search)
1. Given a value to search for -- search argument.
2. Start at the beginning of the array -- set the subscript
to 1,
3. If the array element(subscript) matches, process the matched
value, stop searching
4. If no match, add 1 to subscript
5. If the subscript value exceeds the array size, there is no
table match, stop searching
6. Try matching against the next table element -- repeat the
process starting at step 3.
----------------------------------------------------------------------------------------------------------------------------
Given the following working-storage area
01 STOP-FLAG
PIC XXXX.
01 X
PIC 99.
01 TOOL-PRICE-OUT PIC $,$$$.99.
01 FOUND-SWITCH PIC XXX VALUE
'NO'.
01 MIXED-TOOL-PRICE-LIST.
05 FILLER PIC X(15)
VALUE 'HAMMER 01099'.
05 FILLER PIC X(15)
VALUE 'SAW 01550'.
05 FILLER PIC X(15)
VALUE 'CHISEL 00795'.
05 FILLER PIC X(15)
VALUE 'PLANNER 00975'.
05 FILLER PIC X(15)
VALUE 'TOOL BELT 01500'.
05 FILLER PIC X(15)
VALUE 'SANDER 02725'.
05 FILLER PIC X(15)
VALUE 'BUFFER 03327'.
05 FILLER PIC X(15)
VALUE 'POLISHER 01774'.
05 FILLER PIC X(15)
VALUE 'PRY BAR 00923'.
05 FILLER PIC X(15)
VALUE 'CAR JACK 02327'.
05 FILLER PIC X(15)
VALUE 'PLUNGER 00850'.
05 FILLER PIC X(15)
VALUE 'AWL 01225'.
01 MIXED-TOOL-PRICE-TABLE REDEFINES
MIXED-TOOL-PRICE-LIST.
05 MIXED-TOOL-PRICE-GROUP
OCCURS 12 TIMES.
10 NAME-OF-TOOL PIC X(10).
10 PRICE-OF-TOOL PIC 9(3)V99.
The following code will
----------------------------------------------------------------------------------------------------------------------------
What would be displayed if the perform statement above was
PERFORM VARYING X FROM 9 BY 1
UNTIL X > 12 OR FOUND-SWITCH = 'YES'
----------------------------------------------------------------------------------------------------------------------------
A Serial search can also be used to find more than one entry
in a table.
If the task is to find all the tools that sell for less than
15 dollars,
1. Start at the beginning of the array -- set the subscript
to 1,
2. If the array element(subscript) is less than 15, process
the matched value,
3. add 1 to subscript
4. If the subscript value exceeds the array size, stop searching
5. Try matching against the next table element -- repeat the
process starting at step 2.
----------------------------------------------------------------------------------------------------------------------------
Given the MIXED-TOOL-PRICE-TABLE described on the previous page
The following code will display all tools from the table priced
less than 15 dollars.
PERFORM VARYING
X FROM 1 BY 1
UNTIL X > 12
IF PRICE-OF-TOOL (X) < 15.00
MOVE PRICE-OF-TOOL(X) TO TOOL-PRICE-OUT
DISPLAY NAME-OF-TOOL (X) ' COSTS ' TOOL-PRICE-OUT
END-IF
END-PERFORM
----------------------------------------------------------------------------------------------------------------------------
COBOL VERB -- SEARCH and the use of an INDEX.
The COBOL SEARCH verb will do a serial search using indexes.
----------------------------------------------------------------------------------------------------------------------------
SEARCH format
SET index TO start
SEARCH table
AT END imperative-statements
WHEN
condition
Imperative-statements
WHEN
condition
Imperative-statements
END-SEARCH
----------------------------------------------------------------------------------------------------------------------------
01 TOOL-PRICE-OUT PIC $,$$$.99.
01 MIXED-TOOL-PRICE-LIST.
05 FILLER PIC X(15)
VALUE 'HAMMER 01099'.
05 FILLER PIC X(15)
VALUE 'SAW 01550'.
05 FILLER PIC X(15)
VALUE 'CHISEL 00795'.
05 FILLER PIC X(15)
VALUE 'PLANNER 00975'.
05 FILLER PIC X(15)
VALUE 'TOOL BELT 01500'.
05 FILLER PIC X(15)
VALUE 'SANDER 02725'.
05 FILLER PIC X(15)
VALUE 'BUFFER 03327'.
05 FILLER PIC X(15)
VALUE 'POLISHER 01774'.
05 FILLER PIC X(15)
VALUE 'PRY BAR 00923'.
05 FILLER PIC X(15)
VALUE 'CAR JACK 02327'.
05 FILLER PIC X(15)
VALUE 'PLUNGER 00850'.
05 FILLER PIC X(15)
VALUE 'AWL 01225'.
01 MIXED-TOOL-PRICE-TABLE REDEFINES
MIXED-TOOL-PRICE-LIST.
05 MIXED-TOOL-PRICE-GROUP
OCCURS 12 TIMES INDEXED BY PL.
10 NAME-OF-TOOL PIC X(10).
10 PRICE-OF-TOOL PIC 9(3)V99.
----------------------------------------------------------------------------------------------------------------------------
The INDEXED BY clause.
Indexes can be used like subscripts for initializing, updating and referencing data in an array.
The SEARCH verb requires a table with an INDEXED BY clause.
----------------------------------------------------------------------------------------------------------------------------
INDEX stuff
Examples:
SET PL TO 1
SET PL TO 6
SET PL UP BY 1
SET PL DOWN BY 1
PERFORM VARYING PL FROM 1 BY 1 UNTIL PL > SIZE-OF-TABLE
----------------------------------------------------------------------------------------------------------------------------
The SEARCH verb looking for a POLISHER in the tool price list.
SET PL TO 1
SEARCH MIXED-TOOL-PRICE-GROUP
AT END DISPLAY 'POLISHER
NOT FOUND'
WHEN NAME-OF-TOOL(X) =
'POLISHER'
MOVE PRICE-OF-TOOL(X) TO TOOL-PRICE-OUT
DISPLAY NAME-OF-TOOL (X) ' COSTS ' TOOL-PRICE-OUT
END-SEARCH
SET PL TO 9
---------------------------------------------------------------------------------------------------------------------------
The following SEARCH code will display all tools from the table
priced less than $15.
SET PL TO 1
MOVE SPACES TO STOP-FLAG
PERFORM UNTIL STOP-FLAG = 'STOP'
SEARCH MIXED-TOOL-PRICE-GROUP
AT END MOVE 'STOP' TO STOP-FLAG
WHEN PRICE-OF-TOOL (X) < 15.00
MOVE PRICE-OF-TOOL(X)
TO TOOL-PRICE-OUT
DISPLAY NAME-OF-TOOL
(X) ' COSTS ' TOOL-PRICE-OUT
END-SEARCH
SET PL UP BY 1
END-PERFORM
---------------------------------------------------------------------------------------------------------------------------
BINARY SEARCH TABLE
Must be ordered by at least one field within the table.
Binary searching works by mathematically guessing where the
data will be found.
The first guess is at the half way-point of the list.
If the item sought is not there, an adjustment is made pick
the next half-way point.
01 ORDERED-TOOL-PRICE-LIST.
05 FILLER PIC X(15) VALUE 'AWL
01225'.
05 FILLER PIC X(15) VALUE 'BUFFER
03327'.
05 FILLER PIC X(15) VALUE 'CAR JACK
02327'.
05 FILLER PIC X(15) VALUE 'CHISEL
00795'.
05 FILLER PIC X(15) VALUE 'HAMMER
01099'.
05 FILLER PIC X(15) VALUE 'PLANNER
00975'.
05 FILLER PIC X(15) VALUE 'PLUNGER
00850'.
05 FILLER PIC X(15) VALUE 'POLISHER
01774'.
05 FILLER PIC X(15) VALUE 'PRY BAR
00923'.
05 FILLER PIC X(15) VALUE 'SANDER
02725'.
05 FILLER PIC X(15) VALUE 'SAW
01550'.
05 FILLER PIC X(15) VALUE 'TOOL BELT 01500'.
01 ORDERED-TOOL-PRICE-TABLE REDEFINES ORDERED-TOOL-PRICE-LIST.
05 ORDERED-TOOL-PRICE-GROUP
ASCENDING KEY IS
NAME-OF-TOOL
OCCURS 12 TIMES.
10 NAME-OF-TOOL
PIC X(10).
10 PRICE-OF-TOOL
PIC 9(3)V99.
---------------------------------------------------------------------------------------------------------------------------
ASCENDING KEY key-1, key-2, etc
DESCENDING KEY key-x, key-y, etc
COBOL format for the SEARCH ALL
SEARCH ALL table
AT END imperative-statements
WHEN key-1 field (PL) = search_value1
[AND key-2 field(PL)
= search_value2]
Imperative-statements
END-SEARCH
The Key-field must be in the KEY phrase of the table.
If the item is found, the index is set to the location of the
item in the array.
If the item is not found, the index value is not predictable.
---------------------------------------------------------------------------------------------------------------------------
The following does a binary search for the table entry
SEARCH ALL ORDERED-TOOL-PRICE-GROUP
AT END DISPLAY 'POLISHER NOT FOUND'
WHEN NAME-OF-TOOL(X) = 'POLISHER'
MOVE PRICE-OF-TOOL(X) TO TOOL-PRICE-OUT
DISPLAY NAME-OF-TOOL (X) ' COSTS
' TOOL-PRICE-OUT
END-SEARCH
---------------------------------------------------------------------------------------------------------------------------