Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Forest
Description
Multi-way trees (also known as rose trees) and forests, similar to Data.Tree
from the popular containers library.
- data Forest a
- data Tree a
- forest :: [Tree a] -> Forest a
- tree :: a -> Forest a -> Tree a
- leaf :: a -> Tree a
- leaves :: [a] -> Forest a
- trees :: Forest a -> [Tree a]
- root :: Tree a -> a
- subforest :: Tree a -> Forest a
- subtrees :: Tree a -> [Tree a]
- foldForest :: ([(a, b)] -> b) -> Forest a -> b
- foldTree :: (a -> [b] -> b) -> Tree a -> b
Importing
Recommended imports:
import Data.Forest (Forest, Tree) import qualified Data.Forest as Forest
Types
Constructing
Deconstructing
Folds
foldForest :: ([(a, b)] -> b) -> Forest a -> b Source #
Catamorphism on forests.
>>>
:{ example :: Forest Char example = forest [ tree 'a' $ leaves "bc" , tree 'd' $ forest [ leaf 'e' , tree 'f' $ leaves "g" ] ] :}
>>>
foldForest (intercalate ", " . fmap (\(a, b) -> [a] <> " [" <> b <> "]")) example
"a [b [], c []], d [e [], f [g []]]"
foldTree :: (a -> [b] -> b) -> Tree a -> b Source #
Catamorphism on trees.
>>>
:{ example :: Tree Char example = tree 'a' $ forest [ tree 'b' $ leaves "cd" , tree 'e' $ forest [ leaf 'f' , tree 'g' $ leaves "h" ] ] :}
>>>
foldTree (\a bs -> [a] <> " [" <> intercalate ", " bs <> "]") example
"a [b [c [], d []], e [f [], g [h []]]]"
Forest functor
One notable difference of this Forest
from that of the containers library is
that this Forest
is a newtype rather than a type alias, and so it provides a
more appropriate Functor
instance:
>>>
:{ example :: Forest Char example = forest [ tree 'a' $ leaves "bc" , tree 'd' $ forest [ leaf 'e' , tree 'f' $ leaves "g" ] ] :}
>>>
:{ showCharForest f = intercalate ", " (showCharTree <$> trees f) where showCharTree t = case trees (subforest t) of [] -> [root t] [t'] -> [root t] <> ": " <> showCharTree t' ts -> [root t] <> ": (" <> showCharForest (subforest t) <> ")" :}
>>>
showCharForest example
"a: (b, c), d: (e, f: g)"
>>>
showCharForest (fmap toUpper example)
"A: (B, C), D: (E, F: G)"
Likewise, Forest'
s Foldable
instance folds over the elements of the forest.
>>>
toList example
"abcdefg"