[Haskell-cafe] RoseTree + Data.Typeable.Zipper
Sergey Mironov
ierton at gmail.com
Sun Jan 8 16:56:16 CET 2012
2012/1/8 Sergey Mironov <ierton at gmail.com>
> 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
>
Heh, look like I've found the solution by myself! Here is the missing part:
get_child n t = ((_rules t) !! n) -- fast'n'diry
set_child n c t = t{ _rules = (hs ++ (c:ts)) } where
(hs,ts) = splitAt n (_rules t)
focus_child :: Int -> Tree k a :-> (k, Tree k a)
focus_child n = lens (get_child n) (set_child n)
moveToLeftmostChild :: (Ord k, Typeable k, Typeable a)
=> Zipper (Tree k a) (Tree k a) -> Zipper (Tree k a) (k, Tree k a)
moveToLeftmostChild z = moveTo (focus_child 0) z
Thanks,
Sergey
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120108/92874ef5/attachment.htm>
More information about the Haskell-Cafe
mailing list