Data.List.Tree
Description
Functions for iterating trees.
A List whose underlying monad is also a List is a tree.
It's nodes are accessible, in contrast to the list monad, which can also be seen as a tree, except only its leafs are accessible and only in dfs order.
import Control.Monad.Generator
import Data.List.Class (genericTake, takeWhile, toList, lastL)
bits = t ""
t prev =
generate $ do
yield prev
x <- lift "01"
yields $ t (prev ++ [x])
> take 3 (bfsLayers bits)
[[""],["0","1"],["00","01","10","11"]]
> take 10 (bfs bits)
["","0","1","00","01","10","11","000","001","010"]
> dfs (genericTake 4 bits)
["","0","00","000","001","01","010","011","1","10","100","101","11","110","111"]
> toList $ genericTake 3 bits
[["","0","00"],["","0","01"],["","1","10"],["","1","11"]]
Examples of pruning with prune and takeWhile:
> dfs . takeWhile (not . isSuffixOf "11") $ genericTake 4 bits ["","0","00","000","001","01","010","1","10","100","101"] > lastL . takeWhile (not . isSuffixOf "11") $ genericTake 4 bits ["000","001","010","01","100","101","1"] > lastL . prune (not . isSuffixOf "11") $ genericTake 4 bits ["000","001","010","100","101"]
- class (List l k, List k m) => Tree l k m
- dfs :: (List l m, MonadPlus m) => l a -> m a
- bfs :: Tree l k m => l a -> k a
- bfsLayers :: Tree l k m => l a -> k (k a)
- bestFirstSearchOn :: (Ord b, Tree l k m) => (a -> b) -> l a -> k a
- prune :: (List l m, MonadPlus m) => (a -> Bool) -> l a -> l a
- bestFirstSearchSortedChildrenOn :: (Ord b, Tree l k m) => (a -> b) -> l a -> k a
Documentation
dfs :: (List l m, MonadPlus m) => l a -> m aSource
Iterate a tree in DFS pre-order. (Depth First Search)
bfsLayers :: Tree l k m => l a -> k (k a)Source
Transform a tree into lists of the items in its different layers
bestFirstSearchOn :: (Ord b, Tree l k m) => (a -> b) -> l a -> k aSource
Best First Search given a scoring function.
bestFirstSearchSortedChildrenOn :: (Ord b, Tree l k m) => (a -> b) -> l a -> k aSource
Best-First-Search given that a node's children are in sorted order (best first) and given a scoring function.
Especially useful for trees where nodes have an infinite amount of children, where bestFirstSearchOn will get stuck.