The COBOL-85 Tutorial, Chapter 8

Working with tables in COBOL.

Copyright © 1998-2017

Kim Kjærsulf.


This chapter (TOC)

Tables / arrays in COBOL
Table declaration.
The use of tables with subscripts.
Initializing tables.
Complete example.
Use of tables with indexes.
indexexample
Search.
Binary search.
Sequential search
Search example.
An example of a multi-dimensional table.
An example of how to initialize a complex table.
Exercises

Tables / arrays in COBOL

[This chapter] [TOC] [Tutorial]


As all other programming languages, COBOL has facilities for the declaration and use of tables (arrays). The standard procedure is to work with up to three dimensions, though different COBOL compilers support anything between 7 and 16 dimensions. In COBOL you can also specify that a table is to have a sorting key, which makes it possible to make binary searches with the SEARCH statement.



Table declaration.

[This chapter] [TOC] [Tutorial]


A table is defined in the same way as other data fields or records, but with the stating of a certain number of OCCURS. It is possible to specify a variable that hold the actual number of currently used entries, though note that this does not save memory.



The use of tables with subscripts.

[This chapter] [TOC] [Tutorial]


This example shows a simple data field, which is repeated ten times:
01  FIELD  PIC X(10) OCCURS 10.

It is then possible to refer to each entry as follows:
MOVE SPACE TO FIELD (3).
or
MOVE FIELD (4) TO LINE.

Note that the possibilities for stating a calculation expression for the subscript are extremely limited.


Initializing tables.

[This chapter] [TOC] [Tutorial]


There are at least three ways of initializing a table:

1.
By using INITIALIZE, which refers to a higher level. All fields in the table are initialized in accordance with their data type. Normally, alphanumeric fields are set to SPACE and numeric to ZERO, but this is not mandatory.

2.
By using VALUE, as in the main example below.
3.
Or as in this example:
	01 week.
	    03  day pic x(8) occurs 7 
			value from (1)	"monday" "tuesday" 
						"wednesday" "thursday"
						"friday" "saturday"
						"sunday".

This example is not applicable to all compilers.


Complete example :

[This chapter] [TOC] [Tutorial]


      * Example of working with tables in COBOL.
       identification division.
      *  ------------ program identication.
       program-id.    table.
       author.        kik.
       environment division.
      *  ------------ program environment.
       configuration section.
       special-names.
           console is crt
           decimal-point is comma.
       data division.
       working-storage section.
       77  in-1      pic 9999.
       77  in-2      pic 9999.
       77  tel       pic 99.
       77  lin       pic 99.

       01  result    pic s9(6) occurs 5.

       01  res-texts.
           03  filler pic x(15) value "Addition". 
           03  filler pic x(15) value "Difference". 
           03  filler pic x(15) value "Quotient".
           03  filler pic x(15) value "Remainder".
           03  filler pic x(15) value "Product".
       01  res-text  redefines res-texts pic x(15) occurs 5.

       01  Out-field.
           03  text      pic x(15).
           03  tal1      pic ---.--9.

       procedure division.
      *  ------------ executable instructions.
       main section.
           display space.

           display "Enter 1st figure :" line 5 position 10.
           accept in-1 line 5 position 27.
           display "Enter 2nd figure :" line 6 position 10.
           accept in-2 line 6 position 27.

           add in-1, in-2 giving result (1).
           subtract in-2 from in-1 giving result (2).
           divide in-1 into in-2 
                   giving result (3) remainder result (4).
           multiply in-1 by in-2 giving result (5).

           perform varying tel from 1 by 1 until tel > 5
               move space to Out-field 
               move res-text (tel) to text
               move result (tel) to tal1
               add tel, 7 giving lin
               display Out-field line lin position 1
               end-perform.

           exit program.


Use of tables with indexes.

[This chapter] [TOC] [Tutorial]


Already during the declaration phase it is possible to establish an index variable for a table.

01  FIELD  PIC X(10) OCCURS 10 INDEXED BY IDX.

It is then possible to refer to each entry in the following manner:
SET IDX TO 3.
MOVE SPACE TO FIELD (IDX) .

or
SET IDX UP BY 1.
MOVE FIELD (IDX) TO LINE.

Note that the possibilities for stating a calculation expression for the index are extremely limited. The advantage of adding an index field is that you avoid using a wrong index for a table "by mistake"; the price to be paid for this is that there are some restrictions, primarily that these index fields cannot be used in MOVE statements or calculations.



index example.

[This chapter] [TOC] [Tutorial]


      * Example of working with tables in COBOL.
       identification division.
      *  ------------ program indentifiaction.
       program-id.    table.
       author.        kik.
       environment division.
      *  ------------ program environment.
       configuration section.
       special-names.
           console is crt
           decimal-point is comma.
       data division.
       working-storage section.
       77  in-1      pic 9999.
       77  in-2      pic 9999.
       77  lin       pic 99.

       01  result   pic s9(6) occurs 5 indexed by tel1.

       01  res-texts.
           03  filler pic x(15) value "Addition". 
           03  filler pic x(15) value "Difference". 
           03  filler pic x(15) value "Quotient".
           03  filler pic x(15) value "Remainder".
           03  filler pic x(15) value "Product".
       01  res-text  redefines res-texts 
                         pic x(15) occurs 5 indexed by tel2.

       01  Out-field.
           03  text      pic x(15).
           03  tal1      pic ---.--9.

       procedure division.
      *  ------------ executable instructions.
       main section.
           display space.

           display "Enter 1st figure :" line 5 position 10.
           accept in-1 line 5 position 27.
           display "Enter 2nd figure :" line 6 position 10.
           accept in-2 line 6 position 27.

           add in-1, in-2 giving result (1).
           subtract in-2 from in-1 giving result (2).
           divide in-1 into in-2 
                   giving result (3) remainder result (4).
           multiply in-1 by in-2 giving result (5).

           perform varying tel1 from 1 by 1 until tel1 > 5
               move space to out-field
               set tel2 to tel1
               move res-text (tel2) to text
               move result (tel1) to tal1
               set lin to tel1
               add lin, 7 giving lin
               display Out-field line lin position 1
               end-perform.

           exit program.


Search.

[This chapter] [TOC] [Tutorial]


There are two variations of SEARCH:

The sequential search will work no matter how the values in the table are ordered, simply because the instruction will examine the entire table.
The binary search is very fast, but it requires that the values are ordered.


Binary Search.

[This chapter] [TOC] [Tutorial]


The binary search is very fast.
It split the array into two halves and determines which half that does not contain the value that are sought. The half that might contain the value is then split into halves, of which one is excluded. And so on until the value is found or not found. The not found is determined when an array part is to small to be split : it consist of just one value, that is not the one we are looking for.
With just 10 comparisons it is possible to find a value in an array with approximately 1000 values. With a little luck the value is found in less that 10 comparisons.
Note that with binary searches it is the programmer's responsibility to make sure that the contents of the table is sorted as defined in KEY when using OCCURS.


Sequential search.

[This chapter] [TOC] [Tutorial]


The sequential search is iterating through the values in the array until the end of the array or the value is found.


Search example.

[This chapter] [TOC] [Tutorial]


The following example involves three searches:

  1. A binary search to find the key.
  2. A sequential search which does not find the key (even though it does in fact exist).
  3. A sequential search which finds the key.
* Example of how to use SEARCH in a table in COBOL.
       identification division.
      *  ------------ program identification.
       program-id.    searchtab.
       author.        kik.
       environment division.
      *  ------------ program environment.
       configuration section.
       special-names.
           console is crt
           decimal-point is comma.
       data division.
       working-storage section.
       77  teller           pic 99.
       77  lin              pic 99.

       01  eot-code         pic 9 value 0.
           88  eot                value 1.
           88  not-eot            value 0.

       01  tabel occurs 50 ascending key is key 
                           indexed by idx.
           03  key       pic 999.
           03  text      pic x(10).

       procedure division.
      *  ------------ executable instructions.
       main section.
           display space.

           perform init-table varying idx from 1 by 1
                       until idx > 50.

      * Binary search :
          
           search all table
              when key (idx) is = 10 next sentence.

           set teller to idx.
           display "Key found in idx =" line 10 position 1.
           display teller line 10 position 24.

      * Sequential search from index = 10 and thereafter.
           move 15 to lin.
           perform sequ-search.

      * Sequential search from index = 1 and thereafter.
           set idx to 1.
           move 17 to lin.
           perform sequ-search.

           stop run.

       init-table.
           set key (idx) to idx.
           move space to text (idx).

       sequ-search.
           set not-eot to true.
           search table varying idx
              at end set eot to true
              when key (idx) = 5 next sentence.

           if not-eot then
              set teller to idx
              display "Key found in idx =" 
                               line lin position 1
              display teller line lin position 24
           else
              display "Key not found" line lin position 1.


An example of a multi-dimensional table.

[This chapter] [TOC] [Tutorial]


It is not actually possible to give a table several dimensions, but it is however easy to construct, for example, records with several dimensions. The following example shows how it is possible to construct a table consisting of these sorts of records:

01  Table occurs 10.
      03  field-1	   pic xxx.
      03  sub-table  pic 9(5) occurs 5.
      03  field-2	   pic 999.
It is then possible to refer to an entire record:
	table (idx)

or a field in it:
	field-1 (idx)

or a field in a sub-table:
	sub-table (idx1, idx2)

where idx1 refers to "table" and idx2 to the entry in the sub-table.


An example of how to initialize a complex table.

[This chapter] [TOC] [Tutorial]


Using VALUE when working with tables will allow the programmer to initialize only the first entry in a table. Standard practice is therefore to use a loop to initialize the entire table. If a table has to be initialized many times while a program is being executed it may well lead to significant strain on the CPU. It is therefore a good idea to use the technique outlined below which result in rapid initialization. This technique is somewhat tricky to code and is therefore normally only used to solve the problem outlined here.

The principle behind the technique is that a higher level is considered as one large alphanumeric field. When making a MOVE from a large field to one that is smaller, the excess bytes will be truncated automatically. The idea is to redefine the table so that all entries from 2 and thereafter are considered as an entity. It is then sufficient to initialise the first entry and then move the entire table into itself (from the second entry). This will allow the initialization value to be spread down through the table with the help of just one MOVE instruction.

01  source.
    03  table	occurs 100.	(The table used in the program)
        05  s-1 ........
        05  s-2 ........

01  x redefines source.		(for purposes of initialisation only)
    03  dummy.
        05  filler ......		(defined as s-1)
        05  filler ......		(defined as s-2)
    03  target.
        05  filler .... occurs 99.	(defined as s-1)
        05  filler .... occurs 99.	(defined as s-2)
.
.
.

move ... to s-1.				(First entry is initialised)
move ... to s-2.

move source to target.			(First entry is "spread")


Exercise 1.

[This chapter] [TOC] [Tutorial]


Solve this exercise by using a table and a local subprogram.
You will find the basis for this exercise in chapter 6.

The purpose of this exercise is to train the following points:

Design a program with which you can:

File description:

Physical file-name: "SEQUDATA"

Record layout:
Customer number, 4 characters, value set: 0-9999.
Transaction code, 2 characters, value set: 1, 2, 3, 4, 99.
Movement, 6 characters + 2 decimals (no decimal point).
Balance, 6 characters + 2 decimals (no decimal point).

Comments:
The file is not to be sorted.
The "Movement" field should only apply to transaction codes 1-4.
The "Balance" field should only relate to transaction code 99.
Here is an extract of the file:

	4711010001230000000000
	7100020011002500000000
	5500990000000000043200

Model answer for this exercise.


Copyright © 1998-2017

Kim Kjærsulf


Last Updated october 3, 2003
For more information contact: Kim Kjærsulf