Hi

I am trying to use HXT (8.3.2) for parsing XML. I think an example will
clarify what I want to do. I want to parse XML like this:

<object class="ex1">
   <foo/>
   <foo>
      <object class="ex2"/>
      <object class="ex3"/>
   </foo>
   <object class="ex4"/>
</object>

and want to turn it into the following Haskell data structure:

data Widget = Widget 
    { cls :: String
    , children :: [Widget]
    }

The XML above should be turned into:

Widget "ex1" [Widget "ex2" [], Widget "ex3" [], Widget "ex4" []]

That is, I want everything but the object-tags stripped out. And I want
to keep the hierarchy of the object-tags.

I thus wrote the following program:

{-# LANGUAGE Arrows, NoMonomorphismRestriction #-}

module Main where

import Text.XML.HXT.Arrow


data Widget = Widget 
    { cls :: String
    , children :: [Widget]
    }
    deriving Show

main = (runX (readDocument [(a_validate,v_0)] "test.xrc"
               >>> getObject))
       >>= print

getObject =
    deep (isElem >>> hasName "object") >>>
    proc x -> do
      cls <- getAttrValue "class"            -< x
      cs  <- listA getObject <<< getChildren -< x  -- recursive call here
      returnA -< Widget cls cs


But it do not work as intended. In stead I get the following output:

[Widget {cls = "ex1", children = []},Widget {cls = "ex1", children =
[]},Widget {cls = "ex1", children = []},Widget {cls = "ex1", children =
[]},Widget {cls = "ex1", children = []},Widget {cls = "ex1", children =
[]},Widget {cls = "ex1", children = []}]


Hopefully somebody can point me in the right direction.


Greetings,

Mads Lindstrøm

Attachment: signature.asc
Description: This is a digitally signed message part

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to