| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
Data.Forest
Description
Multi-way trees (also known as rose trees) and forests,
similar to Data.Tree from the containers library.
Synopsis
- 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
Instances
| Foldable Forest Source # | |
Defined in Data.Forest Methods fold :: Monoid m => Forest m -> m # foldMap :: Monoid m => (a -> m) -> Forest a -> m # foldMap' :: Monoid m => (a -> m) -> Forest a -> m # foldr :: (a -> b -> b) -> b -> Forest a -> b # foldr' :: (a -> b -> b) -> b -> Forest a -> b # foldl :: (b -> a -> b) -> b -> Forest a -> b # foldl' :: (b -> a -> b) -> b -> Forest a -> b # foldr1 :: (a -> a -> a) -> Forest a -> a # foldl1 :: (a -> a -> a) -> Forest a -> a # elem :: Eq a => a -> Forest a -> Bool # maximum :: Ord a => Forest a -> a # minimum :: Ord a => Forest a -> a # | |
| Traversable Forest Source # | |
| Functor Forest Source # | |
| Monoid (Forest a) Source # | |
| Semigroup (Forest a) Source # | |
| Show a => Show (Forest a) Source # | |
| Eq a => Eq (Forest a) Source # | |
Instances
| Foldable Tree Source # | |
Defined in Data.Forest Methods fold :: Monoid m => Tree m -> m # foldMap :: Monoid m => (a -> m) -> Tree a -> m # foldMap' :: Monoid m => (a -> m) -> Tree a -> m # foldr :: (a -> b -> b) -> b -> Tree a -> b # foldr' :: (a -> b -> b) -> b -> Tree a -> b # foldl :: (b -> a -> b) -> b -> Tree a -> b # foldl' :: (b -> a -> b) -> b -> Tree a -> b # foldr1 :: (a -> a -> a) -> Tree a -> a # foldl1 :: (a -> a -> a) -> Tree a -> a # elem :: Eq a => a -> Tree a -> Bool # maximum :: Ord a => Tree a -> a # | |
| Traversable Tree Source # | |
| Functor Tree Source # | |
| Show a => Show (Tree a) Source # | |
| Eq a => Eq (Tree a) Source # | |
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' _ -> [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"