IBM Mainframe Forum Index
 
Log In
 
IBM Mainframe Forum Index Mainframe: Search IBM Mainframe Forum: FAQ Register
 

Help in loading a PS file into 3 dimensional Table


IBM Mainframe Forums -> COBOL Programming
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
ankit9jain

New User


Joined: 20 Jan 2009
Posts: 17
Location: India

PostPosted: Fri Jan 29, 2010 3:19 pm
Reply with quote

hi,
i have below table definition in the code
Code:
01 WS-RULEDEF-TABLE.
          05 WS-DEF-CNT                 PIC 9(01) COMP SYNC VALUE ZERO.
          05 WS-DESC-CNT                PIC 9(02) COMP SYNC VALUE ZERO.
          05 WS-DTL-CNT                 PIC 9(02) COMP SYNC VALUE ZERO.
          05 WS-DEF-TABLE               OCCURS 1 TO 9 TIMES
                                        DEPENDING ON WS-DEF-CNT
                                        INDEXED   BY WS-DEF-IDX.

             10 WS-DEF-NAME             PIC X(15).
             10 WS-DEF-KEY              PIC X(10).
             10 WS-DEF-K-VAL            PIC X(20).

             10 WS-RULEDESC-TABLE.
                15 WS-DESC-TABLE        OCCURS 1 TO 99 TIMES
                                        DEPENDING ON WS-DESC-CNT
                                        INDEXED   BY WS-DESC-IDX.
                20 WS-DESC-NAME         PIC X(08).
                20 WS-DESC-DTL          PIC X(30).
                20 WS-DESC-SUB-CNT      PIC 9(02) COMP SYNC VALUE ZERO.

                20 WS-RULEDTL-TABLE.
                   25 WS-DTL-TABLE      OCCURS 1 TO 99 TIMES
                                        DEPENDING ON WS-DTL-CNT
                                        INDEXED   BY WS-DTL-IDX.
      *
                   30 WS-DTL-TYPE       PIC X(03).
                   30 WS-DTL-SC         PIC X(03).
                   30 WS-DTL-EC         PIC X(03).
                   30 WS-DTL-VALUE      PIC X(10).


My input file looks like

Code:
Main-Record-1
        Record-1
           sub-record-1
           sub-record-2
        Record-2
        .....
Main-Record-2
        Record-1
          sub-record-1
        Record-2
          .....



i am trying to load the table like below

Code:
move record(1:5) into temp-var
evaluate temp-var
  when 'main'
       ADD +1                   TO WS-DEF-CNT
       SET WS-DEF-IDX           TO WS-DEF-CNT
       MOVE record(1:15)        TO WS-DEF-NAME(WS-DEF-IDX)
       MOVE ZEROES              TO WS-DESC-CNT
  when 'Recor'
       ADD +1                     TO WS-DESC-CNT
       SET WS-DESC-IDX            TO WS-DESC-CNT
       move record(1:8)           to WS-DESC-DTL(WS-DEF-IDX,WS-DESC-IDX)
       MOVE ZEROES              TO WS-DTL-CNT
  when 'sub-r'
       ADD +1                   TO WS-DTL-CNT
       SET WS-DTL-IDX           TO WS-DTL-CNT
       move record(1:3)         to WS-DTL-TYPE(WS-DEF-IDX,WS-DESC-IDX,WS-DTL-IDX)
End-Evaluate.


When i am trying to do Search in the table
Code:
            PERFORM VARYING WS-DEF-IDX FROM 1 BY 1
            UNTIL (WS-DEF-IDX EQUAL (WS-DEF-CNT + 1))
              PERFORM VARYING WS-DESC-IDX FROM 1 BY 1
              UNTIL (WS-DESC-IDX EQUAL (WS-DESC-CNT + 1))
                SET WS-DTL-IDX                 TO 1
                SEARCH WS-DTL-TABLE
                 WHEN WS-DTL-type(WS-DEF-IDX,WS-DESC-IDX,WS-DTL-IDX)
                 EQUAL TO WS-TEMP9
                 .....

                END-SEARCH
              END-PERFORM
            END-PERFORM.

when i am trying above search routine, its not working properly as in XPD editor
it shows INDEX TOO HIGH as soon as WS-DTL-IDX values becomes 2, and thus yielding
improper results.

could someone help me on this? it looks like while loading the PS file, i am doing
some mistake but not able to trace it back.
Back to top
View user's profile Send private message
dick scherrer

Moderator Emeritus


Joined: 23 Nov 2006
Posts: 19244
Location: Inside the Matrix

PostPosted: Fri Jan 29, 2010 10:02 pm
Reply with quote

Hello,

The "sample" data is indented but the temp-var is built only from the first 5 positions icon_confused.gif
Back to top
View user's profile Send private message
Robert Sample

Global Moderator


Joined: 06 Jun 2008
Posts: 8697
Location: Dubuque, Iowa, USA

PostPosted: Sat Jan 30, 2010 1:13 am
Reply with quote

I see several issues that need to be addressed:

1. As Dick says, you're using reference modification to check the first bytes of the data record, yet they are indented in your example so you will never get any matches and your counts are all going to be zero.

2. Using a variable number of occurrences makes no sense since the storage will be allocated anyway -- and it complicates the code.

3. It is not clear from your post just what is supposed to be in WS-DTL-TYPE; I hope this is due to your extracting code but it's impossible to tell. And nothing is loaded into WS-DTL-SC, WS-DTL-RC, WS-DTL-VALUE so who knows if the posted code is anywhere near what you want to do.

4. Even if the indentation issue is addressed, your code looks for MAIN while the file contains MAIN- so there will never be any increment to WS-DEF-CNT.
Back to top
View user's profile Send private message
ankit9jain

New User


Joined: 20 Jan 2009
Posts: 17
Location: India

PostPosted: Sat Jan 30, 2010 11:13 am
Reply with quote

Hi Dick and Robert, thanks for ur responses

first of all, i gave the sample file in the intended format just to avoid confusion and add clarity to the input file format. Sorry if i confused you by this. input file is not indented.

2nd, sorry as i mentioned but it should have been "Main-".

for the 3rd one, i did not mention what is being loaded WS-DTL-SC, WS-DTL-RC, WS-DTL-VALUE, it goes like this

i am using delimited verb to extract the few sections of the sub-record and moving it accordingly.

UNSTRING SUB-RECORD-1 DELIMITED BY "(" OR ")" OR ":" OR "-"
INTO WS-TEMP1, WS-TEMP2,WS-TEMP3,WS-TEMP4

MOVE WS-TEMP1 INTO WS-DTL-TYPE(WS-DTL-IDX, WS-DESC-IDX, WS-DEF-IDX)
MOVE WS-TEMP2 INTO WS-DTL-SC(WS-DTL-IDX, WS-DESC-IDX, WS-DEF-IDX)
MOVE WS-TEMP3 INTO WS-DTL-EC(WS-DTL-IDX, WS-DESC-IDX, WS-DEF-IDX)
MOVE WS-TEMP4 INTO WS-DTL-VALUE(WS-DTL-IDX, WS-DESC-IDX, WS-DEF-IDX)

it looks like while loading the values into the table, i am messing it up.
could you please provide suggestions or better approach to handle(load/search)
3 dimensional table
Back to top
View user's profile Send private message
dick scherrer

Moderator Emeritus


Joined: 23 Nov 2006
Posts: 19244
Location: Inside the Matrix

PostPosted: Sat Jan 30, 2010 11:29 am
Reply with quote

Hello,

While this info is not like the original, it does not appear to handle the first 2 dimensions values. . .

Suggest you post some realistic sample data and mention what values should be placed in the temp variables and the arrays for each input record.

We can go from there. . .

Until there is a clear understanding of what "should" happen, it will be difficult to suggest how to change/improve the process - at least for me icon_confused.gif
Back to top
View user's profile Send private message
ankit9jain

New User


Joined: 20 Jan 2009
Posts: 17
Location: India

PostPosted: Tue Feb 02, 2010 12:21 pm
Reply with quote

Hi Dick,

My table definition is

Code is in later reply.


Now i need to match my Input files field by field and if any mismatch is found, i need to search the table on the starting
column of the mismatched field and do further processing accordingly. i am trying to achieve that by writing below code.

PERFORM VARYING WS-DEF-IDX FROM 1 BY 1
UNTIL (WS-DEF-IDX EQUAL (WS-DEF-CNT + 1))
PERFORM VARYING WS-DESC-IDX FROM 1 BY 1
UNTIL (WS-DESC-IDX EQUAL (WS-DESC-CNT + 1))
SET WS-DTL-IDX TO 1
SEARCH WS-DTL-TABLE
WHEN WS-DTL-SC(WS-DEF-IDX,WS-DESC-IDX,WS-DTL-IDX)
EQUAL TO WS-TEMP9
.....

END-SEARCH
END-PERFORM
END-PERFORM.


but as i mentioned before, it gives me "INDEX TOO HIGH" as soon as after 2 iteration.
Back to top
View user's profile Send private message
dick scherrer

Moderator Emeritus


Joined: 23 Nov 2006
Posts: 19244
Location: Inside the Matrix

PostPosted: Wed Feb 03, 2010 4:03 am
Reply with quote

Hello,

What values are in these fields after the tables are loaded but before the searching begins? I suspect def-cnt is zero or 1. . .
05 WS-DEF-CNT PIC 9(01) COMP SYNC VALUE ZERO.
05 WS-DESC-CNT PIC 9(02) COMP SYNC VALUE ZERO.
05 WS-DTL-CNT PIC 9(02) COMP SYNC VALUE ZERO.

Please re-post the code using proper indentation and the "Code" tag. If you copy/paste already indented code into a reply, highlight it, and click Code, you will have what is needed. Use the Preview to see your post as it will appear to the forum rather than what you see in the Reply Editor. Whe the post appears as you want it, Submit.
Back to top
View user's profile Send private message
ankit9jain

New User


Joined: 20 Jan 2009
Posts: 17
Location: India

PostPosted: Wed Feb 03, 2010 11:20 am
Reply with quote

Hi Dick,

My table definition is

Code:
01 WS-RULEDEF-TABLE.
          05 WS-DEF-CNT                 PIC 9(01) COMP SYNC VALUE ZERO.
          05 WS-DESC-CNT                PIC 9(02) COMP SYNC VALUE ZERO.
          05 WS-DTL-CNT                 PIC 9(02) COMP SYNC VALUE ZERO.
          05 WS-DEF-TABLE               OCCURS 1 TO 9 TIMES
                                        DEPENDING ON WS-DEF-CNT
                                        INDEXED   BY WS-DEF-IDX.

             10 WS-DEF-NAME             PIC X(15).
             10 WS-DEF-KEY              PIC X(10).
             10 WS-DEF-K-VAL            PIC X(20).

             10 WS-RULEDESC-TABLE.
                15 WS-DESC-TABLE        OCCURS 1 TO 99 TIMES
                                        DEPENDING ON WS-DESC-CNT
                                        INDEXED   BY WS-DESC-IDX.
                20 WS-DESC-NAME         PIC X(08).
                20 WS-DESC-DTL          PIC X(30).

                20 WS-RULEDTL-TABLE.
                   25 WS-DTL-TABLE      OCCURS 1 TO 99 TIMES
                                        DEPENDING ON WS-DTL-CNT
                                        INDEXED   BY WS-DTL-IDX.
   
                   30 WS-DTL-TYPE       PIC X(03).
                   30 WS-DTL-SC         PIC X(03).
                   30 WS-DTL-EC         PIC X(03).
                   30 WS-DTL-VALUE      PIC X(10).


My Input file is below.

Code:
MATCHRULE01-CPCSSEQ(X0000000000)
RULE01(RCDTYP,SRCTYP)
OLD-RCDTYP(03)
NEW-RCDTYP(02)
DNM-SRCTYP
RULE02(ITMTYP)
OLD-ITMTYP(01)
NEW-ITMTYP(02)
MATCHRULE02-CPCSSEQ(X0000000000)
.....
....


and below is my code to load into the table

Code:
MOVE IN-RULE-RECORD           TO WS-TEMP
            MOVE WS-TEMP(1:4)             TO WS-TEMP-VAR
            EVALUATE WS-TEMP-VAR

            WHEN "MATC"
              ADD +1                   TO WS-DEF-CNT
              SET WS-DEF-IDX           TO WS-DEF-CNT
              UNSTRING WS-TEMP DELIMITED BY "-" OR "(" OR ")"
                INTO WS-TEMP1,WS-TEMP2,WS-TEMP3
         MOVE WS-TEMP1            TO WS-DEF-NAME(WS-DEF-IDX)    -> it should have value MATCHRULE01         
              MOVE WS-TEMP2            TO WS-DEF-KEY(WS-DEF-IDX)     -> CPCSSEQ
              MOVE WS-TEMP3            TO WS-DEF-K-VAL(WS-DEF-IDX)   -> X0000000000
              MOVE ZEROES              TO WS-DESC-CNT     

            WHEN "RULE"
       ADD +1                     TO WS-DESC-CNT   
            SET WS-DESC-IDX            TO WS-DESC-CNT
             UNSTRING WS-TEMP DELIMITED BY "(" OR ")"
                     INTO WS-TEMP1,WS-TEMP2
             MOVE WS-TEMP1            TO WS-DESC-NAME(WS-DEF-IDX,
                  WS-DESC-IDX)                                       -> RULE01
             MOVE WS-TEMP2            TO WS-DESC-DTL(WS-DEF-IDX,
                  WS-DESC-IDX)                                       -> RCDTYP,SRCTYP

            WHEN OTHER
              ADD +1                   TO WS-DTL-CNT
              SET WS-DTL-IDX           TO WS-DTL-CNT
              UNSTRING WS-TEMP DELIMITED BY "-" OR "(" OR ")"
                   INTO WS-TEMP1,WS-TEMP2,WS-TEMP3                   -> WS-TEMP1 = OLD, WS-TEMP2 = RCDTYP, WS-TEMP3 = 03

              PERFORM 1203-SEARCH-FILE-TABLE       THRU 1203-EXIT    -> it will search another table to get the starting
                           and ending column of "RCDTYP" field           

              IF FIELD-DEF
                 MOVE WS-TEMP1         TO WS-DTL-TYPE(WS-DEF-IDX,
                    WS-DESC-IDX,WS-DTL-IDX)                          -> WS-TEMP1 = OLD
                 MOVE WS-TEMP4         TO WS-DTL-SC(WS-DEF-IDX,
                    WS-DESC-IDX,WS-DTL-IDX)                          -> WS-TEMP4 = 005 (Starting column of RCDTYP) (These values are coming correct from the other table)
                 MOVE WS-TEMP5         TO WS-DTL-EC(WS-DEF-IDX,
                    WS-DESC-IDX,WS-DTL-IDX)                          -> WS-TEMP5 = 009 (Ending column of RCDTYP)(These values are coming correct from the other table)
                 MOVE WS-TEMP3         TO WS-DTL-VALUE(WS-DEF-IDX,
                    WS-DESC-IDX,WS-DTL-IDX)                          -> WS-TEMP3 = 03

              ELSE
                 PERFORM 9999-ABEND-PROGRAM
                 DISPLAY "RULE NOT FOUND"
              END-IF

            END-EVALUATE.

            PERFORM 1200-READ-RULE-INPUT             THRU 1200-EXIT.

       1201-EXIT.
            EXIT.


       1203-SEARCH-FILE-TABLE.
      *----------------------
           MOVE 'N'                           TO WS-FIELD-DEF
           SET WS-FILE-IDX TO 1
           SEARCH WS-FILE-TABLE VARYING WS-FILE-IDX
               AT END DISPLAY "RULE NOT FOUND"
             WHEN WS-TEMP2 = WS-FILE-VAR(WS-FILE-IDX)
               MOVE WS-FILE-SC(WS-FILE-IDX) TO WS-TEMP4
               MOVE WS-FILE-EC(WS-FILE-IDX) TO WS-TEMP5
               MOVE 'Y'                       TO WS-FIELD-DEF
           END-SEARCH.

       1203-EXIT.
           EXIT.



Now i need to match my Input files field by field and if any mismatch is found, i need to search the table on the starting
column of the mismatched field and do further processing accordingly. i am trying to achieve that by writing below code.

Code:
PERFORM VARYING WS-DEF-IDX FROM 1 BY 1
            UNTIL (WS-DEF-IDX EQUAL (WS-DEF-CNT + 1))
              PERFORM VARYING WS-DESC-IDX FROM 1 BY 1
              UNTIL (WS-DESC-IDX EQUAL (WS-DESC-CNT + 1))
                SET WS-DTL-IDX                 TO 1
                SEARCH WS-DTL-TABLE
                 WHEN WS-DTL-SC(WS-DEF-IDX,WS-DESC-IDX,WS-DTL-IDX)
                 EQUAL TO WS-TEMP9
                 .....

                END-SEARCH
              END-PERFORM
            END-PERFORM.



What values are in these fields after the tables are loaded but before the searching begins?
I suspect def-cnt is zero or 1.


As i am using ODO for the below mentioned fields, and it changes with each iteration,
i suspect that these 3 fields will have the values of the last iteration, and not zero or 1
and if i am correct, this is causing the problem.
because of that while searching the table, i am compairing index value to the those last iteration values
Back to top
View user's profile Send private message
dick scherrer

Moderator Emeritus


Joined: 23 Nov 2006
Posts: 19244
Location: Inside the Matrix

PostPosted: Wed Feb 03, 2010 8:11 pm
Reply with quote

Hello,

It does not matter what happens from iteration to iteration. It matters (for now at least) what is in the count fields when you try to reference the loaded arrays.

I'm also not sure why you chose ODO. . . All of the space is allocated anyway. . . Possibly a solution in search of a requirement? And the way you are processing does not lend itself to ODO.

Suggest you give it a try without ODO and see what happens.
Back to top
View user's profile Send private message
ankit9jain

New User


Joined: 20 Jan 2009
Posts: 17
Location: India

PostPosted: Thu Feb 04, 2010 11:07 am
Reply with quote

Hi Dick,

Thanks for the suggestion. As per your suggestion, i tried without ODO
and code is working fine now.
Thanks again!!
Back to top
View user's profile Send private message
dick scherrer

Moderator Emeritus


Joined: 23 Nov 2006
Posts: 19244
Location: Inside the Matrix

PostPosted: Thu Feb 04, 2010 11:38 am
Reply with quote

You're welcome - good to hear it is working.

Thank you for letting us know icon_smile.gif

d
Back to top
View user's profile Send private message
View previous topic :: :: View next topic  
Post new topic   Reply to topic View Bookmarks
All times are GMT + 6 Hours
Forum Index -> COBOL Programming

 


Similar Topics
Topic Forum Replies
No new posts Compare 2 files and retrive records f... DFSORT/ICETOOL 3
No new posts FTP VB File from Mainframe retaining ... JCL & VSAM 8
No new posts Extract the file name from another fi... DFSORT/ICETOOL 6
No new posts How to split large record length file... DFSORT/ICETOOL 10
No new posts Extracting Variable decimal numbers f... DFSORT/ICETOOL 17
Search our Forums:

Back to Top