binary-tree-0.1.0.0

Copyright(c) Donnacha Oisín Kidney 2018
LicenseMIT
Maintainermail@doisinkidney.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Tree.Binary.Preorder

Contents

Description

This module provides a simple preorder binary tree, as is needed in several applications. Instances, if sensible, are defined, and generally effort is made to keep the implementation as generic as possible.

Synopsis

The tree type

data Tree a Source #

A preorder binary tree.

Constructors

Leaf 
Node a (Tree a) (Tree a) 

Instances

Functor Tree Source # 

Methods

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

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

Applicative Tree Source # 

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 # 

Methods

fold :: Monoid m => Tree m -> 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 # 

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 # 

Methods

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

Ord1 Tree Source # 

Methods

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

Read1 Tree Source # 

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 # 

Methods

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

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

Alternative Tree Source # 

Methods

empty :: Tree a #

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

some :: Tree a -> Tree [a] #

many :: Tree a -> Tree [a] #

Eq a => Eq (Tree a) Source # 

Methods

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

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

Data a => Data (Tree a) Source # 

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 :: (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 # 

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 # 
Show a => Show (Tree a) Source # 

Methods

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

show :: Tree a -> String #

showList :: [Tree a] -> ShowS #

Generic (Tree a) Source # 

Associated Types

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

Methods

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

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

Semigroup (Tree a) Source # 

Methods

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

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

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

Monoid (Tree a) Source #

This instance is necessarily inefficient, to obey the monoid laws.

>>> printTree (fromList [1..6])
   ┌3
 ┌2┤
 │ └4
1┤
 │ ┌6
 └5┘
>>> printTree (fromList [1..6] `mappend` singleton 7)
   ┌3
 ┌2┤
 │ └4
1┤
 │ ┌6
 └5┤
   └7

mappend distributes over toList:

toList (mappend xs (ys :: Tree Int)) === mappend (toList xs) (toList ys)

Methods

mempty :: Tree a #

mappend :: Tree a -> Tree a -> Tree a #

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

NFData a => NFData (Tree a) Source # 

Methods

rnf :: Tree a -> () #

Generic1 * Tree Source # 

Associated Types

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

Methods

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

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

type Rep (Tree a) Source # 
type Rep1 * Tree Source # 

Construction

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

Unfold a tree from a seed.

replicate :: Int -> a -> Tree a Source #

replicate n a creates a tree of size n filled a.

>>> putStr (drawTree (replicate 4 ()))
     ┌()
  ┌()┘
()┤
  └()
\(NonNegative n) -> length (replicate n ()) === n

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

replicateA n a replicates the action a n times, trying to balance the result as much as possible. The actions are executed in a preorder traversal (same as the Foldable instance.)

>>> toList (evalState (replicateA 10 (State (\s -> (s, s + 1)))) 1)
[1,2,3,4,5,6,7,8,9,10]

singleton :: a -> Tree a Source #

A binary tree with one element.

empty :: Tree a Source #

A binary tree with no elements.

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

Construct a tree from a list, in an preorder fashion.

toList (fromList xs) === xs

Consumption

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

Fold over a tree.

foldTree Leaf Node xs === xs

Querying

depth :: Tree a -> Int Source #

The depth of the tree.

>>> depth empty
0
>>> depth (singleton ())
1

Display

drawTree :: Show a => Tree a -> String Source #

Convert a tree to a human-readable structural representation.

>>> putStr (drawTree (fromList [1..7]))
   ┌3
 ┌2┤
 │ └4
1┤
 │ ┌6
 └5┤
   └7

drawTreeWith :: (a -> String) -> Tree a -> ShowS Source #

Pretty-print a tree with a custom show function.

>>> putStr (drawTreeWith (const "─") (fromList [1..7]) "")
   ┌─
 ┌─┤
 │ └─
─┤
 │ ┌─
 └─┤
   └─
>>> putStr (drawTreeWith id (singleton "abc") "")
abc
>>> putStr (drawTreeWith id (Node "abc" (singleton  "d") Leaf) "")
   ┌d
abc┘
>>> putStr (drawTreeWith id (fromList ["abc", "d", "ef", "ghij"]) "")
     ┌ef
   ┌d┘
abc┤
   └ghij

printTree :: Show a => Tree a -> IO () Source #

Pretty-print a tree.

>>> printTree (fromList [1..7])
   ┌3
 ┌2┤
 │ └4
1┤
 │ ┌6
 └5┤
   └7
>>> printTree (singleton 1 `mappend` singleton 2)
1┐
 └2