type-indexed-queues-0.1.0.0: Queues with verified and unverified versions.

Safe HaskellSafe
LanguageHaskell2010

Data.BinaryTree

Description

A simple, generic binary tree and some operations. Used in some of the heaps.

Synopsis

Documentation

data Tree a Source #

A simple binary tree for use in some of the heaps.

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 #

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

Generic1 Tree Source # 

Associated Types

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

Methods

from1 :: Tree a -> Rep1 Tree a #

to1 :: Rep1 Tree a -> 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] #

Show1 Tree Source # 

Methods

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

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

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 #

Monoid (Tree a) Source # 

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

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

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

Fold over a tree.

isHeap :: Ord a => Tree a -> Bool Source #

Check to see if this tree maintains the heap property.

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

Unfold a tree from a seed.

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

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

>>> replicateTree 4 ()
Node () (Node () (Node () Leaf Leaf) Leaf) (Node () Leaf Leaf)
n >= 0 ==> length (replicateTree n x) == n

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

replicateA n a replicates the action a n times.

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

Construct a tree from a list, putting each even-positioned element to the left.

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

A zygomorphism over a tree. Used if you want perform two folds over a tree in one pass.

As an example, checking if a tree is balanced can be performed like this using explicit recursion:

isBalanced :: Tree a -> Bool
isBalanced Leaf = True
isBalanced (Node _ l r)
  = length l == length r && isBalanced l && isBalanced r

However, this algorithm performs several extra passes over the tree. A more efficient version is much harder to read, however:

isBalanced :: Tree a -> Bool
isBalanced = snd . go where
  go Leaf = (0 :: Int,True)
  go (Node _ l r) =
      let (llen,lbal) = go l
          (rlen,rbal) = go r
      in (llen + rlen + 1, llen == rlen && lbal && rbal)

This same algorithm (the one pass version) can be expressed as a zygomorphism:

isBalanced :: Tree a -> Bool
isBalanced =
    zygoTree
        (0 :: Int)
        (\_ x y -> 1 + x + y)
        True
        go
  where
    go _ llen lbal rlen rbal = llen == rlen && lbal && rbal

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

Pretty-print a tree.