containers-0.6.5.1: Assorted concrete container types
Copyright(c) The University of Glasgow 2002
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Tree

Description

Multi-way Trees and Forests

The Tree a type represents a lazy, possibly infinite, multi-way tree (also known as a rose tree).

The Forest a type represents a forest of Tree as.

Synopsis

Trees and Forests

data Tree a Source #

Non-empty, possibly infinite, multi-way trees; also known as rose trees.

Constructors

Node 

Fields

Instances

Instances details
Monad Tree Source # 
Instance details

Defined in Data.Tree

Methods

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

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

return :: a -> Tree a #

Functor Tree Source # 
Instance details

Defined in Data.Tree

Methods

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

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

MonadFix Tree Source #

Since: 0.5.11

Instance details

Defined in Data.Tree

Methods

mfix :: (a -> Tree a) -> Tree a #

Applicative Tree Source # 
Instance details

Defined in Data.Tree

Methods

pure :: a -> Tree a #

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

liftA2 :: (a -> b -> c) -> Tree a -> Tree b -> Tree c #

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

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

Foldable Tree Source # 
Instance details

Defined in Data.Tree

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.Tree

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) #

Eq1 Tree Source #

Since: 0.5.9

Instance details

Defined in Data.Tree

Methods

liftEq :: (a -> b -> Bool) -> Tree a -> Tree b -> Bool #

Ord1 Tree Source #

Since: 0.5.9

Instance details

Defined in Data.Tree

Methods

liftCompare :: (a -> b -> Ordering) -> Tree a -> Tree b -> Ordering #

Read1 Tree Source #

Since: 0.5.9

Instance details

Defined in Data.Tree

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Tree a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Tree a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Tree a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Tree a] #

Show1 Tree Source #

Since: 0.5.9

Instance details

Defined in Data.Tree

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Tree a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Tree a] -> ShowS #

MonadZip Tree Source # 
Instance details

Defined in Data.Tree

Methods

mzip :: Tree a -> Tree b -> Tree (a, b) #

mzipWith :: (a -> b -> c) -> Tree a -> Tree b -> Tree c #

munzip :: Tree (a, b) -> (Tree a, Tree b) #

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

Defined in Data.Tree

Methods

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

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

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

Defined in Data.Tree

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tree a -> c (Tree a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tree a) #

toConstr :: Tree a -> Constr #

dataTypeOf :: Tree a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Tree a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tree a)) #

gmapT :: (forall b. Data b => b -> b) -> Tree a -> Tree a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tree a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tree a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tree a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tree a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) #

Ord a => Ord (Tree a) Source #

Since: 0.6.5

Instance details

Defined in Data.Tree

Methods

compare :: Tree a -> Tree a -> Ordering #

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

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

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

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

max :: Tree a -> Tree a -> Tree a #

min :: Tree a -> Tree a -> Tree a #

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

Defined in Data.Tree

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

Defined in Data.Tree

Methods

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

show :: Tree a -> String #

showList :: [Tree a] -> ShowS #

Generic (Tree a) Source #

Since: 0.5.8

Instance details

Defined in Data.Tree

Associated Types

type Rep (Tree a) :: Type -> Type #

Methods

from :: Tree a -> Rep (Tree a) x #

to :: Rep (Tree a) x -> Tree a #

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

Defined in Data.Tree

Methods

rnf :: Tree a -> () #

Generic1 Tree Source #

Since: 0.5.8

Instance details

Defined in Data.Tree

Associated Types

type Rep1 Tree :: k -> Type #

Methods

from1 :: forall (a :: k). Tree a -> Rep1 Tree a #

to1 :: forall (a :: k). Rep1 Tree a -> Tree a #

type Rep (Tree a) Source # 
Instance details

Defined in Data.Tree

type Rep (Tree a) = D1 ('MetaData "Tree" "Data.Tree" "containers-0.6.5.1-DtpF2niqxyY5fgKWwj67yi" 'False) (C1 ('MetaCons "Node" 'PrefixI 'True) (S1 ('MetaSel ('Just "rootLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "subForest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tree a])))
type Rep1 Tree Source # 
Instance details

Defined in Data.Tree

type Rep1 Tree = D1 ('MetaData "Tree" "Data.Tree" "containers-0.6.5.1-DtpF2niqxyY5fgKWwj67yi" 'False) (C1 ('MetaCons "Node" 'PrefixI 'True) (S1 ('MetaSel ('Just "rootLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "subForest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 Tree)))

type Forest a = [Tree a] Source #

This type synonym exists primarily for historical reasons.

Construction

unfoldTree :: (b -> (a, [b])) -> b -> Tree a Source #

Build a (possibly infinite) tree from a seed value in breadth-first order.

unfoldTree f b constructs a tree by starting with the tree Node { rootLabel=b, subForest=[] } and repeatedly applying f to each rootLabel value in the tree's leaves to generate its subForest.

For a monadic version see unfoldTreeM_BF.

Examples

Expand

Construct the tree of Integers where each node has two children: left = 2*x and right = 2*x + 1, where x is the rootLabel of the node. Stop when the values exceed 7.

let buildNode x = if 2*x + 1 > 7 then (x, []) else (x, [2*x, 2*x+1])
putStr $ drawTree $ fmap show $ unfoldTree buildNode 1
1
|
+- 2
|  |
|  +- 4
|  |
|  `- 5
|
`- 3
   |
   +- 6
   |
   `- 7

unfoldForest :: (b -> (a, [b])) -> [b] -> [Tree a] Source #

Build a (possibly infinite) forest from a list of seed values in breadth-first order.

unfoldForest f seeds invokes unfoldTree on each seed value.

For a monadic version see unfoldForestM_BF.

unfoldTreeM :: Monad m => (b -> m (a, [b])) -> b -> m (Tree a) Source #

Monadic tree builder, in depth-first order.

unfoldForestM :: Monad m => (b -> m (a, [b])) -> [b] -> m [Tree a] Source #

Monadic forest builder, in depth-first order

unfoldTreeM_BF :: Monad m => (b -> m (a, [b])) -> b -> m (Tree a) Source #

Monadic tree builder, in breadth-first order.

See unfoldTree for more info.

Implemented using an algorithm adapted from /Breadth-First Numbering: Lessons from a Small Exercise in Algorithm Design, by Chris Okasaki, ICFP'00/.

unfoldForestM_BF :: Monad m => (b -> m (a, [b])) -> [b] -> m [Tree a] Source #

Monadic forest builder, in breadth-first order

See unfoldForest for more info.

Implemented using an algorithm adapted from /Breadth-First Numbering: Lessons from a Small Exercise in Algorithm Design, by Chris Okasaki, ICFP'00/.

Elimination

foldTree :: (a -> [b] -> b) -> Tree a -> b Source #

Fold a tree into a "summary" value in depth-first order.

For each node in the tree, apply f to the rootLabel and the result of applying f to each subForest.

This is also known as the catamorphism on trees.

Examples

Expand

Sum the values in a tree:

foldTree (\x xs -> sum (x:xs)) (Node 1 [Node 2 [], Node 3 []]) == 6

Find the maximum value in the tree:

foldTree (\x xs -> maximum (x:xs)) (Node 1 [Node 2 [], Node 3 []]) == 3

Count the number of leaves in the tree:

foldTree (\_ xs -> if null xs then 1 else sum xs) (Node 1 [Node 2 [], Node 3 []]) == 2

Find depth of the tree; i.e. the number of branches from the root of the tree to the furthest leaf:

foldTree (\_ xs -> if null xs then 0 else 1 + maximum xs) (Node 1 [Node 2 [], Node 3 []]) == 1

You can even implement traverse using foldTree:

traverse' f = foldTree (\x xs -> liftA2 Node (f x) (sequenceA xs))

Since: 0.5.8

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

Returns the elements of a tree in pre-order.

  a
 / \    => [a,b,c]
b   c

Examples

Expand
flatten (Node 1 [Node 2 [], Node 3 []]) == [1,2,3]

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

Returns the list of nodes at each level of the tree.

  a
 / \    => [[a], [b,c]]
b   c

Examples

Expand
levels (Node 1 [Node 2 [], Node 3 []]) == [[1],[2,3]]

Ascii Drawings

drawTree :: Tree String -> String Source #

2-dimensional ASCII drawing of a tree.

Examples

Expand
putStr $ drawTree $ fmap show (Node 1 [Node 2 [], Node 3 []])
1
|
+- 2
|
`- 3

drawForest :: [Tree String] -> String Source #

2-dimensional ASCII drawing of a forest.

Examples

Expand
putStr $ drawForest $ map (fmap show) [(Node 1 [Node 2 [], Node 3 []]), (Node 10 [Node 20 []])]
1
|
+- 2
|
`- 3

10
|
`- 20