[Haskell-cafe] RoseTree + Data.Typeable.Zipper

Sergey Mironov ierton at gmail.com
Sun Jan 8 15:15:35 CET 2012


Hi list!
Could you please give me a quick example of navigating throw
Data.Typeable.Zipper built on top of a Rose Tree?
eg. (See ??? in the last line - is my question)

{-#LANGUAGE TemplateHaskell, DeriveDataTypeable, TypeOperators #-}

import Data.Typeable.Zipper

data Tree k a = Tree {
    _rules :: [(k,Tree k a)]
    } deriving(Show, Typeable)

$(mkLabelsNoTypes [''Tree])

atree = Tree [(1, Tree []), (2, Tree []), (3, Tree [(11, Tree [])])]

moveToLeftmostChild :: (Typeable k, Typeable a) =>
    Zipper1 (Tree k a) -> Zipper1 (Tree k a)
moveToLeftmostChild z = moveTo ??? z

Thanks,
Sergey
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120108/372708a3/attachment.htm>


More information about the Haskell-Cafe mailing list