Tree Construction

Hi, Often I need to assemble a tree from things with unstructured hierarchical paths. I built a function [1] to do this for ImProve. But does a library already exist that does this? If not I may create one, as I need it for a few different libraries. data Tree a b = Branch a [Tree a b] | Leaf a b tree :: (Eq a, Ord a) => (b -> [a]) -> [b] -> [Tree a b] Note, type 'a' is some sort of label, most often a string, and type 'b' form the leaves of the tree. The function passed into 'tree' returns the hierarchical path of a leaf object. -Tom [1] http://hackage.haskell.org/packages/archive/improve/0.0.12/doc/html/Language...

Hi, I think what you need is a trie. See f.e. http://hackage.haskell.org/package/list-tries On Sep 25, 2010, at 11:54 AM, Tom Hawkins wrote:
Hi,
Often I need to assemble a tree from things with unstructured hierarchical paths. I built a function [1] to do this for ImProve. But does a library already exist that does this? If not I may create one, as I need it for a few different libraries.
data Tree a b = Branch a [Tree a b] | Leaf a b
tree :: (Eq a, Ord a) => (b -> [a]) -> [b] -> [Tree a b]
Note, type 'a' is some sort of label, most often a string, and type 'b' form the leaves of the tree. The function passed into 'tree' returns the hierarchical path of a leaf object.
-Tom
[1] http://hackage.haskell.org/packages/archive/improve/0.0.12/doc/html/Language... _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Sjoerd Visscher http://w3future.com

Am 25.09.2010 um 11:54 schrieb Tom Hawkins:
Hi,
Often I need to assemble a tree from things with unstructured hierarchical paths. I built a function [1] to do this for ImProve. But does a library already exist that does this? If not I may create one, as I need it for a few different libraries.
data Tree a b = Branch a [Tree a b] | Leaf a b
tree :: (Eq a, Ord a) => (b -> [a]) -> [b] -> [Tree a b]
Note, type 'a' is some sort of label, most often a string, and type 'b' form the leaves of the tree. The function passed into 'tree' returns the hierarchical path of a leaf object.
-Tom
[1] http://hackage.haskell.org/packages/archive/improve/0.0.12/doc/html/Language...
As Sjoerd Visscher has pointed out, this data structure is called trie. Here is a version of your module that allows for empty paths, uses sets instead of lists and stores values and subtrees separately: module Language.ImProve.Tree ( Tree (..), tree) where import qualified Data.Map as Map import Data.Monoid data Tree a b = Tree [b] (Map.Map a (Tree a b)) instance Ord a => Monoid (Tree a b) where mempty = Tree [] Map.empty mappend (Tree vs1 sts1) (Tree vs2 sts2) = Tree (vs1 ++ vs2) (Map.unionWith mappend sts1 sts2) tree :: Ord a => (b -> [a]) -> [b] -> Tree a b tree path leaves = mconcat [ foldr branch (leaf l) (path l) | l <- leaves ] where leaf a = Tree [a] Map.empty branch b t = Tree [] (Map.singleton b t)
participants (3)
-
Holger Siegel
-
Sjoerd Visscher
-
Tom Hawkins