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 t, List (ItemM t)) => Tree t
- dfs :: (List l, MonadPlus (ItemM l)) => l a -> ItemM l a
- bfs :: Tree t => t a -> ItemM t a
- bfsLayers :: Tree t => t a -> ItemM t (ItemM t a)
- bestFirstSearchOn :: (Ord b, Tree t) => (a -> b) -> t a -> ItemM t a
- prune :: (List l, MonadPlus (ItemM l)) => (a -> Bool) -> l a -> l a
- bestFirstSearchSortedChildrenOn :: (Ord b, Tree t) => (a -> b) -> t a -> ItemM t a
Documentation
dfs :: (List l, MonadPlus (ItemM l)) => l a -> ItemM l aSource
Iterate a tree in DFS pre-order. (Depth First Search)
bfsLayers :: Tree t => t a -> ItemM t (ItemM t a)Source
Transform a tree into lists of the items in its different layers
bestFirstSearchOn :: (Ord b, Tree t) => (a -> b) -> t a -> ItemM t aSource
Best First Search given a scoring function.
bestFirstSearchSortedChildrenOn :: (Ord b, Tree t) => (a -> b) -> t a -> ItemM t 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.
Example: Find smallest Pythagorian Triplets
import Control.Monad
import Control.Monad.Generator
import Control.Monad.Trans
import Data.List.Tree
import Data.Maybe
pythagorianTriplets =
catMaybes .
fmap fst .
bestFirstSearchSortedChildrenOn snd .
generate $ do
x <- lift [1..]
yield (Nothing, x)
y <- lift [1..]
yield (Nothing, x + y)
z <- lift [1..]
yield (Nothing, x + y + z)
lift . guard $ x^2 + y^2 == z^2
yield (Just (x, y, z), 0)
> print $ take 10 pythagorianTriplets
[(3,4,5),(4,3,5),(6,8,10),(8,6,10),(5,12,13),(12,5,13),(9,12,15),(12,9,15),(15,8,17),(8,15,17)]