You can produce XML output from a COBOL program by using the XML GENERATE statement , the XML GENERATE statement takes as input the source data item for which the XML needs be generated and stores the corresponding XML in a target or receive data item mentioned in your XML GENERATE statement. Both the source and receive data items must be declared in your programs Data Division.
The COBOL data item which receives the XML code typically must be 10 times the size of the source and is declared as an alphanumeric group or elementary item . The source is also generally declared as an alphanumeric group or elementary item.
Any data items that specify a REDEFINES clause, or are subordinate to such a redefining item or specify the RENAMES or FILLER clause are not transformed to XML by the XML GENERATE.
DATA DIVISION. WORKING STORAGE SECTION. 01 WS-MIS-VARIABLES. 05 TOTAL-CHAR PIC 9(05) VALUE 0. 05 XML-OUTPUT PIC X(1000) VALUE QUOTES. 01 XML-INPUT. 05 NAME PIC X(10) VALUE 'JOHN'. 05 AGE PIC X(02) VALUE 33. PROCEDURE DIVISION. 1000-MAINLINE. XML GENERATE XML-OUTPUT FROM XML-INPUT COUNT IN TOTAL-CHAR ON EXCEPTION DISPLAY "ERROR-XML-CODE = " XML-CODE. DISPLAY XML-OUTPUT(1:TOTAL-CHAR). STOP RUN.
The output of the above program will be :
<XML-INPUT><NAME>JOHN</NAME><AGE>33</AGE></XML-INPUT>
The COUNT IN phrase gives the number of XML character encoding units that are filled during generation of the XML output and you can use the count field as a reference modification length to obtain only that portion of the receiving data item that contains the generated XML output.
XML-CODE is special register that can be used to determine the status of XML generation. At termination of an XML GENERATE statement, XML-CODE contains either zero, indicating successful completion of XML generation, or a nonzero error code, indicating that an exception occurred during XML generation. The common XML GENERATE exception codes : XML GENERATE exceptions.
The ON EXCEPTION phrase in XML GENERATE statement causes control to be transferred to the imperative statement that is specified after on ON EXCEPTION , if you do not code an ON EXCEPTION phrase control is transferred to the end of the XML GENERATE statement.
XML GENERATE XML-OUTPUT FROM XML-INPUT COUNT IN TOTAL-CHAR-COUNT ON EXCEPTION DISPLAY 'XML generation error ' XML-CODE NOT ON EXCEPTION DISPLAY 'XML document was successfully generated.' END-XML.
Example of generating XML using an array as input
DATA DIVISION.
WORKING STORAGE SECTION.
01 WS-MIS-VARIABLES.
05 TOTAL-CHAR PIC 9(05) VALUE 0.
05 XML-OUTPUT PIC X(1000) VALUE QUOTES.
01 XML-INPUT.
02 INPUT-DATA OCCURS 2 TIMES
05 NAME PIC X(10)
05 AGE PIC X(02)
PROCEDURE DIVISION.
1000-MAINLINE.
MOVE "JOHN" TO NAME(1).
MOVE "TOM" TO NAME(2).
MOVE "34" TO AGE(1).
MOVE "24" TO AGE(2).
XML GENERATE XML-OUTPUT
FROM XML-INPUT
COUNT IN TOTAL-CHAR
ON EXCEPTION DISPLAY "ERROR-XML-CODE = " XML-CODE.
DISPLAY XML-OUTPUT(1:TOTAL-CHAR).
STOP RUN.
The output of the program will be :
“<XML-INPUT><INPUT-DATA><NAME>GOVIND</NAME><AGE>22</AGE></INPUT-DATA> <INPUT-DATA><NAME>RAVI</NAME><AGE>34</AGE></INPUT-DATA></XML-INPUT>”
You can use the ATTRIBUTES phrase of the XML GENERATE statement.to have each elementary data item included in the generated XML document to be expressed as an attribute of the XML element that corresponds to its immediately superordinate data item, rather than as a child element.
01 XML-INPUT. 05 NAME PIC X(10) VALUE "JANE". 05 SALARY. 10 BASIC PIC X(5) VALUE "10000" 10 HRA PIC X(3) VALUE "2000". 05 DEPT PIC X(3) VALUE "SALES" XML GENERATE XML-OUT FROM XML-INPUT WITH ATTRIBUTE
The code would then generate the following XML document, in which NAME and DEPT are expressed as attributes of element XML-INPUT, and BASIC and HRA become attributes of element SALARY
: <XML-INPUT NAME=”JANE” DEPT=”SALES”><SALARY BASIC=”10000″ HRA=”2000″></SALARY></XML-INPUT>
You can code the ENCODING phrase of the XML GENERATE statement to specify the CCSID of the generated XML document. If you do not use the ENCODING phrase, the document encoding is determined by the category of the receiving data item and by the CODEPAGE compiler option . The XML-DECLARATION phrase causes the generated XML document to have an XML declaration that includes version information and an encoding declaration.
01 MESSAGE. 05 MSG PIC X(80) VALUE 'Hello world!' XML GENERATE OUTPUT FROM MESSAGE WITH ENCODING 1208 WITH XML-DECLARATION
The code above generates the following XML document:
<?XML VERSION=”1.0″ ENCODING=”UTF-8″?><MESSAGE><MSG>Hello world!</MSG></MESSAGE>
If you do not code the XML-DECLARATION phrase, an XML declaration is not generated.
NAMESPACE phrase is used to specify a namespace for the generated XML document.
01 MESSAGE. 05 MSG PIC X(80) VALUE 'Hello world!' 01 NAME-SPACE PIC X(10) VALUE "HTTP://MAINFRAMEWIKI.COM" XML GENERATE OUTPUT FROM MESSAGE WITH ENCODING 1208 WITH XML-DECLARATION
The code above generates the following XML document:
<MESSAGE XMLNS=”HTTP://MAINFRAMEWIKI”><MSG>Hello world!</MSG></MESSAGE>
If you do not specify a namespace, the element names in the generated XML document are not in any namespace.
Recent Comments