[Haskell-cafe] HXT - problems with runIOSLA or xread

Niklas din.kompis at gmail.com
Fri Jul 21 10:33:21 EDT 2006


Hi everybody,

and especially Uwe Schmidt et al.

I ran into some problems trying to process some xml from a string source,
illustrated in the code below. From file, using readDocument, everything works
great though. I've probably missed a finer detail or two in the arrow handling,
or it could be a bug in HXT (if I run the code in ghci, it will crash hard).

Output:
-->main.exe
NTree (XTag (QN {namePrefix = "", localPart = "small", namespaceUri = ""}) []) [
NTree (XTag (QN {namePrefix = "", localPart = "xml", namespaceUri = ""}) []) [],
NTree (XTag (QN {namePrefix = "", localPart = "example", namespaceUri = ""}) [])
 []]
-->

So it seems that the string gets read, since it shows up as a result from
procString, but I get no output from writeDocument in writeStrDoc. Could anybody
enlighten me?

I'm using GHC 6.5 and HXT 6.0 on Windows XP.

Regards,

    /Niklas

---8<---

module Main where

import Text.XML.HXT.Arrow

wa = [(a_indent, "1"), (a_remove_whitespace, "1")]

main = procString tststr >>= mapM_ print . snd

procString = runIOSLA writeStrDoc (initialState ())

writeStrDoc = xread >>> writeDocument wa "-"

tststr = "<small><xml/><example/></small>"

--->8---




More information about the Haskell-Cafe mailing list