
Hello All, Both CFP and SOE have chapters on trees and there is a standard library Data.Tree. I expected to find all kinds of functions there, as in Data.List, but instead the functions are defined as instances of more general structures. It uses: import Control.Applicative (Applicative(..), (<$>)) import Control.Monad import Data.Monoid (Monoid(..)) import Data.Sequence (Seq, empty, singleton, (<|), (|>), fromList, ViewL(..), ViewR(..), viewl, viewr) import Data.Foldable (Foldable(foldMap), toList) import Data.Traversable (Traversable(traverse)) import Data.Typeable When looking at those it is not clear (to me) what those all mean and I have not been able to find much on the WiKi either. Could someone with more experience provide some guidance on how to learn to use these libraries (and ultimately on the tree type in Data.Tree, which is what I want). There is a Zipper Monad with defined functions, which look promising, but I have not heard of this before, and it appears not to be standard. http://www.haskell.org/haskellwiki/Zipper_monad/TravelBTree http://www.haskell.org/haskellwiki/Zipper_monad Does anybody have any experience with these libraries they could share? Ideally I would want a N-ary tree, where the branches are what's actually the represented data, and so I would like to access it both from the root and the leaves. In an imperative language I would just add an up-pointer in each node, but I have no idea how expensive this would be in Haskell, or if it's necessary at all. Many thanks for your help, Hans van Thiel

Hans van Thiel wrote:
Both CFP and SOE have chapters on trees and there is a standard library Data.Tree. I expected to find all kinds of functions there, as in Data.List, but instead the functions are defined as instances of more general structures.
Well, Data.Tree is not much in use since one almost always needs some special kind of tree and because it's so easy to roll your own.
import Control.Applicative (Applicative(..), (<$>)) import Data.Foldable (Foldable(foldMap), toList) import Data.Traversable (Traversable(traverse))
The papers mentioned on the haddock for Data.Traversable are good start. Basically, these concepts are a generalization of the good old "fold" from lists to arbitrary trees (=> Foldable) and from pure functions to general computations (=> Applicative Functors, Traversable).
There is a Zipper
http://en.wikibooks.org/wiki/Haskell/Zippers
Ideally I would want a N-ary tree, where the branches are what's actually the represented data, and so I would like to access it both from the root and the leaves. In an imperative language I would just add an up-pointer in each node, but I have no idea how expensive this would be in Haskell, or if it's necessary at all.
Up-pointers won't work in Haskell, you'll need a different approach. Can you elaborate on what your tree looks like and what it stores? Regards, apfelmus

apfelmus wrote:
Up-pointers won't work in Haskell, you'll need a different approach. Can you elaborate on what your tree looks like and what it stores?
"pointers" don't exist in Haskell, though they do exist in the Foreign.* interface package. But Up-values work just fine:
import Data.Tree
-- Build a tree of divisors: tree :: Tree String tree = unfoldTree f 12 -- example where f 1 = (show 1,[]) f n = (show n,[ x | x <- [1..n `div` 2], n `mod` x == 0])
-- One possible design, using Maybe: data UpTree a = UpTree { value :: a , parent :: Maybe (UpTree a) , children :: [UpTree a] }
-- Convert a Tree to an UpTree treeToUpTree t = helper Nothing t where helper p t = let p' = UpTree { value = rootLabel t , parent = p , children = map (helper (Just p')) (subForest t) } in p'
upTree :: UpTree String upTree = treeToUpTree tree -- example
-- Pretty print this example UpTree with careful access to parent:
instance Show a => Show (UpTree a) where show u@(UpTree {parent=Nothing}) = "ROOT_UpTree "++show (value u)++"\n" ++(indent 3 $ show (children u)) show u@(UpTree {parent=Just p,children=[]}) = "UpTree "++show (value u)++"\n" ++" parent value is "++show (value p)++"\n" show u@(UpTree {parent=Just p}) = "UpTree "++show (value u)++"\n" ++" parent value is "++show (value p)++"\n" ++(indent 3 $ show (children u))
indent n x = let xs = lines x in if null xs then "" else unlines $ map (replicate n ' ' ++) xs
main = print upTree
Gives: ROOT_UpTree "12" [LEAF UpTree "1" parent value is "12" ,BRANCH UpTree "2" parent value is "12" [LEAF UpTree "1" parent value is "2" ] ,BRANCH UpTree "3" parent value is "12" [LEAF UpTree "1" parent value is "3" ] ,BRANCH UpTree "4" parent value is "12" [LEAF UpTree "1" parent value is "4" ,BRANCH UpTree "2" parent value is "4" [LEAF UpTree "1" parent value is "2" ] ] ,BRANCH UpTree "6" parent value is "12" [LEAF UpTree "1" parent value is "6" ,BRANCH UpTree "2" parent value is "6" [LEAF UpTree "1" parent value is "2" ] ,BRANCH UpTree "3" parent value is "6" [LEAF UpTree "1" parent value is "3" ] ] ]

I pasted the wrong show code. Here is the version I actually ran:
instance Show a => Show (UpTree a) where show u@(UpTree {parent=Nothing}) = "ROOT_UpTree "++show (value u)++"\n" ++(indent 3 $ show (children u)) show u@(UpTree {parent=Just p,children=[]}) = "LEAF UpTree "++show (value u)++"\n" ++" parent value is "++show (value p)++"\n" show u@(UpTree {parent=Just p}) = "BRANCH UpTree "++show (value u)++"\n" ++" parent value is "++show (value p)++"\n" ++(indent 3 $ show (children u))

[snip] Thanks, Apfelmus, for the references. Guess I'll start there, then. And thanks, Chris, for the info and code. Read only 'up pointers' could be what is needed. But before going on, I want first to get more confortable with programming with trees. It's all very well to say they're easy to roll, but lists are even simpler, and look at them... Regards, Hans

On 27 jun 2007, at 18.41, Hans van Thiel wrote:
[snip]
Thanks, Apfelmus, for the references. Guess I'll start there, then. And thanks, Chris, for the info and code. Read only 'up pointers' could be what is needed. But before going on, I want first to get more confortable with programming with trees. It's all very well to say they're easy to roll, but lists are even simpler, and look at them...
I guess it's in the papers, too, but the chapter on zippers in the Wikibook is very nice, too: http://en.wikibooks.org/wiki/Haskell/Zippers / Thomas

On Fri, 2007-06-29 at 19:35 +0200, Thomas Schilling wrote:
On 27 jun 2007, at 18.41, Hans van Thiel wrote:
[snip]
Thanks, Apfelmus, for the references. Guess I'll start there, then. And thanks, Chris, for the info and code. Read only 'up pointers' could be what is needed. But before going on, I want first to get more confortable with programming with trees. It's all very well to say they're easy to roll, but lists are even simpler, and look at them...
I guess it's in the papers, too, but the chapter on zippers in the Wikibook is very nice, too:
http://en.wikibooks.org/wiki/Haskell/Zippers
/ Thomas Yes, I've seen this. Thanks! Regards, Hans

Chris Kuklewicz wrote:
apfelmus wrote:
Up-pointers won't work in Haskell, you'll need a different approach. Can you elaborate on what your tree looks like and what it stores?
"pointers" don't exist in Haskell, though they do exist in the Foreign.* interface package.
But Up-values work just fine:
Well, not really: they're read-only. To "update" a single Branch/Leaf in the presence of up-values/"pointers" requires to update the up-values of _every_ Branch/Leaf in the tree. Regards, apfelmus
participants (4)
-
apfelmus
-
Chris Kuklewicz
-
Hans van Thiel
-
Thomas Schilling