• Iterating an array

    From Bruce Axtens@21:1/5 to All on Wed Sep 15 13:13:51 2021
    So I have an array created by defining with an occurs. Let's say I have
    OCCURS 10 TIMES. When it comes to the PERFORM VARYING (or whatever) is
    there a way to iterate through the rows in the array without specifying
    the same number of rows in the PERFORM, that is, the compiler knowing
    how many rows are defined in WORKING-STORAGE, it can limit the number of iterations in the PERFORM?

    Bruce

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Bruce Axtens@21:1/5 to Bruce Axtens on Wed Sep 15 21:05:30 2021
    Bruce Axtens wrote:
    So I have an array created by defining with an occurs.

    And this is what I ended up with (so far)

    IDENTIFICATION DIVISION.

    PROGRAM-ID. HelloWorldTests.

    ENVIRONMENT DIVISION.

    DATA DIVISION.

    WORKING-STORAGE SECTION.

    01 Hello PIC X(13).

    01 WS-CNT PIC 9 VALUE 0.

    01 WS-MAX PIC 9 VALUE 0.

    01 Tests.

    03 Test1.

    05 WS-T-Enabled PIC X VALUE '1'.

    05 WS-T-Name PIC X(5) VALUE 'Test1'.

    05 WS-T-Func PIC X(10) VALUE 'HelloWorld'.

    05 WS-T-Answer PIC X(13) VALUE 'Hello, World!'.

    03 Test2.

    05 WS-T-Enabled PIC X VALUE '0'.

    05 WS-T-Name PIC X(5) VALUE 'Test1'.

    05 WS-T-Func PIC X(10) VALUE 'HelloWorld'.

    05 WS-T-Answer PIC X(13) VALUE 'Hello, World!'.

    01 TestGroup REDEFINES Tests.

    03 TestList OCCURS 2 TIMES.

    05 WS-TL-Enabled PIC X.

    05 WS-TL-Name PIC X(5).

    05 WS-TL-Func PIC X(10).

    05 WS-TL-Answer PIC X(13).

    01 TestItem.

    03 WS-TI-Enabled PIC X.

    03 WS-TI-Name PIC X(5).

    03 WS-TI-Func PIC X(10).

    03 WS-TI-Answer PIC X(13).

    PROCEDURE DIVISION.

    COMPUTE WS-MAX = LENGTH OF TestGroup / LENGTH OF Test1.

    PERFORM 10-TEST

    VARYING WS-CNT

    FROM 1

    BY 1

    UNTIL WS-CNT > WS-MAX

    STOP RUN.

    10-TEST.

    MOVE TestList(WS-CNT) TO TestItem.

    IF WS-TI-Enabled = '1'

    CALL WS-TI-Func USING BY REFERENCE Hello

    IF Hello = WS-TI-Answer

    DISPLAY "Pass"

    ELSE

    DISPLAY "Fail"

    END-IF

    END-IF.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From docdwarf@panix.com@21:1/5 to bugmagnet@outlook.com on Wed Sep 15 18:18:03 2021
    In article <shsr2t$r7p$1@dont-email.me>,
    Bruce Axtens <bugmagnet@outlook.com> wrote:

    [snip]

    03 TestList OCCURS 2 TIMES.

    03 TestList OCCURS WS-NC-2 TIMES.


    05 WS-TL-Enabled PIC X.

    05 WS-TL-Name PIC X(5).

    05 WS-TL-Func PIC X(10).

    05 WS-TL-Answer PIC X(13).

    01 TestItem.

    03 WS-TI-Enabled PIC X.

    03 WS-TI-Name PIC X(5).

    03 WS-TI-Func PIC X(10).

    03 WS-TI-Answer PIC X(13).

    01 WS-NUMERIC-CONSTANTS.
    05 WS-NC-1 PIC 9 VALUE 1.
    05 WS-NC-2 PIC 9 VALUE 2.
    05 WS-NC-3 PIC 9 VALUE 3.
    etc.


    PROCEDURE DIVISION.

    COMPUTE WS-MAX = LENGTH OF TestGroup / LENGTH OF Test1.

    PERFORM 10-TEST

    VARYING WS-CNT

    FROM 1

    BY 1

    UNTIL WS-CNT > WS-MAX

    PERFORM 10-TEST
    VARYING SUB1 FROM 1 BY 1
    UNTIL SUB1 > WS-NC-2.


    etc.

    DD

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Rick Smith@21:1/5 to bruce....@gmail.com on Wed Sep 15 11:23:13 2021
    On Wednesday, September 15, 2021 at 1:13:59 AM UTC-4, bruce....@gmail.com wrote:
    So I have an array created by defining with an occurs. Let's say I have OCCURS 10 TIMES. When it comes to the PERFORM VARYING (or whatever) is
    there a way to iterate through the rows in the array without specifying
    the same number of rows in the PERFORM, that is, the compiler knowing
    how many rows are defined in WORKING-STORAGE, it can limit the number of iterations in the PERFORM?

    COBOL tables are often defined to be larger than the apparent
    need because the number of entries may be variable. That is,
    a table may be defined as OCCURS 100, when the number of
    entries determined during design may be 1 to 50. Sometimes
    designs change.

    It is not uncommon to define both a limit and a count for
    the number of entries available and used, respectively.
    For example,

    01 t1-limit comp pic 9(4) value 100.
    01 t1-count comp pic 9(4) value 0.
    01 t1-index comp pic 9(4) value 0.
    01 t1-table.
    03 t1-entry occurs 100.
    05 (the description of the entry)

    When loading a table, one may do something like.

    add-entry.
    if t1-count not > t1-limit
    add 1 to t1-count
    move new-entry to t1-entry (t1-count)
    else
    perform error-proc-t1-no-space
    end-if
    .

    When using PERFORM to find an entry, one may do.

    find-entry.
    perform varying t1-index from 1 by 1
    until t1-index > t1-count
    or (whatever search criteria)
    end-perform
    .

    Tables are not just in the WORKING-STORAGE SECTION, they
    may be placed in the FILE SECTION, LOCAL-STORAGE SECTION
    and LINKAGE SECTION.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From Bruce Axtens@21:1/5 to Rick Smith on Thu Sep 16 13:38:51 2021
    Rick Smith wrote:
    On Wednesday, September 15, 2021 at 1:13:59 AM UTC-4, bruce....@gmail.com wrote:

    So best practice then is to oversize the array and read the data in from somewhere, keeping track of how much is read in and then iterating the
    table accordingly? I'm fine with that.

    I've just begun the COBOL track on https://exercism.org . I learned
    COBOL on a VAX-11 back in the early 1980s but never got to use it to
    earn a living. I'm hardly the best qualified for creating the track but
    I'm giving it my best anyway.

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)
  • From docdwarf@panix.com@21:1/5 to bruce.axtens@gmail.com on Thu Sep 16 12:10:56 2021
    In article <shul9b$10e$1@dont-email.me>,
    Bruce Axtens <bruce.axtens@gmail.com> wrote:
    Rick Smith wrote:
    On Wednesday, September 15, 2021 at 1:13:59 AM UTC-4, bruce....@gmail.com wrote:

    So best practice then is to oversize the array and read the data in from >somewhere, keeping track of how much is read in and then iterating the
    table accordingly? I'm fine with that.

    You've got the general idea down fairly well. Tables are intended to keep small amounts of frequently- and rapidly-needed data available in core (remember core?) so as to cut down the time and I/O needed for file
    access. Think of a small shipping company, 700, 800 clients, each of
    which has its own discount. How do you process a week's orders and make
    sure folks get what they deserve?

    DD

    --- SoupGate-Win32 v1.05
    * Origin: fsxNet Usenet Gateway (21:1/5)