hgeometry-combinatorial-0.12.0.1: Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.BinaryTree

Description

Several types of Binary trees.

Synopsis

Documentation

data BinLeafTree v a Source #

Binary tree that stores its values (of type a) in the leaves. Internal nodes store something of type v.

Constructors

Leaf !a 
Node (BinLeafTree v a) !v (BinLeafTree v a) 

Instances

Instances details
Bifunctor BinLeafTree Source # 
Instance details

Defined in Data.BinaryTree

Methods

bimap :: (a -> b) -> (c -> d) -> BinLeafTree a c -> BinLeafTree b d #

first :: (a -> b) -> BinLeafTree a c -> BinLeafTree b c #

second :: (b -> c) -> BinLeafTree a b -> BinLeafTree a c #

Measured v a => Measured v (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

measure :: BinLeafTree v a -> v Source #

Functor (BinLeafTree v) Source # 
Instance details

Defined in Data.BinaryTree

Methods

fmap :: (a -> b) -> BinLeafTree v a -> BinLeafTree v b #

(<$) :: a -> BinLeafTree v b -> BinLeafTree v a #

Foldable (BinLeafTree v) Source # 
Instance details

Defined in Data.BinaryTree

Methods

fold :: Monoid m => BinLeafTree v m -> m #

foldMap :: Monoid m => (a -> m) -> BinLeafTree v a -> m #

foldMap' :: Monoid m => (a -> m) -> BinLeafTree v a -> m #

foldr :: (a -> b -> b) -> b -> BinLeafTree v a -> b #

foldr' :: (a -> b -> b) -> b -> BinLeafTree v a -> b #

foldl :: (b -> a -> b) -> b -> BinLeafTree v a -> b #

foldl' :: (b -> a -> b) -> b -> BinLeafTree v a -> b #

foldr1 :: (a -> a -> a) -> BinLeafTree v a -> a #

foldl1 :: (a -> a -> a) -> BinLeafTree v a -> a #

toList :: BinLeafTree v a -> [a] #

null :: BinLeafTree v a -> Bool #

length :: BinLeafTree v a -> Int #

elem :: Eq a => a -> BinLeafTree v a -> Bool #

maximum :: Ord a => BinLeafTree v a -> a #

minimum :: Ord a => BinLeafTree v a -> a #

sum :: Num a => BinLeafTree v a -> a #

product :: Num a => BinLeafTree v a -> a #

Traversable (BinLeafTree v) Source # 
Instance details

Defined in Data.BinaryTree

Methods

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

sequenceA :: Applicative f => BinLeafTree v (f a) -> f (BinLeafTree v a) #

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

sequence :: Monad m => BinLeafTree v (m a) -> m (BinLeafTree v a) #

Foldable1 (BinLeafTree v) Source # 
Instance details

Defined in Data.BinaryTree

Methods

fold1 :: Semigroup m => BinLeafTree v m -> m #

foldMap1 :: Semigroup m => (a -> m) -> BinLeafTree v a -> m #

toNonEmpty :: BinLeafTree v a -> NonEmpty a #

(Eq a, Eq v) => Eq (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

(==) :: BinLeafTree v a -> BinLeafTree v a -> Bool #

(/=) :: BinLeafTree v a -> BinLeafTree v a -> Bool #

(Ord a, Ord v) => Ord (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

compare :: BinLeafTree v a -> BinLeafTree v a -> Ordering #

(<) :: BinLeafTree v a -> BinLeafTree v a -> Bool #

(<=) :: BinLeafTree v a -> BinLeafTree v a -> Bool #

(>) :: BinLeafTree v a -> BinLeafTree v a -> Bool #

(>=) :: BinLeafTree v a -> BinLeafTree v a -> Bool #

max :: BinLeafTree v a -> BinLeafTree v a -> BinLeafTree v a #

min :: BinLeafTree v a -> BinLeafTree v a -> BinLeafTree v a #

(Read a, Read v) => Read (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

(Show a, Show v) => Show (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

showsPrec :: Int -> BinLeafTree v a -> ShowS #

show :: BinLeafTree v a -> String #

showList :: [BinLeafTree v a] -> ShowS #

Generic (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

Associated Types

type Rep (BinLeafTree v a) :: Type -> Type #

Methods

from :: BinLeafTree v a -> Rep (BinLeafTree v a) x #

to :: Rep (BinLeafTree v a) x -> BinLeafTree v a #

Measured v a => Semigroup (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

(<>) :: BinLeafTree v a -> BinLeafTree v a -> BinLeafTree v a #

sconcat :: NonEmpty (BinLeafTree v a) -> BinLeafTree v a #

stimes :: Integral b => b -> BinLeafTree v a -> BinLeafTree v a #

(Arbitrary a, Arbitrary v) => Arbitrary (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

arbitrary :: Gen (BinLeafTree v a) #

shrink :: BinLeafTree v a -> [BinLeafTree v a] #

(NFData v, NFData a) => NFData (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

Methods

rnf :: BinLeafTree v a -> () #

type Rep (BinLeafTree v a) Source # 
Instance details

Defined in Data.BinaryTree

node :: Measured v a => BinLeafTree v a -> BinLeafTree v a -> BinLeafTree v a Source #

smart constructor

asBalancedBinLeafTree :: NonEmpty a -> BinLeafTree Size (Elem a) Source #

Create a balanced tree, i.e. a tree of height \(O(\log n)\) with the elements in the leaves.

\(O(n)\) time.

foldUp :: (b -> v -> b -> b) -> (a -> b) -> BinLeafTree v a -> b Source #

Given a function to combine internal nodes into b's and leafs into b's, traverse the tree bottom up, and combine everything into one b.

foldUpData :: (w -> v -> w -> w) -> (a -> w) -> BinLeafTree v a -> BinLeafTree w a Source #

Traverses the tree bottom up, recomputing the assocated values.

zipExactWith :: (u -> v -> w) -> (a -> b -> c) -> BinLeafTree u a -> BinLeafTree v b -> BinLeafTree w c Source #

Takes two trees, that have the same structure, and uses the provided functions to "zip" them together

Converting into a Data.Tree

toRoseTree :: BinLeafTree v a -> Tree (TreeNode v a) Source #

\( O(n) \) Convert binary tree to a rose tree, aka Tree.

drawTree :: (Show v, Show a) => BinLeafTree v a -> String Source #

2-dimensional ASCII drawing of a tree.

Internal Node Tree

data BinaryTree a Source #

Binary tree in which we store the values of type a in internal nodes.

Constructors

Nil 
Internal (BinaryTree a) !a (BinaryTree a) 

Instances

Instances details
Functor BinaryTree Source # 
Instance details

Defined in Data.BinaryTree

Methods

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

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

Foldable BinaryTree Source # 
Instance details

Defined in Data.BinaryTree

Methods

fold :: Monoid m => BinaryTree m -> m #

foldMap :: Monoid m => (a -> m) -> BinaryTree a -> m #

foldMap' :: Monoid m => (a -> m) -> BinaryTree a -> m #

foldr :: (a -> b -> b) -> b -> BinaryTree a -> b #

foldr' :: (a -> b -> b) -> b -> BinaryTree a -> b #

foldl :: (b -> a -> b) -> b -> BinaryTree a -> b #

foldl' :: (b -> a -> b) -> b -> BinaryTree a -> b #

foldr1 :: (a -> a -> a) -> BinaryTree a -> a #

foldl1 :: (a -> a -> a) -> BinaryTree a -> a #

toList :: BinaryTree a -> [a] #

null :: BinaryTree a -> Bool #

length :: BinaryTree a -> Int #

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

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

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

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

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

Traversable BinaryTree Source # 
Instance details

Defined in Data.BinaryTree

Methods

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

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

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

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

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

Defined in Data.BinaryTree

Methods

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

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

Ord a => Ord (BinaryTree a) Source # 
Instance details

Defined in Data.BinaryTree

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

Defined in Data.BinaryTree

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

Defined in Data.BinaryTree

Generic (BinaryTree a) Source # 
Instance details

Defined in Data.BinaryTree

Associated Types

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

Methods

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

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

Arbitrary a => Arbitrary (BinaryTree a) Source # 
Instance details

Defined in Data.BinaryTree

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

Defined in Data.BinaryTree

Methods

rnf :: BinaryTree a -> () #

type Rep (BinaryTree a) Source # 
Instance details

Defined in Data.BinaryTree

type Rep (BinaryTree a) = D1 ('MetaData "BinaryTree" "Data.BinaryTree" "hgeometry-combinatorial-0.12.0.1-3UsM6nqO83QAAGVLl4vU5w" 'False) (C1 ('MetaCons "Nil" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Internal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BinaryTree a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BinaryTree a)))))

access :: BinaryTree a -> Maybe a Source #

Get the element stored at the root, if it exists

asBalancedBinTree :: [a] -> BinaryTree a Source #

Create a balanced binary tree.

running time: \(O(n)\)

foldBinaryUp :: b -> (a -> b -> b -> b) -> BinaryTree a -> BinaryTree (a, b) Source #

Fold function for folding over a binary tree.

toRoseTree' :: BinaryTree a -> Maybe (Tree a) Source #

Convert a BinaryTree into a RoseTree

drawTree' :: Show a => BinaryTree a -> String Source #

Draw a binary tree.