Two-dimensional variable-length array in Cobol

30,303

Solution 1

What you are trying to define is a "Complex Occurs Depending On" structure (complex ODO).

You may define a Complex ODO where the table is rectaguar as follows:

       01  TABLE-REC.
05 M PIC S9(4) BINARY. 05 N PIC S9(4) BINARY. 05 ROWS OCCURS 10 TIMES DEPENDING ON M. 10 COLUMNS OCCURS 10 TIMES DEPENDING ON N. 20 CELL PIC X(1).

The trick is that the declaration of N cannot occur within the variable part of the table. For example, the following declaration:

       01  TABLE-REC.
           05  M             PIC S9(4) BINARY.
           05  ROWS OCCURS 1 TO 10 TIMES DEPENDING ON M.
               10 N          PIC S9(4) BINARY
               10 COLUMNS OCCURS 1 TO 10 TIMES DEPENDING ON N.
                  20 CELL PIC X(1).

will give you an error because the declaration implies that each row may contain a different number of columns (ie. not a rectangular table).

In general, there is a lot of confusion as to what an ODO structure in COBOL really "buys" you. There is a common, but mistaken view, that it may be used to save memory because the size of the data structure can be dynamically sized. This is absolutely false when the ODO is declared under LOCAL or WORKING STORAGE. The COBOL compiler will allocate enough memory to accomodate the largest value of M and N.

What it does "buy" you is a mechanism to physically organize data in memory. Look at the following program and what it displays:

       IDENTIFICATION DIVISION.
         PROGRAM-ID. EXODO.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       77  I                 PIC S9(4) BINARY.
       77  J                 PIC S9(4) BINARY.
       01  DIMENSIONS.
           05  M             PIC S9(4) BINARY VALUE 6.
           05  N             PIC S9(4) BINARY VALUE 7.
       01  TABLE-REC-1.
           05  ROWS OCCURS 1 TO 10 TIMES DEPENDING ON M.
               10 COLUMNS OCCURS 1 TO 10 TIMES DEPENDING ON N.
                  20 CELL PIC X(1).
       01  TABLE-REC-2.
           05  ROWS OCCURS 10 TIMES.
               10 COLUMNS OCCURS 10 TIMES.
                  20 CELL PIC X(1).
       PROCEDURE DIVISION.
           PERFORM VARYING I FROM 1 BY 1 UNTIL I > M
              PERFORM VARYING J FROM 1 BY 1 UNTIL J > N
                 MOVE 'X' TO CELL OF TABLE-REC-1 (I J)
                 MOVE 'X' TO CELL OF TABLE-REC-2 (I J)
              END-PERFORM
           END-PERFORM
           DISPLAY TABLE-REC-1
           DISPLAY TABLE-REC-2
           GOBACK
           .

Displays:

    XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX
    XXXXXXX   XXXXXXX   XXXXXXX   XXXXXXX   XXXXXXX   XXXXXXX

Notice the ODO version has all of the data nicely compated into a 6 X 7 matrix while the fixed table version retains the 10 X 10 matrix with a bunch of "holes" in it to fill out each row to its maximum number of OCCURS. There are times when this distinction is important (most often it isn't though).

I see you are using Net Express, which I am not familiar with so you may have to fiddle around to get the next part to work. With IBM Enterprise COBOL for Z/OS you can do the following:

Define an ODO in the program LINKAGE SECTION so no memory is allocated, it is just a record layout. Then you can dynamically allocate enough memory for the actual size of table needed (ie. M times N elements). Connect the two using something like: SET ADDRESS OF ODO-DATA-STRUCTURE TO mem-address (under CICS use GETMAIN and under batch use CEEGTST to obtain memory). Now you have a dynamic data structure that does use the minimum amount of space and will still index properly because of the layout propreties illustrated above.

There are other ways of using (or not using) ODO's in COBOL but these are the most common ones I am aware of.

Solution 2

you can define multi-dimensional variable length array by defining OCCURS.. DEPENDING ON on every level of dimension you wish to go.

Share:
30,303
James P.
Author by

James P.

Updated on June 09, 2020

Comments

  • James P.
    James P. almost 4 years

    How do you go about defining a two-dimensional MxN array in Cobol of which both M and N are of variable length?

    Here's the message I get in Net Express when attempting to have a variable array inside another:

    COBCH0144S OCCURS DEPENDING subsidiary to OCCURS only allowed with ODOSLIDE
    
    • James P.
      James P. about 14 years
      It's true that Cobol is an old language. However it is possible to define variable-length arrays/tables (see NealB's reply) without the memory allocation tricks that are used in dynamic arrays.
  • James P.
    James P. about 14 years
    Thank you for the explanation NealB. Following research, it turns out that Net Express requires a compiler directive (ODOSLIDE) in a project in order to compile a structure that has a nested Occurs Depending On.