{-# OPTIONS_GHC -XEmptyDataDecls #-} -- -- Simple experimentation with System.Xml.Linq functionality -- -- Example invocations: -- runQuery "@examples\\xml\\books.xml" "book" -- runQuery "bd" "c" module LINQ where import NET data XDocument_ a type XDocument a = Object (XDocument_ a) data XContainer_ a type XContainer a = Object (XContainer_ a) data XObject_ a type XObject a = Object (XContainer_ a) parseDocument :: String -> IO (XDocument ()) parseDocument s = invokeStatic "System.Xml.Linq.XDocument" "Parse" s enumMethod :: String -> String enumMethod s = "System.Collections.Generic.IEnumerable." ++ s enumaMethod :: String -> String enumaMethod s = "System.Collections.Generic.IEnumerator." ++ s loadDocument :: String -> IO (XDocument ()) loadDocument s = invokeStatic "System.Xml.Linq.XDocument" "Load" s descendants :: String -> XDocument a -> IO (XContainer ()) descendants str d = do -- too funky, no XName constructor just an implicit from-string operator (which is accessed as below..) nm <- invokeStatic "System.Xml.Linq.XName" "op_Implicit" str obj <- d # invoke "Descendants" (nm :: Object ()) ie <- obj # invoke (enumMethod "GetEnumerator") () -- nm :: Object ()) ie # invoke_ "MoveNext" () return ie enumObjs :: XContainer () -> IO [XObject ()] enumObjs obj = go [] where go acc = do v <- obj # qCurrent b <- obj # invoke "MoveNext" () if not b then return (reverse (v:acc)) else go (v:acc) qCurrent :: XContainer a -> IO (XObject b) qCurrent c = c # invoke (enumaMethod "get_Current") () runQuery :: String -> String -> IO () runQuery s chNode = do d <- case s of { '@':xs -> loadDocument xs ; _ -> parseDocument s} ds <- d # descendants chNode ls <- ds # enumObjs putStrLn (filter (/='\r') $ show ls)