I have some XML things to take care of, and I had hoped to use
a nice functional language with combinators. But I'm having
trouble getting HaXml to do anything useful. Here is a program
that I wrote just to read in the XML and prettyprint it.
But it fails with an error message. The 'expat' tool 'xmlwf'
claims the XML is well formed, and the XML was generated from
gpsbabel, a tool I trust to behave properly. And yet:
: [EMAIL PROTECTED] 10429 ; xmlwf 2006-12-27-backup.gpx
: [EMAIL PROTECTED] 10430 ; $AWD/Main 2006-12-27-backup.gpx
Main: Parse error: unexpected EOF
Here is Main.hs:
module Main where
import qualified Text.XML.HaXml as X
import qualified Text.XML.HaXml.Parse as XP
import qualified Text.XML.HaXml.Pretty as XPP
import qualified IO
import qualified System
load :: String -> IO X.Document
load fn = do handle <- IO.openFile fn IO.ReadMode
contents <- IO.hGetContents handle
IO.hClose handle
return $ XP.xmlParse fn contents
main = do [xml] <- System.getArgs
d <- load xml
IO.putStrLn $ show $ XPP.document $ d
I'm using HaXml version 1.13.2-5 as distributed by Debian,
with GHC 6.6.
Does anyone have thoughts or suggestions? Is there software I should
prefer to HaXml? (I notice that HaXml does not understand XML Schema,
which I seem to be stuck with...)
Norman
_______________________________________________
Haskell mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell