Hi again,
Sorry for the delay.
> I like lookupTree (being the one who suggested that)
Indeed :)
I'll include the new version of the proposal at end of the email.
Just some quick notes first:
> Why is filter now missing? That's the one I've needed the most.
It isn't. Me too. Its just in a different order regarding proposal v1. But:
> Note however, that there are two possible implementations
> of filtering for Trees and Forests. The type signature you
> provided doesn't match any of them, so I'm not sure exactly what
> you had in mind.
I agree! My proposal was actual identical to your filterPruneTree, where the first node was not actually analysed, but always kept. I agree that this is not the best approach, so yours seem fine (and I've included them). I do however raise the question: could one of them be 'promoted' to a simpler just 'filter' name?
> I think it's just that people missed the fact that we already
> have these functions via the Comonad instance.
Indeed, that is my case, and I can only guess, many others.
Please take the following opinion as one of a beginner, not as criticism, which it isn't:
So, my opinion on this is that since comonads are not included in the haskell platform (for now), we should provide a more complete api. On the other hand, if the comonads are indeed a better aproach, then provide a link to comonads and _good dead simple examples on usage_. Right now I look at the comonad api and cannot see how to use it on trees. I guess I don't understand the utility of cojoin. My limitation, I'm sure...
Consider proposal 3.0.b Milan's idea of splitting forest functions to a different submodule. Milan, could you please elaborate on that? I didn't quite get how they would have the same name...
(My) Proposal 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