user255205
user255205

Reputation: 177

XML in COBOL with nested tables and varying children

Is it possible to use XML GENERATE to create XML with multi-level nested elements of different sizes?

For example:

01  SOURCE-REC.
    05  REPEATING-PARENT OCCURS 5 TIMES.
        10  PARENT-NAME PIC X(7).
        10  CHILD-COUNT PIC 9.
        10  REPEATING-CHILD OCCURS 1 TO 5 TIMES
                DEPENDING ON CHILD-COUNT.
            15  CHILD-NAME PIC X(6).

Compiling this using Enterprise Cobol v4.1 yields:

IGYGR1263-S "OCCURS DEPENDING ON" object "CHILD-COUNT" was defined as a table element. The "DEPENDING ON" phrase was discarded.

IGYGR1116-S The "DEPENDING ON" object for table "REPEATING-CHILD" was invalid. The "DEPENDING ON" phrase was discarded.

Not all parents are going to have the same number of children. How can this be addressed?

Edit: I suppose at its heart, this isn't really an XML question. I hit a wall just trying to build the working storage that I later hope to feed into XML GENERATE.

Upvotes: 4

Views: 5756

Answers (3)

NealB
NealB

Reputation: 16928

Summary of first answer: You cannot define a complex ODO in COBOL where the ODO object is contained within a table. Consequently it is not possible for XML GENERATE to produce a varying number of "childern" for each occurance of a "parent". You have to live with fixed table dimensions and empty nodes.

Round two: Have you considered re-parsing/re-constructing the generated XML string to eliminate the empty nodes? This may sound a little odd but it may not be all that difficult. Have a look at the following program and the output it produces...

   IDENTIFICATION DIVISION.                    
     PROGRAM-ID. EXAMPLE1.                     
   DATA DIVISION.                              
   WORKING-STORAGE SECTION.                    
   77  I                    PIC S9(4) BINARY.  
   77  XL                   PIC S9(4) BINARY.  
   77  XML-TAG              PIC X(34).         
   01  XML-DATA.                               
       05 XML-MSG-A         PIC X(8000).       
       05 XML-CHARS-A       PIC S9(4) BINARY.  
       05 XML-MSG-B         PIC X(8000).       
       05 XML-CHARS-B       PIC S9(4) BINARY.  
   01  SOURCE-REC.                             
       05  REPEATING-PARENT OCCURS 5 TIMES.    
           10  PARENT-NAME PIC X(7).           
           10  CHILD-COUNT PIC 9.              
           10  REPEATING-CHILD OCCURS 5 TIMES. 
               15  CHILD-NAME PIC X(6).        
   01  XML-STACK.                                 
       05 SP                PIC S9(4) BINARY.     
       05 STACK-REC         OCCURS 500 TIMES.     
          15 NODE-NAME      PIC X(31).            
          15 NODE-POS       PIC S9(4) BINARY.     
          15 NODE-IS-EMPTY  PIC X.                
             88 NODE-IS-EMPTY-YES VALUE 'Y'.       
             88 NODE-IS-EMPTY-NO  VALUE 'N'.       
          15 EMPTY-WHEN-IND      PIC X.                
             88 EMPTY-ZERO-OR-SPACE  VALUE 'Z'.   
             88 EMPTY-NEVER          VALUE 'N'.   
   PROCEDURE DIVISION.                            
       INITIALIZE SOURCE-REC.                     
       MOVE 'p-1'       TO PARENT-NAME (1)        
       MOVE 2           TO CHILD-COUNT (1)        
       MOVE 'c-1-1'     TO CHILD-NAME  (1 1)      
       MOVE 'c-1-2'     TO CHILD-NAME  (1 2)      
       MOVE 'p-2'       TO PARENT-NAME (2)        
       MOVE 0           TO CHILD-COUNT (2)        
       MOVE 'p-3'       TO PARENT-NAME (3)                        
       MOVE 1           TO CHILD-COUNT (3)                        
       MOVE 'c-3-1' TO CHILD-NAME  (3 1)                          

       XML GENERATE XML-MSG-A FROM SOURCE-REC COUNT IN XML-CHARS-A
       MOVE ZERO TO XML-CHARS-B                                   
       MOVE SPACES TO XML-MSG-B                                   
       XML PARSE XML-MSG-A(1:XML-CHARS-A)                         
           PROCESSING PROCEDURE CLEAN-UP                          
       PERFORM VARYING I FROM 1 BY 80 UNTIL I > XML-CHARS-B       
         DISPLAY XML-MSG-B (I:80)                                 
       END-PERFORM                                                
       GOBACK                                                     
       .                                                          
   CLEAN-UP SECTION.                                              
       COMPUTE XL = FUNCTION LENGTH (XML-TEXT)                    
       EVALUATE XML-EVENT                                         
       WHEN 'START-OF-ELEMENT'                                    
          ADD 1 TO SP                                             
          MOVE XML-TEXT(1:XL) TO NODE-NAME (SP)                      
          COMPUTE NODE-POS (SP) = XML-CHARS-B + 1              
          STRING '<' XML-TEXT(1:XL) '>' DELIMITED BY SIZE           
            INTO XML-TAG                                      
          MOVE XML-TAG TO XML-MSG-B (XML-CHARS-B + 1:XL + 2)  
          COMPUTE XML-CHARS-B = XML-CHARS-B + XL + 2          
          SET NODE-IS-EMPTY-YES (SP) TO TRUE                   
 *****    EVALUATE XML-TEXT(1:XL)                                   
 *****    WHEN 'CHILD-COUNT'                                  
 *****       SET EMPTY-NEVER (SP) TO TRUE                     
 *****    WHEN OTHER                                          
             SET EMPTY-ZERO-OR-SPACE (SP) TO TRUE             
 *****    END-EVALUATE                                        
       WHEN 'CONTENT-CHARACTERS'                              
          IF EMPTY-ZERO-OR-SPACE (SP) AND                     
             (XML-TEXT(1:XL) = ZERO OR XML-TEXT(1:XL) = SPACE)            
             CONTINUE                                         
          ELSE                                                
             SET NODE-IS-EMPTY-NO (SP) TO TRUE                 
             MOVE XML-TEXT(1:XL) TO XML-MSG-B (XML-CHARS-B + 1:XL)     
             COMPUTE XML-CHARS-B = XML-CHARS-B + XL              
          END-IF                                                 
       WHEN 'END-OF-ELEMENT'                                     
          IF NODE-IS-EMPTY-YES (SP)                               
             COMPUTE XML-CHARS-B = NODE-POS (SP) - 1              
             SUBTRACT 1 FROM SP                                  
          ELSE                                                   
             STRING '</' XML-TEXT(1:XL) '>' DELIMITED BY SIZE          
               INTO XML-TAG                                      
             MOVE XML-TAG TO XML-MSG-B (XML-CHARS-B + 1:XL + 3)  
             COMPUTE XML-CHARS-B = XML-CHARS-B + XL + 3          
             SUBTRACT 1 FROM SP                                  
             IF SP > ZERO                                        
               SET NODE-IS-EMPTY-NO (SP) TO TRUE                  
             ELSE                                                
               MOVE SPACES TO XML-MSG-B (XML-CHARS-B + 1:)       
             END-IF                                              
          END-IF                                                 
       END-EVALUATE         
       .                    

Gives you the following XML string (cut into 80 character chunks)

<SOURCE-REC><REPEATING-PARENT><PARENT-NAME>p-1</PARENT-NAME><CHILD-COUNT>2</CHIL
D-COUNT><REPEATING-CHILD><CHILD-NAME>c-1-1</CHILD-NAME></REPEATING-CHILD><REPEAT
ING-CHILD><CHILD-NAME>c-1-2</CHILD-NAME></REPEATING-CHILD></REPEATING-PARENT><RE
PEATING-PARENT><PARENT-NAME>p-2</PARENT-NAME></REPEATING-PARENT><REPEATING-PAREN
T><PARENT-NAME>p-3</PARENT-NAME><CHILD-COUNT>1</CHILD-COUNT><REPEATING-CHILD><CH
ILD-NAME>c-3-1</CHILD-NAME></REPEATING-CHILD></REPEATING-PARENT></SOURCE-REC>   

All of the empty nodes have been removed.

Note the commented lines of code in the above program. By re-activating these you can preserve the empty REPEATING-PARENT nodes. Depending on your needs, the determination of what constitutes an empty node may be somewhat more complex.

At any rate this might get you a little closer to where you want to be.

Cheers...

Upvotes: 3

Albert Visser
Albert Visser

Reputation: 1134

I think you should lose the DEPENDING ON altogether. It doesn't save memory, and you can just as easily address valid REPEATING-CHILD items by making sure their subscripts are in the range from 1 to the corresponding CHILD-COUNTER.

Upvotes: 0

NealB
NealB

Reputation: 16928

I think the problem is that the CHILD-COUNT must be defined outside of the record structure passed to XML GENERATE. Something like:


01  CHILD-COUNT PIC 9.
01  SOURCE-REC. 
    05  REPEATING-PARENT OCCURS 5 TIMES. 
        10  PARENT-NAME PIC X(7). 
        10  CHILD-COUNTER PIC 9. 
        10  REPEATING-CHILD OCCURS 1 TO 5 TIMES 
                DEPENDING ON CHILD-COUNT. 
            15  CHILD-NAME PIC X(6).

Then just before the XML GENERATE you would have to do something hokey such as:


MOVE CHILD-COUNT TO CHILD-COUNTER (PARENT-COUNT)

if you want to retain the number of occurs for REPEATING-CHILD

This is probably not what you wanted to see because it pretty much means you must to have the same number of dependant children for each REPEATING-PARENT occurance.

Upvotes: 1

Related Questions