Page 1 of 1

INDEX and PERFORM...VARYING

PostPosted: Thu Mar 28, 2013 8:44 pm
by abnk
Hi, all:


First off, thank you for providing this resource.

I'm having a bit of trouble comprehending indexes and PERFORM...VARYING statements. I'm using Cobol Unleashed as a resource, but the examples there are apparently too advanced for me. I also looked the manuals and searched this forum.

This is what I have:

01  ORG-TABLE.
    05  RECORD-KEY.
        10  REC-KEY        PIC XXX.
        10  DEPT           PIC X(5).
    05  OFFICES         PIC X(5000).


New office codes begin every 9 characters. Think of it as:

   05 OFFICES OCCURS 87 TIMES.
       10  OFF-CODE1          PIC X(4).
       10  OFF-CODE2          PIC X(5).


So, each office will have up to 87 names.

I want to MOVE DEPT AND OFFICES TO the field below until spaces are encountered:

01  WORKING-STORAGE
    05 DEPT-AND-OFFICE          PIC X(14).


Then DISPLAY DEPT-AND-OFFICE as follows:

SALES000100001
SALES000T00003
SALESR00041100
...
MAINT000100001
MAINT000R00040
MAINT0M0091100


Any help you can provide will be appreciated.

Re: INDEX and PERFORM...VARYING

PostPosted: Thu Mar 28, 2013 10:34 pm
by Quasar
I did not quite understand your post completely. But, I presume you are trying the build and store data the OFFICES array. This is how you would do it -

PERFORM VARYING WS-I FROM 01 BY 09 UNTIL DEPT-AND-OFFICE = SPACES
   MOVE DEPT-AND-OFFICE(01:05) TO DEPT
   MOVE DEPT-AND-OFFICE(06:09) TO OFFICES(WS-I:09)
END-PERFORM


Thank you very much.

Re: INDEX and PERFORM...VARYING

PostPosted: Thu Mar 28, 2013 10:45 pm
by Robert Sample
I think part of your problem comes from not having data structures defined correctly. A table key should, but does not have to be, a unique value (as long as you are doing sequential searches). It is not clear from what you posted whether there will be up to 87 code1 and code2 values per department, or if there is 1 code1 / code2 combination per department.

Assuming the latter, one possible way (but certainly NOT the only way) to define and access the data you posted would be:
01  ORG-TABLE.
     05  ORG-DATA OCCURS 5000
                  INDEXED BY ORG-NDX, ORG-LOC.
        10  ORG-DEPT PIC X(05).
        10  ORG-CODE1 PIC X(04).
        10  ORG-CODE2 PIC X(05).
Procedure Division:
MOVE SPACES TO ORG-TABLE.
<load the table from a file or however you are loading it>
SET ORG-NDX TO 1.
SEARCH ORG-DATA
     WHEN ORG-DEPT (ORG-NDX) = <your variable to find>
        MOVE ORG-DEPT TO DEPT-AND-OFFICE (1 : 5)
        MOVE ORG-CODE1 TO DEPT-AND-OFFICE (6 : 4)
        MOVE ORG-CODE2 TO DEPT-AND-OFFICE (10 :)
END-SEARCH
and continue from ORG-NDX until ORG-DEPT (ORG-NDX) does not match <your variabe to find>

Re: INDEX and PERFORM...VARYING

PostPosted: Thu Mar 28, 2013 11:26 pm
by pmartyn
Robert is correct "I think part of your problem comes from not having data structures defined correctly "
There are other problems such as your table only being 87 instances yet your input can hold up to 555 entries.

Alas, here is another alternative for your requirement.
This code moves your X(5000) into the array for processing.
Then moves the instances of the array to the output layout for display
Note: rather than display you can put it out to a file or whatever.

I am hoping that this code will at least get you going in the right direction.
PM

DATA DIVISION
             
01  ORG-TABLE.                                            <<== your defined input
    05  RECORD-KEY.
        10  REC-KEY        PIC XXX.
        10  DEPT           PIC X(5).
    05  OFFICES         PIC X(5000).
                             
01  WORKING-STORAGE
    05 DEPT-AND-OFFICE     PIC X(14).
    05 WS-DEPT-AND-OFFICE  REDEFINES DEPT-AND-OFFICE.
       10 WS-DEPT          PIC X(05).
       10 WS-DPT-CODE1     PIC X(04).
       10 WS-DPT-CODE2     PIC X(05).
    05 WS-SUB1             PIC S999  VALUE +0.
    05 WS-OFFICES OCCURS 555 TIMES.
       10 WS-OFF-CODE1     PIC X(4)
       10 WS-OFF-CODE2     PIC X(5).

* THE FOLLOWING IS OVERFLOW PROTECTION FOR  GROUP TO ARRAY MOVE     

    05 FILLER               PIC X(500)  VALUE SPACES.     


PROCEDURE DIVISION

 
      MOVE OFFICES TO WS-OFFICES                          << == GROUP TO ARRAY MOVE
      PERFORM 2000-FORMAT-LAYOUT VARYING WS-SUB1 FROM 1 BY 1
                       UNTIL WS-OFF-CODE1(WS-SUB1) = SPACES  OR  WS-SUB1 => 555.
2000-FORMAT-LAYOUT.
    MOVE DEPT TO WS-DEPT.
    MOVE WS-OFF-CODE1(WS-SUB1)   TO WS-DPT-CODE1.
    MOVE WS-OFF-CODE2(WS-SUB1)   TO WS-DPT-CODE2.   
 
    DISPLAY DEPT-AND-OFFICE.

Re: INDEX and PERFORM...VARYING

PostPosted: Fri Mar 29, 2013 1:57 am
by NicC
I would also advise that having a variable called WORKING-STORAGE is bad as it could be confused with the WORKING-STORAGE SECTION name.

Re: INDEX and PERFORM...VARYING

PostPosted: Fri Mar 29, 2013 5:20 am
by BillyBoyo
You may be able to tell that we don't necessarily understand what you are trying to do.

Your first step is definitely to get your data structures sorted out. We have no idea how the OCCURS 87 and the 5000 relate to each other.

Separately from sorting out the data definition, get to know how to hand "tables" and "subscripting" by starting out with something very easy and becoming very familiar with it.

This you may have to read through several times, but don't worry. It does have some element of confusion, as you'll see from the explanation, but get some grip on it first, then try the really simple example, and through that become familiar with how to use single-dimension Cobol "subscripting". You'll use it a lot. There are a few more dimensions available, but leave those aside for now.

To reference data within a table (a data structure with OCCURS) you use "subscripting".

There are three ways to specify a subscript: a literal; a subscript (numeric data-name not directly related to table); an index (compiler-defined and managed storage, connected to table by name you give it).

DISPLAY TABLE-ENTRY ( 1 )
DISPLAY TABLE-ENTRY ( W-DESRIPTIVE-NAME-SUB )
DISPLAY TABLE-ENTRY ( I-DESCRIPTIVE-NAME-INDEX )

These uses are all called "subscripting" although using an index is also sometimes called "indexing".

A "subscript" is just a numeric item that you define. It is best if it is BINARY or COMP or COMP-4 or COMP-5. It's value when reference a table should be between 1 (one) and the maximum number of table entries. As it is a "normal" data definition, you can use all the normal verbs to manipulate it.

An "index" is defined by INDEXED BY on the OCCURS clause of the table. The Compiler defines the storage for it. You can only change the value of an index by SET, PERFORM ... VARYING ... and SEARCH/SEARCH ALL. An index can be used in conditions and of course for subscripting.

To add a little complexity, there is also USAGE INDEX. This is a field that you define in the DATA DIVISION but which has no PICture clause (meaning the Compiler defines the size and type of the storage). This, using the SET statement, can be used to store the value of an index (an INDEXED BY item), for instance the maxiumum number of entries in a table, expressed as an INDEX.

What does "expressed as an INDEX mean"? This relates to the difference between a subscript and an index. A subscript is just an integer. An index is the "offset" or "displacement" from the start of the table of the particular entry in the table whose value it is SET to.

If you SET an index to 1, the actual content of the index is zero, indicating the entry which is displacement zero from the start of the table, ie the first entry. If you SET an index to 2, the actual content of the index is the length of the entry, ie a displacement from the start of the table which arrives at the 2nd entry. SET an index to 3, and it has the value 2 times entry-length. Etc.

When you SET a USAGE INDEX item to the value of an index name, the "displacement" that the index contains is preserved in the USAGE INDEX item. When you SET an index to a USAGE INDEX item, the compiler knows that it already contains a displacement.

With a SET to a non-USAGE INDEX value, the compiler knows it is an "entry", and calculates the displacement of that entry, and sets the value of the index to that.

This sounds more complicated than it is, partly because of the mixed-nomenclature (subscript, subscripting, index, indexing, USAGE INDEX) and partly because you just haven't done it yet.

Another confusion is "reference modification" which looks a bit like subscripting, but isn't. The longer you can avoid reference-modification, the better (there are examples already in this topic).

The thing to do is to read the manual, the book, try out something really simple, see what happens, and go back to the manual/book to see if you now understand, if not, try again.

01  THE-DIGITS PIC X(10) VALUE "0123456789".
01  FILLER REDEFINES THE-DIGITS.
    05  FILLER OCCURS 10 TIMES
               INDEXED BY I-DIGIT-IND.
        10  A-DIGIT PIC X.
01  W-DIGIT-SUBSCRIPT BINARY PIC 9(4).


You should try to come up with a number of ways to produce this output:

0
1
2
3
4
5
6
7
8
9


using DISPLAY A-DIGIT ( something )

As a start, here's the easiest

DISPLAY A-DIGIT ( 1 )
DISPLAY A-DIGIT ( 2 )
DISPLAY A-DIGIT ( 3 )
DISPLAY A-DIGIT ( 4 )
DISPLAY A-DIGIT ( 5 )
DISPLAY A-DIGIT ( 6 )
DISPLAY A-DIGIT ( 7 )
DISPLAY A-DIGIT ( 8 )
DISPLAY A-DIGIT ( 9 )
DISPLAY A-DIGIT ( 10 )


Don't worry if you don't get it first time, just be systematic. Read. Experiment. Read. Continue until understood. If you have problems, or are unclear about something, just post here.

Re: INDEX and PERFORM...VARYING

PostPosted: Fri Mar 29, 2013 10:20 pm
by abnk
Thank you, all.

Quasar, I am actually trying to do the opposite--MOVE DEPT and OFFICES TO DEPT-AND-OFFICE.

This is what I think it should be:

PERFORM VARYING OFFICES-IDX FROM 1 BY 1
    UNTIL OFFICES-IDX > 87 OR OFFICES(OFFICES-IDX) = SPACES
    MOVE DEPT TO DEPT-AND-OFFICE
    MOVE OFFICES(OFFICES-IDX) TO DEPT-AND-OFFICE
    DISPLAY DEPT-AND-OFFICE
END-PERFORM.



Robert Sample, sorry for the confusion of the data definition. There are 87 code1/code2 combinations for each department. Why PIC X(5000) and OCCURS 87 TIMES don't make sense, is actually a separate problem and perhaps I should have not added it here. I am READing from a variable length VSAM file. This is the actual copybook:

01  ORG-TABLE.
    05  RECORD-KEY.
        10  REC-KEY        PIC XXX.
        10  DEPT           PIC X(5).
   05 OFFICES OCCURS 87 TIMES.
       10  OFF-CODE1          PIC X(4).
       10  OFF-CODE2          PIC X(5).


However, I kept getting failures to read with this definition, so I changed the record length to the maximum length of the VSAM file, which is 5000. This way, I was able to get past the failure to read.

If I MOVE DEPT and OFFICES TO DEPT-AND-OFFICE (after increasing DEPT-AND-OFFICE to PIC X(788), [DEPT PIC(5) + OFFICES PIC X(9) * 87 occurrences]), the output is this (not actual values):

DEPT1OFF-CODE1.1OFF-CODE2.1OFF-CODE1.2OFF-CODE2.2OFF-CODE1.3OFF-CODE2.3...<<== until the 87th occurrence of OFFICES.


What I want is this:

DEPT1OFF-CODE1.1OFF-CODE2.1
DEPT1OFF-CODE1.2OFF-CODE2.2
DEPT1OFF-CODE1.3OFF-CODE2.3
...
DEPT1OFF-CODE1.87OFF-CODE2.87
DEPT2OFF-CODE1.1OFF-CODE2.1
...


I will read the rest of the replies carefully before replying.

Re: INDEX and PERFORM...VARYING

PostPosted: Fri Mar 29, 2013 11:02 pm
by Robert Sample
I am READing from a variable length VSAM file.
Does your COBOL program understand that the vSAM file is variable length? Look at the compiler output to see how the file is listed -- fixed or variable.

To make a file variable length, you must (1) provide more than one 01 level for the FD where at least one 01 in the FD has a different record length, or (2) use OCCURS DEPENDING ON in the 01 definition of the FD, or (3) use RECORD VARYING in the FD. Note that it is NOT enough to merely specify RECORD FORMAT V since this allows for fixed-length or variable length records, per the COBOL manual. The copy book you posted would NOT make the file variable length but fixed length, and the file read errors would make sense.

The data you posted looks like what would be expected for the data structure you described, although a mainframe COBOL program would NOT display the datga the way you showed. To get the output you want, you need to change your PROCEDURE DIVISION statements to
PERFORM VARYING OFFICES-IDX FROM 1 BY 1
    UNTIL OFFICES-IDX > 87 OR OFFICES(OFFICES-IDX) = SPACES
    DISPLAY DEPT OFFICES (OFFICES-IDX)
END-PERFORM.
There is no reason to have the DEPT-AND-OFFICE variable at all. DISPLAY can have one or more variables as well as one or more literals up to the compiler limit.

Re: INDEX and PERFORM...VARYING

PostPosted: Sat Mar 30, 2013 12:18 am
by abnk
pmartyn, thank you for taking the time you write the code. It helps.

NicC, thank you for the advice. I can see how that is confusing.

BillyBoyo, I read your post a few times and each time it makes more sense. It is exactly what I needed to read and more. I will practice with the example you provided. Thank you very much.