MVSFORUMS.com Forum Index MVSFORUMS.com
A Community of and for MVS Professionals
 
 FAQFAQ   SearchSearch   Quick Manuals   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

ODO problem (leading to XML generate problem)

 
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Application Programming
View previous topic :: View next topic  
Author Message
misi01
Advanced


Joined: 02 Dec 2002
Posts: 629
Topics: 176
Location: Stockholm, Sweden

PostPosted: Wed Aug 12, 2015 12:31 am    Post subject: ODO problem (leading to XML generate problem) Reply with quote

First of all, a simple, stripped-down program that illustrates the problem.
Code:

       IDENTIFICATION DIVISION.
       PROGRAM-ID.     MODULDRV.
      ******************************************************************
      *
      *    MODUL       MODULTST
      *
      *    KODAD       JANUARI 2010
      *
      *****************************************************************
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       OBJECT-COMPUTER.            IBM-370.
      *
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01  FILLER                  PIC X(32)       VALUE
                                   'XXX MODUL MODULTST START WSS XXX'.
      *
      *****************************************************************
      *    INDEXAREOR (IX)
      *****************************************************************
       01  filler                   pic x(16) value 'INDEXAREORXXXXXX'.
      *
       01  indexareor.
           05  ix-1                    pic 9(4).
           05  ix-2                    pic s9(8) comp.
           05  ix-noteringar           pic s9(4) comp-3.
           05  ix-placeringsprofil     pic s9(4) comp-3.
      *
      ******************************************************************
      *    ARBETSAREOR  (AA)
      ******************************************************************
       01 FILLER                   PIC X(16)  VALUE 'ARBETSAREORXXXXX'.
      *
       01  arbetsareor.
           05  aa-xml-output           pic x(60000).
           05  aa-xml-char-counter     pic s9(8) comp-3.
      *
       01  DOCUMENT.
      *
           05  PLACERINGSPROFIL
               occurs 0 to 50 times depending on ix-placeringsprofil
                                       pic x(100).
      *
           05  NOTERINGAR.
               10  NOTERINGAR_RUBRIK1  pic x(100).
               10  NOTERINGAR_RAD
                   occurs 0 to 2 times depending on ix-noteringar
                                       pic x(100).
      *
      *****************************************************************
      * PROCEDURE DIVISION
      *****************************************************************
       PROCEDURE DIVISION.
      *****************************************************************
      * Huvudrutin
      *****************************************************************
       a-huvudrutin section.
      *
           perform b-init

           perform varying ix-1 from 1 by 1 until ix-1 > 4

             add 1                       to ix-placeringsprofil
             move ix-placeringsprofil    to ix-2
             move ' '                    to placeringsprofil(ix-2)
             string
               'Line '
               ix-1
                                         delimited by size
               into placeringsprofil(ix-2)
             end-string
           end-perform
      *
           move ' '                    to NOTERINGAR_RUBRIK1
           perform q-generate-xml
      *
           perform z-avslut
      *
           goback.

           exit.
      ******************************************************************
      *    B   INITIERING
      ******************************************************************
       b-init section.
      *
           initialize                     indexareor
                                          arbetsareor
      *
           move ' '                    to NOTERINGAR_RUBRIK1

           exit.
      *****************************************************************
      *
      *****************************************************************
       q-generate-xml section.
      *
           move ' '                    to aa-xml-output

           xml

            generate aa-xml-output from document
              count in aa-xml-char-counter

            on exception
              display 'XML generate on exception 'xml-code

            not on exception
              display 'No exception'
      *
           end-xml
      *
           exit.
      ******************************************************************
      *
      *    Z   AVSLUTNING
      *
      ******************************************************************
       Z-AVSLUT SECTION.
           MOVE ZERO                     TO RETURN-CODE
           CONTINUE.


Note the fact that I init NOTERINGAR_RUBRIK1 to blanks in the b-init section. If you debug this program (we use Xpediter) and keep the NOTERINGAR_RUBRIK1 variable, you'll see that it gets set to blank (no surprise).
However as soon as you run the line "add 1 to ix-placeringsprofil"
it gets set to low values.

For this reason I have ANOTHER move ' ' to the variable AFTER the perform loop.

Here comes the rub. If I comment out the move ' ' after the perform, I get an exception on the XML generate (rc 417) since NOTERINGAR_RUBRIK1 now contains low values.
If I leave the move ' ' in, no exception.

My real problem is the following. As far as I can see it, I need to do one of the following options:-

1 Position my sub-variables in DOCUMENT such that they are placed "in the right order" (ie, place NOTERINGAR_RUBRIK1 above PLACERINGSPROFIL and then create the various values in the same order (ie, NOTERINGAR_RUBRIK1 first, then PLACERINGSPROFIL etc etc). Trouble is, I have quite a few of these groups under DOCUMENT and I can just see how the order would get out of wack somewhere down the line.
2 Define each group under DOCUMENT as its own 01 level variable and then generate each one of them and catenate them together

Here at the bank, we develop/program test using Micro Focus's Mainframe Express. They have an option called NOODOSLIDE which, basically, ensures that all tables "appear" to be defined in advance with the maximum number of entries possible. This results in the problem above being a non-starter. Trouble is, you then lift your programs to the "real" environment and your problems start.

Maybe there's simply a compiler option I could use that I'm not aware of, or maybe there's a PTF that hasn't been applied.

Any suggestions/comments greatly appreciated.
_________________
Michael
Back to top
View user's profile Send private message Send e-mail
William Collins
Supermod


Joined: 03 Jun 2012
Posts: 437
Topics: 0

PostPosted: Wed Aug 12, 2015 1:50 am    Post subject: Reply with quote

You have what is called a Complex ODO (you have data-definitions following an ODO under the same 01-level, meaning those data-items are variably-located).

NOTERINGAR_RUBRIK1 exists only once, it has a fixed length, but it has 51 potential locations depending on ix-placeringsprofil. When you did you MOVE, you only set the first of those (or whatever ix-placeringsprofil happened to contain - actually, looking at ix-placeringsprofil, it has no defined value by the time you do the MOVE of space, it is packed-decimal, so you are either using NUMPROC(NOPFD) as a compile option, or you got (and continue to get) extremely lucky)).

The fix I suggest is to use fixed-length OCCURS for all your preparation of the data. Once that is complete, immediately before the generation of the XML (I'm guessing that is why you want the ODO, to not have "empty" entries) then, and only then, set up the data in the variable-length occurs.

It will greatly simplify things, take a lot of technical clutter away, leaving just the business processing and your program easier to understand.

The alternative, which is absolute standard, is to MOVE all (as in all) the items which follow an ODO-group to a location to save them. Change the ODO value. Then MOVE them back to their original names. The position of the data will have changed. To preserve the content, you have to go through that.

Micro Focus's ODOSLIDE does that processing for you (as I understand it). There is no IBM COBOL that has an equivalent option or functioning.

I'm curious as to why you have a mixture of usages for you loop-control/subscripting, but that's something else.
Back to top
View user's profile Send private message
misi01
Advanced


Joined: 02 Dec 2002
Posts: 629
Topics: 176
Location: Stockholm, Sweden

PostPosted: Wed Aug 12, 2015 2:26 am    Post subject: Thanks William Reply with quote

In answer to your questions/comments.

NUMPROC(NOPFD) - correct, this is the default compiler option here

Quote:
The fix I suggest is to use fixed-length OCCURS for all your preparation of the data

Not sure if I get you here. Do you mean that I should have occurs 50 rather than occurs 0 to 50 depending on ? If so, I'll end up with a load of empty entries won't I (I found a code example that was neat and that did an XML PARSE after the GENERATE and removed all the empty entries, so that might be an option).

Again, if I understand you correctly, the idea of defining the NON-occcurring fields first and then the occurring ones would be a non-starter. The program is complicated enough (and changes a lot) so that you could never be SURE that some restructuring of it wouldn't ruin things.

Quote:
usages for you loop-control/subscripting


Basically, to my (naive ?) way of thinking, the code should be working. I get that nested occurs depending on could cause all sorts of problems, but not of the entries I have in the actual structure are what I would call nested.

Based on what you say, I see 2 options:

1 Define each occurring group as a 01-level group and generate each one and catenate them
2 Define them as occurs x (rather than occurs 0 to x) and then removing the empty entries.

Any other options you can think of?
_________________
Michael
Back to top
View user's profile Send private message Send e-mail
William Collins
Supermod


Joined: 03 Jun 2012
Posts: 437
Topics: 0

PostPosted: Wed Aug 12, 2015 3:36 am    Post subject: Reply with quote

What I'm suggesting is that you use fixed-size OCCURS while you are "loading" and doing whatever else you need with the data.

Then. After all that is complete. Set up the table lengths and copy the data from the fixed-length table to the variable-length table, so you can generate the XML without having to remove unused items.

That way you have the data-manipulation made without the additional complexity of the ODO, and the XML generated without the need to remove "empty" items.

Your program will be smaller, simpler, and easier to understand (the ODOs only existing to ease the production of the XML).
Back to top
View user's profile Send private message
misi01
Advanced


Joined: 02 Dec 2002
Posts: 629
Topics: 176
Location: Stockholm, Sweden

PostPosted: Wed Aug 12, 2015 3:41 am    Post subject: Reply with quote

Aha ..... (eureka moment). That would make it a LOT simpler I think. I'll certainly give it a go and get back to you. Thanks a lot
_________________
Michael
Back to top
View user's profile Send private message Send e-mail
misi01
Advanced


Joined: 02 Dec 2002
Posts: 629
Topics: 176
Location: Stockholm, Sweden

PostPosted: Wed Aug 12, 2015 8:27 am    Post subject: WORKED BEAUTIFULLY William !!!! Reply with quote

I'll include the logic here so it might be of use to others.

First all, the actual XML document (I'll only include the first few entries since the rest is the same)

Code:

       01  DOCUMENT.
           05  RUBHUVUD01.
               15  DOC_DATUM           pic x(10).
               15  DOC_BLANKETT        pic x(30).
      *
           05  ADRESSAT01.
               15  NAMN                pic x(70).
               15  ADRESSAT02
                    occurs 0 to 1 times depending on ix-adress02.
                    20  CO_ADRESS       pic x(35).
                    20  ADRESS          pic x(35).
                    20  ADRESSRAD3      pic x(40).
                    20  filler redefines ADRESSRAD3.
                         25  POSTNR      pic x(5).
                         25  ORT         pic x(35).
      *
           05  KUND_PERSNR
                occurs 0 to 1 times depending on ix-kund-pnr
                                       pic x(11).
      *
           05  KUND_INFOTEXTER.
               10  KUND_INFO
                   occurs 0 to 5 times depending on ix-kund-info.
                       25  KUND_COL1   pic x(45).
                       25  KUND_COL2   pic x(35).
      *
           05    PLACERINGSPROFIL
                  occurs 0 to 50 times depending on ix-placeringsprofil
                                       pic x(100).


Now the fixed length copy of it

Code:

       01  tb_DOCUMENT.
            05  tb_RUBHUVUD01.
                 10  tb_DOC_DATUM           pic x(10).
                 10  tb_DOC_BLANKETT        pic x(30).
      *
           05  tb_ADRESSAT01.
                10  tb_NAMN                pic x(70).
                10  tb_ADRESSAT02 occurs 1 .
                     15  tb_CO_ADRESS       pic x(35).
                     15  tb_ADRESS          pic x(35).
                     15  tb_ADRESSRAD3      pic x(40).
                     15  tb_postnr_ort redefines tb_ADRESSRAD3.
                          20  tb_POSTNR      pic x(5).
                          20  tb_ORT         pic x(35).
      *
           05  tb_KUND_PERSNR  occurs 1  pic x(11).
      *
           05  tb_KUND_INFOTEXTER.
                 10  tb_KUND_INFO occurs 5.
                       15  tb_KUND_COL1   pic x(45).
                       15  tb_KUND_COL2   pic x(35).
      *
           05  tb_PLACERINGSPROFIL occurs 50 pic x(100).


Normally, our standard is NOT to use underscore characters in cobol names, but for some reason or other, the guys who develop the XML schemas use them for tag names. For that reason, I thought it was easier to use exactly the same names but simply preceded by a tb_

When filling the TB_ table elements, I use the/increase the same variable as defined for the XML document, ie. This means that if I add rows to tb_placeringsprofil, I increase the value in ix-placerinsgprofil for each new entry.

Now to the copying of the data from the fixed length table to the XML document. (note that I copy the items/tables in the same order they're defined in the actual XML document)

Code:

      ****
           move tb_doc_datum           to doc_datum
           move tb_doc_blankett        to doc_blankett
      ****
           move tb_namn                to namn
           perform varying ix-1 from 1 by 1                  until
               ix-1 > ix-adress02

             move tb_co_adress(ix-1)   to co_adress(ix-1)
             move tb_adress(ix-1)      to adress(ix-1)
             move tb_adressrad3(ix-1)  to adressrad3(ix-1)

           end-perform
      ****
           perform varying ix-1 from 1 by 1                  until
               ix-1 > ix-kund-pnr

             move tb_kund_persnr(ix-1) to kund_persnr(ix-1)

           end-perform
      ****
           perform varying ix-1 from 1 by 1                  until
               ix-1 > ix-kund-info

             move tb_kund_col1(ix-1)   to kund_col1(ix-1)
             move tb_kund_col2(ix-1)   to kund_col2(ix-1)

           end-perform
      ****
           perform varying ix-1 from 1 by 1                  until
               ix-1 > ix-placeringsprofil

             move tb_placeringsprofil(ix-1)
                                       to placeringsprofil(ix-1)

           end-perform


et voilĂ . I can now generate the XML document without a load of problems.

Thanks again for the help and the (brilliant) suggestion.

(now to keep it to myself so as to be indispensable at work Laughing . Just kidding)
_________________
Michael
Back to top
View user's profile Send private message Send e-mail
William Collins
Supermod


Joined: 03 Jun 2012
Posts: 437
Topics: 0

PostPosted: Wed Aug 12, 2015 10:21 am    Post subject: Reply with quote

Thanks for posting the code.

Updating the ODO values as you go along will work, as will copying the final values once you know them. I prefer the latter, firstly because it used to be a more efficient way to do it (IBM compilers recalculated lengths with the ODO values changed, they now only do it when making a reference requires the current length of the table) and secondly because an unwary maintainer doesn't have to keep two things in step.

I'd also do the final MOVEs to the table in the order you chose, because it seems clearer. However, as long as all the ODO values are set before starting the MOVEs, the order does not matter in this type of case. As soon as you have code which changes a prior ODO value, whilst you already have data in the table, that is where you get the problem.

There is an Appendix in the Programming Guide which deals with Complex ODOs. I guess the use of ODO will be expanding, exactly as the use of XML generation expands. Many people trip up with ODOs, so good to have your example.

Note, the Complex ODO is an IBM Extension. from the Appendix on Extensions in the Language Reference:

Quote:
Complex OCCURS DEPENDING ON. [Standard COBOL 85 requires that an entry containing OCCURS DEPENDING ON be followed only by subordinate entries, and that no entry containing OCCURS DEPENDING ON be subordinate to an entry containing OCCURS DEPENDING ON.]


Just a follow-up on the uninitialised ix-placeringsprofil in your original example. I could tell you had NUMPROC(NOPFD) because with NUMPROG(PFD) (or the rarer NUMPROC(MIG)) you'd have got a S0C7 running that code.

I suspect the field not being initialised was down to you making the short program, rather than in the original, but with NUMPROC(NOPFD), the sign-fixing can make bad things (probable binary zeros in the field (likely), possibly whatever was lying around) good. Your field had it's sign (temporarily) "fixed", to be a proper packed-decimal zero, which was then used to calculate the length of the table (where affected) and the start-position of the items following it.

It's something to be aware of when using NUMPROC(NOPFD).
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12378
Topics: 75
Location: San Jose

PostPosted: Wed Aug 12, 2015 11:03 am    Post subject: Reply with quote

misi01,

You may want to read this which describes with examples about modifying and referring variable ODO objects.

Complex OCCURS DEPENDING ON
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
misi01
Advanced


Joined: 02 Dec 2002
Posts: 629
Topics: 176
Location: Stockholm, Sweden

PostPosted: Thu Aug 13, 2015 4:54 am    Post subject: Reply with quote

Thanks Kolusu. Good link, pity I never found it in my searches
_________________
Michael
Back to top
View user's profile Send private message Send e-mail
William Collins
Supermod


Joined: 03 Jun 2012
Posts: 437
Topics: 0

PostPosted: Thu Aug 13, 2015 8:03 am    Post subject: Reply with quote

Noticed now, with COBOL V5, the Complex ODO is no longer in an Appendix, but in the body of the Programming Guide.

The problem in Kolusu's link, that of an index on a variable-length item, occurs only when an ODO is subordinate to another table (OCCURS or OCCURS DEPENDING ON). Yes, the length of the subordinate table changes, but it is the concomitant change in length of the item with the INDEXED BY which is the problem. True, you can't have one without the other, but the documentation is a little unclear.

The save, change ODO value, restore for the index is analagous to the save, change ODO value, restore to preserve data which follows an ODO within the same 01-level. However, that does not mean the index-preserving has to be done for all indexes on an ODO.

In Michael's final sample code, the index-preserving technique would not be required (and use would therefore confuse), as all the OCCURS items themselves are fixed-length.
Back to top
View user's profile Send private message
misi01
Advanced


Joined: 02 Dec 2002
Posts: 629
Topics: 176
Location: Stockholm, Sweden

PostPosted: Sun Aug 16, 2015 1:29 am    Post subject: Reply with quote

William, just so there's no confusion, your last sentence "the index_preserving technique....." is only relevant with Cobol 5 ????? (Or am I missing something that would make code even easier in cobol 4)
_________________
Michael
Back to top
View user's profile Send private message Send e-mail
William Collins
Supermod


Joined: 03 Jun 2012
Posts: 437
Topics: 0

PostPosted: Sun Aug 16, 2015 4:08 am    Post subject: Reply with quote

Sorry, no, the index-preserving technique is only relevant when a table is variably located (and only impacts when the start-position of the tale changes. This is the same in all versions of Enterprise COBOL. I'll try to clarify here, and look at editing the original.

The point about V5 was that the text had been "promoted" from an Appendix to the main body of the manual, perhaps supporting the idea of an expectation of Complex ODO usage becoming more common.

That is, if there is an ODO within a table (whether or not the table it is within is also an ODO).

Code:

01  some-numeric-item             BINARY PIC 9(4) VALUE ZERO.
01  the-first-table.
    05   table-entry occurs 10 times
        indexed by entry-minus-1-X-length.
        10  a-bit-of-stuff               PIC X.
        10  a-variable-length-table.
            15  filler occurs 0 to 10 times
                 depending on some-numeric-item.
                20  filler               PIC X.


If entry-minus-1-X-length is SET to 1, the value contained in the index is zero. It has been calculated as entry (1) minus 1 (so zero) time length (1, the a-bit-of-stuff, a-variable-length-table has a length of zero, because some-numeric-item is zero).

If one is MOVEd to some-numeric-item, the length of table-entry becomes two.

That doesn't matter for the first entry in the table, because for the first entry, irrespective of the length of the item, an index always contains zero.

SET entry-minus-1-X-length to two. Two minus one is one, length of the table entry is two (the fixed part, of one, and the variable part of one (current value in some-numeric-item is one).

Now, if you want to add another entry to a-variable-length-table (add one to some-numeric-item), then the length of the table entry-name with the INDEXED BY is now three bytes, but the index is unchanged, so is not related to the correct data.

That is the problem. When the length of the subordinate table changes, the length of the entry-name with the INDEXED BY changes. But nothing automatically changes with the INDEXED BY item.

So you have not do it manually: save entry-number represented by the index-name (SET to aninteger); change the length of the subordinate table; SET the index-name to the the integer.

Don't be tempted to use USAGE INDEX, which would be normal when preserving an index value, because that holds the displacement (entry minus one multiplied by entry-length). The displacement is what has been invalidated by the change in length of the entry, due to the change in length of the subordinate table.

Thus, the issue affects any OCCURS which contains a subordinate (not a following) OCCURS DEPENDING ON. It is only in this subb-set of Complex ODO that the technique is required. In any other usage of ODO (Complex or not) it is not required, and will confuse (and consume CPU).

So, the issue did not affect your original coding (you had following ODOs, not subordinate).
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Application Programming All times are GMT - 5 Hours
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


MVSFORUMS
Powered by phpBB © 2001, 2005 phpBB Group