Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data BinLeafTree v a
- = Leaf !a
- | Node (BinLeafTree v a) !v (BinLeafTree v a)
- class Semigroup v => Measured v a | a -> v where
- node :: Measured v a => BinLeafTree v a -> BinLeafTree v a -> BinLeafTree v a
- asBalancedBinLeafTree :: NonEmpty a -> BinLeafTree Size (Elem a)
- foldUp :: (b -> v -> b -> b) -> (a -> b) -> BinLeafTree v a -> b
- foldUpData :: (w -> v -> w -> w) -> (a -> w) -> BinLeafTree v a -> BinLeafTree w a
- zipExactWith :: (u -> v -> w) -> (a -> b -> c) -> BinLeafTree u a -> BinLeafTree v b -> BinLeafTree w c
- newtype Size = Size Int
- newtype Elem a = Elem {
- _unElem :: a
- data Sized a = Sized !Size a
- data RoseElem v a
- = InternalNode v
- | LeafNode a
- toRoseTree :: BinLeafTree v a -> Tree (RoseElem v a)
- drawTree :: (Show v, Show a) => BinLeafTree v a -> String
- data BinaryTree a
- = Nil
- | Internal (BinaryTree a) !a (BinaryTree a)
- access :: BinaryTree a -> Maybe a
- asBalancedBinTree :: [a] -> BinaryTree a
- foldBinaryUp :: b -> (a -> b -> b -> b) -> BinaryTree a -> BinaryTree (a, b)
- toRoseTree' :: BinaryTree a -> Maybe (Tree a)
- drawTree' :: Show a => BinaryTree a -> String
Documentation
data BinLeafTree v a Source #
Leaf !a | |
Node (BinLeafTree v a) !v (BinLeafTree v a) |
Instances
class Semigroup v => Measured v a | a -> v where Source #
Instances
Measured Size (Elem a) Source # | |
Measured v a => Measured v (BinLeafTree v a) Source # | |
Defined in Data.BinaryTree measure :: BinLeafTree v a -> v Source # | |
Semigroup v => Measured v (NodeData d r v) Source # | |
Measured [I a] (I a) Source # | |
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
Instances
Enum Size Source # | |
Eq Size Source # | |
Integral Size Source # | |
Num Size Source # | |
Ord Size Source # | |
Read Size Source # | |
Real Size Source # | |
Defined in Data.BinaryTree toRational :: Size -> Rational # | |
Show Size Source # | |
Generic Size Source # | |
Semigroup Size Source # | |
Monoid Size Source # | |
NFData Size Source # | |
Defined in Data.BinaryTree | |
Measured Size (Elem a) Source # | |
type Rep Size Source # | |
Defined in Data.BinaryTree |
Instances
Functor Elem Source # | |
Foldable Elem Source # | |
Defined in Data.BinaryTree fold :: Monoid m => Elem m -> m # foldMap :: Monoid m => (a -> m) -> Elem a -> m # foldr :: (a -> b -> b) -> b -> Elem a -> b # foldr' :: (a -> b -> b) -> b -> Elem a -> b # foldl :: (b -> a -> b) -> b -> Elem a -> b # foldl' :: (b -> a -> b) -> b -> Elem a -> b # foldr1 :: (a -> a -> a) -> Elem a -> a # foldl1 :: (a -> a -> a) -> Elem a -> a # elem :: Eq a => a -> Elem a -> Bool # maximum :: Ord a => Elem a -> a # | |
Traversable Elem Source # | |
Measured Size (Elem a) Source # | |
Eq a => Eq (Elem a) Source # | |
Ord a => Ord (Elem a) Source # | |
Read a => Read (Elem a) Source # | |
Show a => Show (Elem a) Source # | |
Instances
Converting into a Data.Tree
InternalNode v | |
LeafNode a |
toRoseTree :: BinLeafTree v a -> Tree (RoseElem v a) Source #
Internal Node Tree
data BinaryTree a Source #
Nil | |
Internal (BinaryTree a) !a (BinaryTree a) |
Instances
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
\(O(n)\)
foldBinaryUp :: b -> (a -> b -> b -> b) -> BinaryTree a -> BinaryTree (a, b) Source #
toRoseTree' :: BinaryTree a -> Maybe (Tree a) Source #