[Haskell-cafe] HXT and types in Control.Arrow.ArrowTree

Robert Vollmert rvollmert-lists at gmx.net
Sat Mar 22 10:29:28 EDT 2008


Hello,

I'm having some trouble with HXT, the types of some functions in  
particular. This may well be caused by a lack of understanding for  
arrow programming -- I'd appreciate any hints.

In short, I'm constantly running into what appear to be artificial  
type restrictions in Control.Arrow.ArrowTree. For example, the  
signature of "deep" is

deep :: (Tree t, ArrowTree a) => a (t b) (t b) -> a (t b) (t b)

instead of the more general

deep :: (Tree t, ArrowTree a) => a (t b) c -> a (t b) c

Say I have an arrow

getLink :: (ArrowXml a) => a XmlTree Link

that converts an HTML link (<a href="url">text</a>) into some  
appropriate data type (code below). To collect all links in a  
document, I'd like to use

deep getLink

instead of

deep (hasName "a") >>> getLink

Is this the wrong approach to converting XML into Haskell data types?

Cheers
Robert


module Links where

import Text.XML.HXT.Arrow

data Link = Link { url, text :: String }
	deriving Show

getLink :: (ArrowXml a) => a XmlTree Link
getLink = isElem >>> hasName "a"
	>>> (getAttrValue0 "href" &&& getAllText)
	>>> arr (uncurry Link)

getAllText :: (ArrowXml a) => a XmlTree String
getAllText = listA (deep isText >>> getText) >>> arr concat



More information about the Haskell-Cafe mailing list