containers-0.5.10.2: 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
LanguageHaskell98

Data.Tree

Contents

Description

Multi-way trees (aka rose trees) and forests.

Synopsis

Documentation

data Tree a Source #

Multi-way trees, also known as rose trees.

Constructors

Node 

Fields

Instances

Monad Tree # 

Methods

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

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

return :: a -> Tree a Source #

fail :: String -> Tree a Source #

Functor Tree # 

Methods

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

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

Applicative Tree # 

Methods

pure :: a -> Tree a Source #

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

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

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

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

Foldable Tree # 

Methods

fold :: Monoid m => Tree m -> m Source #

foldMap :: Monoid m => (a -> m) -> Tree a -> m Source #

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

foldr' :: (a -> b -> b) -> b -> Tree a -> b Source #

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

foldl' :: (b -> a -> b) -> b -> Tree a -> b Source #

foldr1 :: (a -> a -> a) -> Tree a -> a Source #

foldl1 :: (a -> a -> a) -> Tree a -> a Source #

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

null :: Tree a -> Bool Source #

length :: Tree a -> Int Source #

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

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

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

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

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

Traversable Tree # 

Methods

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

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

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

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

Eq1 Tree # 

Methods

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

Ord1 Tree # 

Methods

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

Read1 Tree # 

Methods

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

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

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

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

Show1 Tree # 

Methods

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

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

MonadZip Tree # 

Methods

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

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

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

Eq a => Eq (Tree a) # 

Methods

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

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

Data a => Data (Tree a) # 

Methods

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

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

toConstr :: Tree a -> Constr Source #

dataTypeOf :: Tree a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Read a => Read (Tree a) # 
Show a => Show (Tree a) # 

Methods

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

show :: Tree a -> String Source #

showList :: [Tree a] -> ShowS Source #

Generic (Tree a) # 

Associated Types

type Rep (Tree a) :: * -> * Source #

Methods

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

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

NFData a => NFData (Tree a) # 

Methods

rnf :: Tree a -> () Source #

Generic1 * Tree # 

Associated Types

type Rep1 Tree (f :: Tree -> *) :: k -> * Source #

Methods

from1 :: f a -> Rep1 Tree f a Source #

to1 :: Rep1 Tree f a -> f a Source #

type Rep (Tree a) # 
type Rep (Tree a) = D1 * (MetaData "Tree" "Data.Tree" "containers-0.5.10.2" False) (C1 * (MetaCons "Node" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "rootLabel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "subForest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Forest a)))))
type Rep1 * Tree # 
type Rep1 * Tree = D1 * (MetaData "Tree" "Data.Tree" "containers-0.5.10.2" False) (C1 * (MetaCons "Node" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "rootLabel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1) (S1 * (MetaSel (Just Symbol "subForest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ((:.:) * * [] (Rec1 * Tree)))))

type Forest a = [Tree a] Source #

Two-dimensional drawing

drawTree :: Tree String -> String Source #

Neat 2-dimensional drawing of a tree.

drawForest :: Forest String -> String Source #

Neat 2-dimensional drawing of a forest.

Extraction

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

The elements of a tree in pre-order.

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

Lists of nodes at each level of the tree.

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

Catamorphism on trees.

Building trees

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

Build a tree from a seed value

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

Build a forest from a list of seed values

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 (Forest 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, 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 (Forest a) Source #

Monadic forest builder, in breadth-first order, using an algorithm adapted from Breadth-First Numbering: Lessons from a Small Exercise in Algorithm Design, by Chris Okasaki, ICFP'00.