data-forest-0.1.0.9: A simple multi-way tree data structure.
Safe HaskellNone
LanguageHaskell2010

Data.Forest

Description

Multi-way trees (also known as rose trees) and forests, similar to Data.Tree from the popular containers library.

Synopsis

Importing

Recommended imports:

import Data.Forest (Forest, Tree)
import qualified Data.Forest as Forest

Types

data Forest a Source #

A forest is defined completely by its trees.

To construct a forest, use forest or leaves.

Instances

Instances details
Functor Forest Source # 
Instance details

Defined in Data.Forest

Methods

fmap :: (a -> b) -> Forest a -> Forest b #

(<$) :: a -> Forest b -> Forest a #

Foldable Forest Source # 
Instance details

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 #

toList :: Forest a -> [a] #

null :: Forest a -> Bool #

length :: Forest a -> Int #

elem :: Eq a => a -> Forest a -> Bool #

maximum :: Ord a => Forest a -> a #

minimum :: Ord a => Forest a -> a #

sum :: Num a => Forest a -> a #

product :: Num a => Forest a -> a #

Traversable Forest Source # 
Instance details

Defined in Data.Forest

Methods

traverse :: Applicative f => (a -> f b) -> Forest a -> f (Forest b) #

sequenceA :: Applicative f => Forest (f a) -> f (Forest a) #

mapM :: Monad m => (a -> m b) -> Forest a -> m (Forest b) #

sequence :: Monad m => Forest (m a) -> m (Forest a) #

Eq a => Eq (Forest a) Source # 
Instance details

Defined in Data.Forest

Methods

(==) :: Forest a -> Forest a -> Bool #

(/=) :: Forest a -> Forest a -> Bool #

Show a => Show (Forest a) Source # 
Instance details

Defined in Data.Forest

Methods

showsPrec :: Int -> Forest a -> ShowS #

show :: Forest a -> String #

showList :: [Forest a] -> ShowS #

Semigroup (Forest a) Source # 
Instance details

Defined in Data.Forest

Methods

(<>) :: Forest a -> Forest a -> Forest a #

sconcat :: NonEmpty (Forest a) -> Forest a #

stimes :: Integral b => b -> Forest a -> Forest a #

Monoid (Forest a) Source # 
Instance details

Defined in Data.Forest

Methods

mempty :: Forest a #

mappend :: Forest a -> Forest a -> Forest a #

mconcat :: [Forest a] -> Forest a #

data Tree a Source #

A tree is defined completely by its root and its subforest.

To construct a tree, use tree or leaf.

Instances

Instances details
Functor Tree Source # 
Instance details

Defined in Data.Forest

Methods

fmap :: (a -> b) -> Tree a -> Tree b #

(<$) :: a -> Tree b -> Tree a #

Foldable Tree Source # 
Instance details

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 #

toList :: Tree a -> [a] #

null :: Tree a -> Bool #

length :: Tree a -> Int #

elem :: Eq a => a -> Tree a -> Bool #

maximum :: Ord a => Tree a -> a #

minimum :: Ord a => Tree a -> a #

sum :: Num a => Tree a -> a #

product :: Num a => Tree a -> a #

Traversable Tree Source # 
Instance details

Defined in Data.Forest

Methods

traverse :: Applicative f => (a -> f b) -> Tree a -> f (Tree b) #

sequenceA :: Applicative f => Tree (f a) -> f (Tree a) #

mapM :: Monad m => (a -> m b) -> Tree a -> m (Tree b) #

sequence :: Monad m => Tree (m a) -> m (Tree a) #

Eq a => Eq (Tree a) Source # 
Instance details

Defined in Data.Forest

Methods

(==) :: Tree a -> Tree a -> Bool #

(/=) :: Tree a -> Tree a -> Bool #

Show a => Show (Tree a) Source # 
Instance details

Defined in Data.Forest

Methods

showsPrec :: Int -> Tree a -> ShowS #

show :: Tree a -> String #

showList :: [Tree a] -> ShowS #

Constructing

forest :: [Tree a] -> Forest a Source #

Construct a forest from a list of trees.

forest [] is equivalent to mempty.

tree :: a -> Forest a -> Tree a Source #

Construct a tree with a root and subforest.

leaf :: a -> Tree a Source #

Construct a tree with a single root and no subforest.

leaf x is equivalent to tree x mempty.

leaves :: [a] -> Forest a Source #

Construct a forest of depth 1, where each tree contains only a root.

leaves is equivalent to forest . fmap leaf

Deconstructing

trees :: Forest a -> [Tree a] Source #

The trees that constitute the forest.

root :: Tree a -> a Source #

The value at the root node of the tree.

subforest :: Tree a -> Forest a Source #

The forest containing all descendants of the tree's root.

subtrees :: Tree a -> [Tree a] Source #

The tree's immediate subtrees.

subtrees is equivalent to trees . subforest.

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"