Proposal: improve the Data.Tree API

Yitzchak Gale gale at sefer.org
Sun Dec 28 20:58:14 UTC 2014


João Cristóvão wrote in February 2014:
> The Data.Tree API seems rather poor...
> I propose the addition of the following functions, that seem rather straigh forward to me...
> Discussion period: 2 weeks

Umm. A bit more than 2 weeks has passed since last February.
Can we add these yet?

There was a strong consensus to enrich Data.Tree
in the way proposed by João.
There was a bit of discussion about naming -
constructive discussion, not bikeshedding at all,
really.

When the thread ended, we had João's "version 3.0 b"
of his proposal, which is the functions in "version 3.0 a"
(repeated below to jog your memory), but re-organized
into separate modules for Tree and Forest according to
Henning's plan (also repeated below), with all functions
appearing in both of the modules as appropriate, and
the epithets "Tree" and "Forest" removed from the
function names themselves.

Based on the discussion then, I recommend that we add
to the haddock comments a note that some of the
functions are simple uses of the Comonad instance for
Tree, and several more variations can easily be built
using the duplicate and extend functions from the
comonad library.

Can we please add this to the containers library now?

Thanks,
Yitz

Henning's plan for the module organization:

> Data.Tree.Private exports Tree, but the module is hidden
> Data.Tree.Forest imports Tree, exports Forest, module is exposed
> Data.Tree imports Tree and Forest, exports Tree, module is exposed

João's proposal "version 3.0 a":

(Ord instance for Tree)

-- | get the sub-tree rooted at the first (left-most, depth-first) occurrence
-- of the specified node value
lookupTree :: Eq a => a -> Tree a -> Maybe (Tree a)

-- | get the sub-tree rooted at the first (left-most, depth-first) value that
-- matches the provided condition
lookupTreeBy :: (a -> Bool) -> Tree a -> Maybe (Tree a)

-- | get the sub-tree for the specified node value in the first tree in
-- forest in which it occurs.
lookupTreeInForest :: Eq a => a -> [Tree a] -> Maybe (Tree a)

-- | get the sub-tree for the specified node value in the first tree in
-- forest in which it occurs.
lookupTreeInForestBy :: (a -> Bool) -> [Tree a] -> Maybe (Tree a)

-- | Size of the (flattened) tree
size :: Tree a -> Int
size = getSum . F.foldMap (const $ Sum 1)

-- | Maximum depth of tree
maxDepth :: Tree a -> Int

-- | Remove all nodes past a certain depth
prune :: Int -> Tree a -> Tree a

-- | Take the mirror-image of a tree
mirror :: Tree a -> Tree a
mirror (Node a ts) = Node a . reverse $ map mirror ts

-- | List of subtrees (including the tree itself), in pre-order.
subTrees :: Tree a -> [Tree a]

-- | List of subtrees at each level of the tree.
subTreesByLevel :: Tree a -> [[Tree a]]

-- | Label each node of the tree with its full subtree.
cojoin :: :: Tree a -> Tree (Tree a)
cojoin t@(Node _ ts) = Node t (map cojoin ts)

-- | Prune every subtree whose root label does not match.
filterPruneTree :: (a -> Bool) -> Tree a -> Maybe (Tree a)
filterPruneTree p (Node x ns)
  | p x = Just . Node x $ filterPruneForest p ns
  | otherwise = Nothing

filterPruneForest :: (a -> Bool) -> Forest a -> Forest a
filterPruneForest = mapMaybe . filterPruneTree

-- | Remove nodes that do not match, and graft the children of the
removed node onto the tree in place of the parent.
filterGraftTree :: (a -> Bool) -> Tree a -> Forest a
filterGraftTree p (Node x ns)
  | p x = [Node x $ filterGraftForest p ns]
  | otherwise = filterGraftForest p ns

filterGraftForest :: (a -> Bool) -> Forest a -> Forest a
filterGraftForest = concatMap . filterGraftTree


More information about the Libraries mailing list