ListTree-0.2.2: Trees and monadic trees expressed as monadic lists where the underlying monad is a list

Safe HaskellSafe-Inferred
LanguageHaskell98

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.Trans.List.Funcs (repeatM)
import Data.List.Class (genericTake, scanl, takeWhile, toList, lastL)
import Prelude hiding (scanl, takeWhile)

appendToEnd xs x = xs ++ [x]
bits = scanl appendToEnd [] (repeatM "01")

> 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"]

Synopsis

Documentation

class (List t, List (ItemM t)) => Tree t Source

A 'type-class synonym' for Trees.

Instances

(List t, List (ItemM t)) => Tree t 

type TreeT m a = ListT (ListT m) a Source

Search algorithms

dfs :: Tree t => t a -> ItemM t a Source

Iterate a tree in DFS pre-order. (Depth First Search)

bfs :: Tree t => t a -> ItemM t a Source

Iterate a tree in BFS order. (Breadth 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 a Source

Best First Search given a scoring function.

bestFirstSearchSortedChildrenOn :: (Ord b, Tree t) => (a -> b) -> t a -> ItemM t a Source

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.Class
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)]

sortChildrenOn :: (Ord b, Tree t) => (a -> b) -> t a -> ListT (ItemM t) a Source

Pruning methods

prune :: MonadPlus m => (a -> Bool) -> ListT m a -> ListT m a Source

Prune a tree or list given a predicate. Unlike takeWhile which stops a branch where the condition doesn't hold, prune "cuts" the whole branch (the underlying MonadPlus's mzero).

pruneM :: MonadPlus m => (a -> m Bool) -> ListT m a -> ListT m a Source

branchAndBound :: (Ord b, Tree t) => (a -> (Maybe b, Maybe b)) -> t a -> TreeT (StateT (Maybe b) (TreeItemM t)) a Source

Generalized "Branch and Bound". A method for pruning.

The result of this function would usually be given to another search algorithm, such as dfs, in order to find the node with lowest value.

This augments the regular search by pruning the tree. Given a function to calculate a lower and upper bound for a subtree, we keep the lowest upper bound (hence the State monad) encountered so far, and we prune any subtree whose lower bound is over the known upper bound.