IBM Support

XML GENERATE should create attributes mixed with contents under COBOL.

Troubleshooting


Problem

I want to create XML like this data2

Cause

XML GENERATE was designed to be a very simple and straightforward way of externalizing the content of a data structure in a "preferred" XML format.
We reckoned that customers who wanted the XML in some other format would have the full power of XML technology (XSLT and so on) to transform the XML GENERATE output as required.
However, it turns out that customers like the built-in XML GENERATE capability so much that they would like it to produce their various desired output formats directly. As a compromise, many transformations can be done by post-processing the XML GENERATE output in COBOL.

Diagnosing The Problem

Enterprise COBOL version 4.1 and 4.2 have a feature to create attributes, declarations, and namespaces. However, it is not possible to use XML GENERATE to produce output that has attributes and values together. With version 4.1 and beyond, it's possible to produce mixed attributes and elements by using a trick shown in example 1. Version 3.4 programs will have to use example 2 which post-processes the output file.
<item1 item2="hello">goodbye</item1>
You can use XML GENERATE WITH ATTRIBUTES to create
<item1 item2="hello" item3="goodbye"></item1>

Resolving The Problem

Using Enterprise COBOL for z/OS version 5, this is possible by using the TYPE clause. You can use something like
XML GENERATE ... TYPE OF THISX IS ELEMENT, THATX IS ATTRIBUTE, SOMEX IS CONTENT...
Specifics are in the Programming Guide chapter 29.


Example 1 for version 4.:
Expected output will be
<one THISX="1.000" SOMEX="100"><THATX>Data2</THATX></one>
If you want the following, you will have to use two XML GENERATE then piece them together -
<one THISX="1.000" SOMEX="100">Data2</one>

IDENTIFICATION DIVISION.
PROGRAM-ID.  AABBCC.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  TOTAL-CHAR   PIC 9(05) VALUE 0.
01  XML-OUTPUT   PIC X(1000) VALUE QUOTES.
01  one.
    02 THISX PICTURE 9V999 VALUE 1.00.
    02 THATX PICTURE X(5) occurs 1 times.
    02 SOMEX PICTURE 9(5) VALUE 00100.
PROCEDURE DIVISION.
    MOVE "Data2" TO THATX(1).
    DISPLAY " one = " QUOTE one QUOTE.
    XML GENERATE XML-OUTPUT
      FROM one
      COUNT IN TOTAL-CHAR
      WITH ATTRIBUTES
      ON EXCEPTION DISPLAY "Foulup XML-CODE =  " XML-CODE
     NOT EXCEPTION DISPLAY "No problem  XML-CODE =  " XML-CODE.
   PERFORM A.
   DISPLAY "STOP RUN.      ".
   STOP RUN.
A. DISPLAY "Here is the variable XML-OUTPUT".
   DISPLAY XML-OUTPUT(1:TOTAL-CHAR). DISPLAY SPACE.
 
Example 2 for version 3.4 and beyond:
(c2a) changes most (but not all) instances of element content to attribute values. It post-processes XML output:

Identification division.
  Program-id. 'XGFXA'.
Data division.
 Working-storage section.
   01 numItems pic 99 global.
   01 purchaseOrder global.
    03 po.
     05 orderDate pic x(10).
     05 shipTo.
       10 country pic xx value 'US'.
       10 name pic x(30).
       10 street pic x(30).
       10 city pic x(30).
       10 state pic xx.
       10 zip pic x(10).
     05 billTo.
       10 country pic xx value 'US'.
       10 name pic x(30).
       10 street pic x(30).
       10 city pic x(30).
       10 state pic xx.
       10 zip pic x(10).
     05 orderComment pic x(80).
     05 items.
       10 item occurs 0 to 20 times depending on numItems.
         15 partNum pic x(6).
         15 productName pic x(50).
         15 quantity pic 99.
         15 USPrice pic 999v99.
         15 shipDate pic x(10).
         15 itemComment pic x(40).
   01 numChars comp pic 9999.
   01 xmlPO pic x(9999).
   01 xmlPOa pic x(9999).
   01 prettyPrint.
     05 pose pic 999.
     05 posd pic 999.
     05 depth pic 99.
     05 element pic x(30).
     05 indent pic x(20).
     05 buffer pic x(100).
Procedure division.
  m.
    Move 20 to numItems
    Move spaces to purchaseOrder

    Move '1999/10/20' to orderDate

    Move 'US' to country of shipTo
    Move 'Alice Smith' to name of shipTo
    Move '123 Maple Street' to street of shipTo
    Move 'Mill Valley' to city of shipTo
    Move 'CA' to state of shipTo
    Move '90952' to zip of shipTo

    Move 'US' to country of billTo
    Move 'Robert "O''Reilly"' to name of billTo
    Move '8 Oak Avenue' to street of billTo
    Move 'Old Town' to city of billTo
    Move 'PA' to state of billTo
    Move '95819' to zip of billTo
    Move 'Hurry, my lawn is going wild!' to orderComment

    Move 0 to numItems
    Call 'addFirstItem'
    Call 'addSecondItem'
    move space to xmlPO
    Xml generate xmlPO from purchaseOrder count in numChars
      on exception
        display 'XML generation error ' xml-code
    End-xml
    display 'Original XML document:'
    display ' '
    display '|' xmlPO(1:numChars) '|'
    display ' '
    display 'Pretty-printed:'
    display ' '
    Call 'pretty' using xmlPO value numChars
    Call 'c2a' using xmlPO xmlPOa numChars
    display ' '
    display 'Transformed document:'
    display ' '
    display '|' xmlPOa(1:numChars) '|'
    display ' '
    display 'Pretty-printed:'
    display ' '
    Call 'pretty' using xmlPOa value numChars
    Goback
    .

*****************************************************************
Program C2A: Transform XML content to attributes *
Parameters (all by reference): *
XMLOrg pic x(=nc) - input: *
original XML document, using element content *
XMLAsAtt pic x(9999) - output: *
transformed XML document, using attributes *
nc comp pic 9999 - input/output *
input - size of original XML document in characters *
output - size of transformed document in characters *
*****************************************************************
Identification division.
  Program-id. 'c2a'.
Data division.
 Working-storage section.
  1 nca comp pic 99999.
  1 prename pic x(30).
  1 tagname pic x(30).
  1 pos comp pic 999.
  1 buffer pic x(99).
  1 ix comp pic 999.
  1 tagstate comp pic 9.
   88 closed value 0.
   88 opened value 1.
   88 attributes value 2.
 Linkage section.
  1 xmlOrg.
   2 pic x occurs 1 to 9999 depending on nc.
  1 xmlAsAtt pic x(9999).
  1 nc comp pic 9999.
Procedure division using xmlOrg xmlAsAtt nc.
    Initialize tagstate prename tagname
    Move 1 to nca pos
    Xml parse xmlOrg processing procedure p
    Move nca to nc
    Goback
    .
  p.
    Evaluate xml-event
      When 'START-OF-ELEMENT'
        If opened
          Move '>' to xmlAsAtt(nca:1)
          Add 1 to nca
        End-if
        If tagname not = space
          If attributes
            Move '>' to xmlAsAtt(nca:1)
            Add 1 to nca
          End-if
          String '<' delimited by size tagname delimited by space
              into xmlAsAtt with pointer nca
          Move tagname to prename
          Set opened to true
        End-if
        Move xml-text to tagname
      When 'CONTENT-CHARACTERS'
        String xml-text delimited by size into buffer
            with pointer pos
      When 'CONTENT-CHARACTER'
        Evaluate xml-text
          When '<'
            String '&lt;' delimited by size into buffer
                with pointer pos
          When '&'
            String '&amp;' delimited by size into buffer
                with pointer pos
          When other
            String xml-text delimited by size into buffer
                with pointer pos
        End-evaluate
      When 'END-OF-ELEMENT'
        If pos > 1
          Subtract 1 from pos
          If prename not = space
            String space xml-text '="' delimited by size
                into xmlAsAtt with pointer nca
            Move 0 to tally
            Inspect buffer(1:pos) tallying tally for all '"'
            If tally = 0
              Move buffer(1:pos) to xmlAsAtt(nca:pos)
              Add pos to nca
            Else
              Perform varying ix from 1 by 1 until ix > pos
                If buffer(ix:1) = '"'
                  Move '&quot;' to xmlAsAtt(nca:6)
                  Add 6 to nca
                Else
                  Move buffer(ix:1) to xmlAsAtt(nca:1)
                  Add 1 to nca
                End-if
              End-perform
            End-if
            Move '"' to xmlAsAtt(nca:1)
            Add 1 to nca
            Set attributes to true
          Else
            String
                '<' xml-text '>' buffer(1:pos) '</' xml-text '>'
                delimited by size into xmlAsAtt
                with pointer nca
            Set closed to true
          End-if
          Move 1 to pos
        Else
          If xml-text = prename
            Move '/>' to xmlAsAtt(nca:2)
            Add 2 to nca
            Move space to prename
          Else
            String '</' xml-text '>' delimited by size
                into xmlAsAtt with pointer nca
          End-if
          Set closed to true
        End-if
        Move space to tagname
      When other
        Continue
    End-evaluate
    .
End program 'c2a'.

Identification division.
  Program-id. 'addFirstItem'.
Procedure division.
    Add 1 to numItems
    Move '872-AA' to partNum(numItems)
    Move 'Lawnmower' to productName(numItems)
    Move 1 to quantity(numItems)
    Move 148.95 to USPrice(numItems)
    Move 'Confirm this is electric' to itemComment(numItems)
    Goback.
End program 'addFirstItem'.

Identification division.
  Program-id. 'addSecondItem'.
Procedure division.
    Add 1 to numItems
    Move '926-AA' to partNum(numItems)
    Move 'Baby Monitor' to productName(numItems)
    Move 1 to quantity(numItems)
    Move 39.98 to USPrice(numItems)
    Move '1999-05-21' to shipDate(numItems)
    Goback.
End program 'addSecondItem'.

End program 'XGFXA'.

Identification division.
  Program-id. Pretty.
Data division.
 Working-storage section.
   01 prettyPrint.
     05 pose pic 999.
     05 posd pic 999.
     05 depth pic 99.
     05 inx pic 999.
     05 elementName pic x(30).
     05 indent pic x(40).
     05 buffer pic x(998).
     05 lastitem pic 9.
       88 unknown value 0.
       88 element value 1.
       88 attribute value 2.
       88 charcontent value 3.
 Linkage section.
  1 doc.
   2 pic x occurs 16384 times depending on len.
  1 len comp-5 pic 9(9).
Procedure division using doc value len.
  m.
    Move space to prettyPrint
    Move 0 to depth posd
    Move 1 to pose
    Xml parse doc processing procedure p
    Goback
    .
  p.
    Evaluate xml-event
      When 'START-OF-ELEMENT'
        Evaluate true
          When element
            String '>' delimited by size into buffer
                with pointer posd
          When attribute
            String '''>' delimited by size into buffer
                with pointer posd
        End-evaluate
        If elementName not = space
          Perform printline
        End-if
        Move xml-text to elementName
        Add 1 to depth
        Move 1 to pose
        Set element to true
        String '<' xml-text delimited by size into buffer
            with pointer pose
        Move pose to posd
      When 'ATTRIBUTE-NAME'
        If element
          String ' ' delimited by size into buffer
              with pointer posd
        Else
          String ''' ' delimited by size into buffer
              with pointer posd
        End-if
        String xml-text '=''' delimited by size into buffer
            with pointer posd
        Set attribute to true
      When 'ATTRIBUTE-CHARACTERS'
        String xml-text delimited by size into buffer
            with pointer posd
      When 'ATTRIBUTE-CHARACTER'
        String xml-text delimited by size into buffer
            with pointer posd
      When 'CONTENT-CHARACTERS'
        Evaluate true
          When element
            String '>' delimited by size into buffer
                with pointer posd
          When attribute
            String '''>' delimited by size into buffer
                with pointer posd
        End-evaluate
        String xml-text delimited by size into buffer
            with pointer posd
        Set charcontent to true
      When 'CONTENT-CHARACTER'
        Evaluate true
          When element
            String '>' delimited by size into buffer
                with pointer posd
          When attribute
            String '''>' delimited by size into buffer
                with pointer posd
        End-evaluate
        String xml-text delimited by size into buffer
            with pointer posd
        Set charcontent to true
      When 'END-OF-ELEMENT'
        Move space to elementName
        Evaluate true
          When element
            String '/>' delimited by size into buffer
                with pointer posd
          When attribute
            String '''/>' delimited by size into buffer
                with pointer posd
          When other
            String '</' xml-text '>' delimited by size
                into buffer with pointer posd
        End-evaluate
        Set unknown to true
        Perform printline
        Subtract 1 from depth
        Move 1 to posd
      When other
        Continue
    End-evaluate
    .
  printline.
    Compute inx = function max(0 2 * depth - 2) + posd - 1
    If inx > 120
      compute inx = 117 - function max(0 2 * depth - 2)
      If depth > 1
        Display indent(1:2 * depth - 2) buffer(1:inx) '...'
      Else
        Display buffer(1:inx) '...'
      End-if
    Else
      If depth > 1
        Display indent(1:2 * depth - 2) buffer(1:posd - 1)
      Else
        Display buffer(1:posd - 1)
      End-if
    End-if
    .
End program Pretty.

And here's the output from the example:

Original XML document:

|<purchaseOrder><po><orderDate>1999/10/20</orderDate><shipTo><country>US</country><name>Alice Smith</name><street>123 Ma
ple Street</street><city>Mill Valley</city><state>CA</state><zip>90952</zip></shipTo><billTo><country>US</country><name>
Robert &quot;O&apos;Reilly&quot;</name><street>8 Oak Avenue</street><city>Old Town</city><state>PA</state><zip>95819</zi
p></billTo><orderComment>Hurry, my lawn is going wild!</orderComment><items><item><partNum>872-AA</partNum><productName>
Lawnmower</productName><quantity>1</quantity><USPrice>148.95</USPrice><shipDate> </shipDate><itemComment>Confirm this is
electric</itemComment></item><item><partNum>926-AA</partNum><productName>Baby Monitor</productName><quantity>1</quantit
y><USPrice>39.98</USPrice><shipDate>1999-05-21</shipDate><itemComment> </itemComment></item></items></po></purchaseOrder
>|

Pretty-printed:

<purchaseOrder>
<po>
<orderDate>1999/10/20</orderDate>
<shipTo>
<country>US</country>
<name>Alice Smith</name>
<street>123 Maple Street</street>
<city>Mill Valley</city>
<state>CA</state>
<zip>90952</zip>
</shipTo>
<billTo>
<country>US</country>
<name>Robert "O'Reilly"</name>
<street>8 Oak Avenue</street>
<city>Old Town</city>
<state>PA</state>
<zip>95819</zip>
</billTo>
<orderComment>Hurry, my lawn is going wild!</orderComment>
<items>
<item>
<partNum>872-AA</partNum>
<productName>Lawnmower</productName>
<quantity>1</quantity>
<USPrice>148.95</USPrice>
<shipDate> </shipDate>
<itemComment>Confirm this is electric</itemComment>
</item>
<item>
<partNum>926-AA</partNum>
<productName>Baby Monitor</productName>
<quantity>1</quantity>
<USPrice>39.98</USPrice>
<shipDate>1999-05-21</shipDate>
<itemComment> </itemComment>
</item>
</items>
</po>
</purchaseOrder>

Transformed document:

|<purchaseOrder><po orderDate="1999/10/20"><shipTo country="US" name="Alice Smith" street="123 Maple Street" city="Mill
Valley" state="CA" zip="90952"/><billTo country="US" name="Robert &quot;O'Reilly&quot;" street="8 Oak Avenue" city="Old
Town" state="PA" zip="95819"/><orderComment>Hurry, my lawn is going wild!</orderComment><items><item partNum="872-AA" pr
oductName="Lawnmower" quantity="1" USPrice="148.95" shipDate=" " itemComment="Confirm this is electric"/><item partNum="
926-AA" productName="Baby Monitor" quantity="1" USPrice="39.98" shipDate="1999-05-21" itemComment=" "/></items></po></pu
rchaseOrder> |

Pretty-printed:

<purchaseOrder>
<po orderDate='1999/10/20'>
<shipTo country='US' name='Alice Smith' street='123 Maple Street' city='Mill Valley' state='CA' zip='90952'/>
<billTo country='US' name='Robert "O'Reilly"' street='8 Oak Avenue' city='Old Town' state='PA' zip='95819'/>
<orderComment>Hurry, my lawn is going wild!</orderComment>
<items>
<item partNum='872-AA' productName='Lawnmower' quantity='1' USPrice='148.95' shipDate=' ' itemComment='Confirm ...
<item partNum='926-AA' productName='Baby Monitor' quantity='1' USPrice='39.98' shipDate='1999-05-21' itemCommen...
</items>
</po>
</purchaseOrder>



And here's the output from the example:

Original XML document:

|<purchaseOrder><po><orderDate>1999/10/20</orderDate><shipTo><country>US</country><name>Alice Smith</name><street>123 Ma
ple Street</street><city>Mill Valley</city><state>CA</state><zip>90952</zip></shipTo><billTo><country>US</country><name>
Robert &quot;O&apos;Reilly&quot;</name><street>8 Oak Avenue</street><city>Old Town</city><state>PA</state><zip>95819</zi
p></billTo><orderComment>Hurry, my lawn is going wild!</orderComment><items><item><partNum>872-AA</partNum><productName>
Lawnmower</productName><quantity>1</quantity><USPrice>148.95</USPrice><shipDate> </shipDate><itemComment>Confirm this is
electric</itemComment></item><item><partNum>926-AA</partNum><productName>Baby Monitor</productName><quantity>1</quantit
y><USPrice>39.98</USPrice><shipDate>1999-05-21</shipDate><itemComment> </itemComment></item></items></po></purchaseOrder
>|

Pretty-printed:

<purchaseOrder>
<po>
<orderDate>1999/10/20</orderDate>
<shipTo>
<country>US</country>
<name>Alice Smith</name>
<street>123 Maple Street</street>
<city>Mill Valley</city>
<state>CA</state>
<zip>90952</zip>
</shipTo>
<billTo>
<country>US</country>
<name>Robert "O'Reilly"</name>
<street>8 Oak Avenue</street>
<city>Old Town</city>
<state>PA</state>
<zip>95819</zip>
</billTo>
<orderComment>Hurry, my lawn is going wild!</orderComment>
<items>
<item>
<partNum>872-AA</partNum>
<productName>Lawnmower</productName>
<quantity>1</quantity>
<USPrice>148.95</USPrice>
<shipDate> </shipDate>
<itemComment>Confirm this is electric</itemComment>
</item>
<item>
<partNum>926-AA</partNum>
<productName>Baby Monitor</productName>
<quantity>1</quantity>
<USPrice>39.98</USPrice>
<shipDate>1999-05-21</shipDate>
<itemComment> </itemComment>
</item>
</items>
</po>
</purchaseOrder>

Transformed document:

|<purchaseOrder><po orderDate="1999/10/20"><shipTo country="US" name="Alice Smith" street="123 Maple Street" city="Mill
Valley" state="CA" zip="90952"/><billTo country="US" name="Robert &quot;O'Reilly&quot;" street="8 Oak Avenue" city="Old
Town" state="PA" zip="95819"/><orderComment>Hurry, my lawn is going wild!</orderComment><items><item partNum="872-AA" pr
oductName="Lawnmower" quantity="1" USPrice="148.95" shipDate=" " itemComment="Confirm this is electric"/><item partNum="
926-AA" productName="Baby Monitor" quantity="1" USPrice="39.98" shipDate="1999-05-21" itemComment=" "/></items></po></pu
rchaseOrder> |

Pretty-printed:

<purchaseOrder>
<po orderDate='1999/10/20'>
<shipTo country='US' name='Alice Smith' street='123 Maple Street' city='Mill Valley' state='CA' zip='90952'/>
<billTo country='US' name='Robert "O'Reilly"' street='8 Oak Avenue' city='Old Town' state='PA' zip='95819'/>
<orderComment>Hurry, my lawn is going wild!</orderComment>
<items>
<item partNum='872-AA' productName='Lawnmower' quantity='1' USPrice='148.95' shipDate=' ' itemComment='Confirm ...
<item partNum='926-AA' productName='Baby Monitor' quantity='1' USPrice='39.98' shipDate='1999-05-21' itemCommen...
</items>
</po>
</purchaseOrder>

[{"Product":{"code":"SS6SG3","label":"Enterprise COBOL for z\/OS"},"Business Unit":{"code":"BU054","label":"Systems w\/TPS"},"Component":"Compile","Platform":[{"code":"PF035","label":"z\/OS"}],"Version":"3.4;4.1;4.2;5.1","Edition":"","Line of Business":{"code":"LOB17","label":"Mainframe TPS"}},{"Product":{"code":"SS6SGM","label":"COBOL for AIX"},"Business Unit":{"code":"BU058","label":"IBM Infrastructure w\/TPS"},"Component":"Compiler","Platform":[{"code":"PF002","label":"AIX"}],"Version":"2.0","Edition":"","Line of Business":{"code":"LOB17","label":"Mainframe TPS"}}]

Historical Number

FITS_MR0526047450

Document Information

Modified date:
08 August 2018

UID

swg21218516