XML, COBOL and Application
XML, COBOL and Application
IBM 2007
Agenda
Some XML terminology Scenarios XML support in COBOL WebSphere Developer XSE
Discussion, questions
IBM 2007
Agenda...
IBM 2007
fragment)
effect the XML document becomes a miniature data base that supports navigation and simple queries
exactly one root element a matching end tag for every start tag elements properly nested, etc., etc. Well-formedness, plus... Element order and containment (structure constraints) Proper content (type constraints)
4
IBM 2007
Agenda...
IBM 2007
Customer scenarios/problems - 1
To allow non-traditional clients to use them A step towards componentization In particular to allow access as a Web Service Various transports/protocols Performance typically critical
B i n a r y I n t e r f a c e
Web
Interactive Voice Response
XML
Adapter/ converter
IBM 2007
Customer scenarios/problems - 2
Inter-application communication
Need arises because of mergers/acquisitions, or Between different purchased applications Interfaces need only be compatible, not identical Allows schema evolution without synchronized updates Would previously have been done with file readers/writers Single Enterprise system/complex
Existing app-1
[Address space A]
B i n a r y I n t e r f a c e C o n v e r t e r B i n a r y I n t e r f a c e
Existing app-2
[Address space B]
or
C o n v e r t e r
XML
New app-2
[Address space B]
IBM 2007
Agenda...
IBM 2007
Coherent development context and methodology Centralizes business logic within the application
Independent of middleware choices, characteristics Allows business logic to be conveniently applied during and after message acquisition/generation Incremental step from existing application design Can process XML messages as such
IBM 2007
Converters, bridging to existing (unchanged) applications Direct use of XML in new or enhanced applications
IBM 2007
10
XML PARSE xml-doc PROCESSING PROCEDURE xml-handler XML GENERATE xml-doc FROM data-item COUNT IN char-count
Designed for high-speed transaction processing CICS, IMS, batch, TSO, USS, ... Use MQSeries, CICS transient queue or COMMAREA, IMS message processing queue, WebSphere, etc.
Provides basic SAX-style parsing Checks well-formedness (but not validity) XML Parser is part of the run-time library
IBM 2007
XML PARSE
Parses XML documents that are in memory, in a COBOL alphanumeric or national data item Discovers the individual pieces of XML documents
During parsing you can populate COBOL data structures with the data from XML messages
Advantage: non-COBOL programs can communicate data to/from COBOL without having to know the COBOL data structure formats!
IBM 2007
12
XML PARSE
The COBOL interface to the high-speed XML parser XML-CODE: communicates status of parsing XML-EVENT: describes each event during parsing XML-TEXT: contains XML document fragments XML-NTEXT: contains NATIONAL XML doc fragments
XML PARSE XMLDOCUMENT PROCESSING PROCEDURE XMLEVENT-HANDLER END-XML ... XMLEVENT-HANDLER. EVALUATE TRUE WHEN XML-EVENT = 'START-OF-ELEMENT' AND XML-TEXT = 'TRADE DISPLAY 'Processing new stock trade ...
IBM 2007
13
XML Text <?xml version="1.0"?><msg type="succinct">Hello, World!</msg> 1.0 msg type succinct Hello, World! msg
14
Into an alphanumeric or national data item From a group or elementary item Trailing spaces removed from alphanumeric values (leading spaces from right-justified items) Leading zeroes removed from numeric values
XML tag names are the mixed-case data names Supports all data types except -pointer and object reference Unnamed and redefining items are ignored For more details see V3.4 Programming Guide:
www.ibm.com/software/awdtools/cobol/zos/library/
15
IBM 2007
|<Greeting><msg>Hello, World!</msg></Greeting>|
IBM 2007
16
1 Hello-doc pic x(200). 1 Greeting-Grp. 2 Contact-info. 3 Name PIC x(20) Value 'Tom'. 3 Addr PIC x(18) Value '555 Bailey Ave'. 3 Telephone PIC 9(12) Value 4084634242. 2 Contact-redef REDEFINES Contact-info. 3 Junk PIC X(50). 2 msg pic x(100) value 'Hello, World! '. 1 Greeting-redef REDEFINES Greeting-Grp. 2 Name PIC x(20). 2 PIC x(18). 2 Phone PIC 9(12). 2 Short-Msg PIC X(10). 1 Num-chars binary pic 9(9).
IBM 2007
17
18
Agenda...
Some XML terminology Scenarios XML support in COBOL WebSphere Developer for zSeries (WD for z) XML Services for the Enterprise (XSE)
IBM 2007
19
What is WD XSE?
Allows COBOL applications to consume and produce XML messages Leverages XML parsing capabilities of IBM Enterprise COBOL V3 Creates:
Inbound converter program, to convert XML messages into native COBOL data Outbound converter program, to convert native COBOL data into XML messages Sample COBOL driver program:
Illustrates
the invocation of converters Illustrates the interaction with existing application Needs to be modified before use
IBM 2007
WD XSE
IBM 2007
Web Service Runtime and Scenario Selection dialog Create New Service Interface (bottom-up) wizard Compiled XML conversion type Language structures page Generation options page BIDI conversion options dialog Runtime specific pages Web Services for CICS page IMS SOAP Access page File, data set or member selection Interpretive XML conversion type (bottom-up) CICS Web Services Assistant pages (bottom-up) Create New Service Implementation (top-down) wizard Interpretive XML conversion type (top-down) CICS Web Services Assistant pages (top-down) Map to an Existing Service Interface (meet-in-the-middle) Mapping Converter Generator wizard Generating artifacts remotely
21
WD XSE
Web Service Runtime and Scenario Selection dialog
Select artifact then File->New->Other
OR Enable Enterprise Web service from pop-up menu
IBM 2007
22
Start the appropriate XSE wizard for selected combination of target runtime, web service development scenario and XML conversion technology type.
IBM 2007
23
Supported Runtimes Web Services for CICS (CICS TS 3.1) SOAP for CICS (CICS TS 2.2/2.3/3.1) IMS SOAP Gateway Batch, TSO and USS
IBM 2007
24
Scenario name Create New Service Interface Map an Existing Service Interface Create New Service Implementation
IBM 2007
25
Supported Conversion Types Compiled XML Conversion Interpretive XML Conversion (CICS TS 3.1)
IBM 2007
26
Help on the XML Conversion technology type is available. Interpretive is only available for Web Services for CICS runtime.
IBM 2007
27
To learn about the Runtimes, Scenarios and Conversion types, refer to the WD/z online help. Note that not all possible combinations are supported. The WD/z online help has a table of the supported combinations.
IBM 2007
28
IBM 2007
29
Create New Service Interface (bottom-up) wizard Compiled XML conversion type Runtime specific pages
Web services for CICS IMS SOAP Gateway
IBM 2007
30
Interpretive XML conversion type CICS Web Services Assistant pages (bottom up)
IBM 2007
31
IBM 2007
32
Map to an Existing Service Interface (meet-in-the-middle) Generate Conversion Code for mapping
You start Mapping Converter Generator wizard from Web Service Runtime selection dialog (similar to the Create New Service Interface (bottom-up) wizard) Even though you specify the Runtime when you create the Mapping session file, that information does not persist after creation of the mapping file.
IBM 2007
33
Common
Common
34
Common
Common
35
IBM 2007
WD XSEstrengths:
Robust error recovery, using LE services Highly optimized and sophisticated content processing
Uses
Unnecessary elements are conveniently ignored Can derive XML definition from COBOL, or match independent XML and COBOL definitions Generated schema can be used to validate messages and as input to the WSDL file
IBM 2007
37
XML PARSEstrengths:
Business logic can be conveniently applied during and after message acquisition/generation XML definition can be independent of (any) data structure Can short-circuit parsing early after required input is seen
XML GENERATEFROMstrengths:
Very simple to use A single COBOL statement provides wholesale conversion from a data structure to a document The generated XML precisely matches the data structure Redefinition allows selective output, different tag names
38
IBM 2007
Agenda...
Some XML terminology Scenarios XML support in COBOL WebSphere StudioXML Enablement Discussion, questions
IBM 2007
39
40
Procedure division. mainline section. perform get-doc perform until in-len = 0 if p > 0 xml parse xml-document(1:p) processing procedure xml-handler on exception display 'XML document error ' xml-code not on exception display 'XML document successfully parsed' end-xml end-if perform get-doc end-perform goback . get-fn section. display ' Enter XML document file name or SYSIN (null to end)' move space to fn move 0 to tally accept fn inspect function reverse(fn) tallying tally for leading space compute in-len = 150 - tally .
IBM 2007
41
IBM 2007
get-doc section. perform get-fn evaluate true when in-len = 0 continue when fn(1:in-len) = 'SYSIN' display ' Enter XML document:' move spaces to xml-document(1:150) accept xml-document(1:150) move function lower-case(xml-document(1:150)) to xml-document(1:150) move 0 to p inspect function reverse(xml-document(1:150)) tallying p for leading spaces compute p = 150 - p when other move ft to fn(in-len + 1:length of ft) call 'putenv' using by value address of fv returning rc if rc not = 0 display 'putenv failed with rc = ' rc '.' stop run end-if open input xf if fs = 0 read xf end-if move 1 to p perform until fs not = 0 if p - 1 + length of r > length of xml-document display 'XML document is larger than the document ' 'buffer (' length of xml-document ' bytes).' move 13 to fs else string r delimited by size into xml-document with pointer p read xf end-if end-perform evaluate fs when 10 subtract 1 from p when 13 move 0 to p when other display 'Some catastrophe on file ' fn(1:in-len) '; status = ' fs '.' move 0 to p end-evaluate close xf end-evaluate 42 .
IBM 2007
xml-handler section. evaluate xml-event when 'START-OF-DOCUMENT' compute rc = function length(xml-text) move rc to st call 'nzp' using st l display ' ' display 'Start of document: length=' st(l:) ' characters.' when 'END-OF-DOCUMENT' display 'End of document.' display ' ' when 'VERSION-INFORMATION' display 'Version: <' xml-text '>' when 'ENCODING-DECLARATION' display 'Encoding: <' xml-text '>' when 'STANDALONE-DECLARATION' display 'Standalone: <' xml-text '>' when 'START-OF-ELEMENT' display 'Start element tag: <' xml-text '>' when 'ATTRIBUTE-NAME' display 'Attribute name: <' xml-text '>' when 'ATTRIBUTE-CHARACTERS' display 'Attribute value characters: <' xml-text '>' when 'ATTRIBUTE-CHARACTER' display 'Attribute value character: <' xml-text '>' when 'END-OF-ELEMENT' display 'End element tag: <' xml-text '>' when 'START-OF-CDATA-SECTION' display 'Start of CData: <' xml-text '>' when 'END-OF-CDATA-SECTION' display 'End of CData: <' xml-text '>' when 'CONTENT-CHARACTERS' display 'Content characters: <' xml-text '>' when 'CONTENT-CHARACTER' display 'Content character: <' xml-text '>' when 'PROCESSING-INSTRUCTION-TARGET' display 'PI target: <' xml-text '>' when 'PROCESSING-INSTRUCTION-DATA' display 'PI data: <' xml-text '>' when 'COMMENT' display 'Comment: <' xml-text '>' when 'EXCEPTION' compute rc = function length (xml-text) move rc to st call 'nzp' using st l display 'Exception ' xml-code ' at offset ' st(l:) '.' when other display 'Unexpected xml event: ' xml-event '.' end-evaluate . End program xmldump.
43
Identification division. Program-id. nzp. Data division. Linkage section. 1 str pic x(9). 1 pos binary pic 9(5). Procedure division using str pos. if str = '000000000' move 9 to pos else move 0 to pos inspect str tallying pos for leading '0' add 1 to pos end-if goback . End program nzp.
IBM 2007
44
IBM 2007
45
Procedure division. m. Move 20 to numItems Move spaces to purchaseOrder Move '1999-10-20' to orderDate Move Move Move Move Move Move Move Move Move Move Move Move Move 'US' to country of shipTo 'Alice Smith' to name of shipTo '123 Maple Street' to street of shipTo 'Mill Valley' to city of shipTo 'CA' to state of shipTo '90952' to zip of shipTo 'US' to country of billTo 'Robert Smith' to name of billTo '8 Oak Avenue' to street of billTo 'Old Town' to city of billTo 'PA' to state of billTo '95819' to zip of billTo '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 Call 'pretty' using xmlPO value numChars Goback.
IBM 2007
46
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 XGFX.
IBM 2007
47
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 element pic x(30). 05 indent pic x(20). 05 buffer pic x(100). 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.
IBM 2007
48
p. Evaluate xml-event When 'START-OF-ELEMENT' If element not = space If depth > 1 Display indent(1:2 * depth - 2) buffer(1:pose - 1) Else Display buffer(1:pose - 1) End-if End-if Move xml-text to element Add 1 to depth Move 1 to pose String '<' xml-text '>' delimited by size into buffer with pointer pose Move pose to posd When 'CONTENT-CHARACTERS' String xml-text delimited by size into buffer with pointer posd When 'CONTENT-CHARACTER' String xml-text delimited by size into buffer with pointer posd When 'END-OF-ELEMENT' Move space to element String '</' xml-text '>' delimited by size into buffer with pointer posd If depth > 1 Display indent(1:2 * depth - 2) buffer(1:posd - 1) Else Display buffer(1:posd - 1) End-if Subtract 1 from depth Move 1 to posd When other Continue End-evaluate. End program Pretty.
IBM 2007
49
IBM 2007
50
<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> </purchaseOrder>
IBM 2007
51