{- Basic demonstration of how to do a lighterweight binding to a .NET type and its methods (without generating a full wrapper module for it and all its dependencies.) The System.Xml.XmlReader type is used to read in a document: * tokenize it by the nodes we encounter via the XmlReader API. * translate that into a tree representation. There's room for improvement in this translation etc., but the main mission of the example is to demonstrate how to make use of the .NET bridge. Test: parseXML "xml/books.xml" -} module ParseXML where import NET -- Simple rep. of XML trees: data Xml = Element String [Attribute] [Xml] | Txt String | CData String deriving ( Show ) type Attribute = (String,String) data XmlNode = XmlNode { xmlNodeKind :: NodeKind , xmlName :: String , xmlAttrs :: [(String,String)] , xmlValue :: String } deriving ( Show ) data NodeKind = None | Elem | Attribute | Text | CDATA | EntityReference | Entity | ProcessingInstruction | Comment | Document | DocumentType | DocumentFragment | Notation | Whitespace | SignificantWhitespace | EndElement | EndEntity | XmlDeclaration deriving ( Eq, Show, Enum, Bounded ) type XMLDoc a = Object a readXML :: FilePath -> IO (XMLDoc ()) readXML fp = do xmlReader <- createObject "System.Xml.XmlTextReader" fp return xmlReader parseXML :: FilePath -> IO [Xml] --String parseXML fp = readXML fp >>= parseIt parseIt :: XMLDoc () -> IO [Xml] parseIt xr = do -- uncomment if you are not interested in the initial decls -- xr # invoke_ "MoveToContent" () ts <- xr # tokenize return (fst $ parse (const False) ts) where parse _ [] = ([],[]) parse pre (x:xs) = let (as,bs) = parse pre xs in case xmlNodeKind x of EndElement | pre (xmlName x) -> ([],xs) Text -> (Txt (xmlValue x) : as, bs) CDATA -> (CData (xmlValue x) : as, bs) Elem -> case parse ((xmlName x)==) xs of (vs,xs1) -> let (as,bs) = parse pre xs1 in (Element (xmlName x) (xmlAttrs x) vs : as, bs) _ -> (as,bs) -- -- Read in the nodes making up the document; separate this from -- the subsequent functional construction of the XML tree. -- tokenize :: XMLDoc () -> IO [XmlNode] tokenize xr = do xr # invoke_ "Read" () v <- xr # getField "NodeType" () if v == 0 || v > (fromEnum (maxBound :: NodeKind)) then return [] else do (nm,val)<- xr # getNameValue as <- xr # getAttributes let newNode = XmlNode{xmlNodeKind=toEnum v, xmlAttrs=as, xmlValue=val, xmlName=nm} xs <- xr # tokenize return (newNode : xs) where getNameValue th = do n <- th # getField "Name" () v <- th # getField "Value" () return (n,v) getAttributes th = do flg <- th # getField "HasAttributes" () if not flg then return [] else do c <- th # getField "AttributeCount" () mapM (\ i -> do th # invoke_ "MoveToAttribute" (i::Int) th # getNameValue) [0..(c-1)]