Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides a Braun tree which keeps track of its size, and associated functions.
- data Braun a = Braun {}
- fromList :: [a] -> Braun a
- empty :: Braun a
- singleton :: a -> Braun a
- type Builder a b = Int -> Int -> Int -> (([Tree a] -> [Tree a] -> [Tree a]) -> [Tree a] -> Int -> b) -> b
- consB :: a -> Builder a b -> Builder a b
- nilB :: Builder a b
- runB :: Builder a (Braun a) -> Braun a
- snoc :: a -> Braun a -> Braun a
- unsnoc :: Braun a -> Maybe (a, Braun a)
- unsnoc' :: HasCallStack => Braun a -> (a, Braun a)
- cons :: a -> Braun a -> Braun a
- uncons :: Braun a -> Maybe (a, Braun a)
- uncons' :: HasCallStack => Braun a -> (a, Braun a)
- insertBy :: (a -> a -> Ordering) -> a -> Braun a -> Braun a
- deleteBy :: (a -> a -> Ordering) -> a -> Braun a -> Braun a
- glb :: (a -> b -> Ordering) -> a -> Braun b -> Maybe b
- cmpRoot :: (a -> b -> Ordering) -> a -> Braun b -> Ordering
- ltRoot :: (a -> b -> Ordering) -> a -> Braun b -> Bool
Braun type
A Braun tree which keeps track of its size.
Functor Braun Source # | |
Foldable Braun Source # |
fromList (toList xs) === xs |
Traversable Braun Source # | |
Eq a => Eq (Braun a) Source # | |
Data a => Data (Braun a) Source # | |
Ord a => Ord (Braun a) Source # | |
Read a => Read (Braun a) Source # | |
Show a => Show (Braun a) Source # | |
Generic (Braun a) Source # | |
NFData a => NFData (Braun a) Source # | |
Generic1 * Braun Source # | |
type Rep (Braun a) Source # | |
type Rep1 * Braun Source # | |
Construction
fromList :: [a] -> Braun a Source #
O(n). Create a Braun tree (in order) from a list. The algorithm is similar to that in:
Okasaki, Chris. ‘Three Algorithms on Braun Trees’. Journal of Functional Programming 7, no. 6 (November 1997): 661–666. https://doi.org/10.1017/S0956796897002876.
However, it uses a fold rather than explicit recursion, allowing fusion.
toList (fromList xs) === xs
Building
type Builder a b = Int -> Int -> Int -> (([Tree a] -> [Tree a] -> [Tree a]) -> [Tree a] -> Int -> b) -> b Source #
A type suitable for building a Braun tree by repeated applications
of consB
.
Modification
At ends
snoc :: a -> Braun a -> Braun a Source #
O(log n). Append an item to the end of a Braun tree.
x `snoc` fromList xs === fromList (xs ++ [x])
unsnoc :: Braun a -> Maybe (a, Braun a) Source #
O(log n). Returns the last element in the list and the other
elements, if present, or Nothing
if the tree is empty.
>>>
unsnoc empty
Nothing
unsnoc (snoc x xs) === Just (x, xs)
unfoldr unsnoc (fromList xs) === reverse xs
unsnoc' :: HasCallStack => Braun a -> (a, Braun a) Source #
O(log n). Returns the last element in the list and the other elements, if present, or raises an error if the tree is empty.
isBraun (snd (unsnoc' (fromList (1:xs))))
fst (unsnoc' (fromList (1:xs))) == last (1:xs)
cons :: a -> Braun a -> Braun a Source #
O(log n). Append an element to the beginning of the Braun tree.
uncons' (cons x xs) === (x,xs)
uncons :: Braun a -> Maybe (a, Braun a) Source #
O(log n). Returns the first element in the array and the rest
the elements, if it is nonempty, or Nothing
if it is empty.
>>>
uncons empty
Nothing
uncons (cons x xs) === Just (x,xs)
unfoldr uncons (fromList xs) === xs
uncons' :: HasCallStack => Braun a -> (a, Braun a) Source #
O(log n). Returns the first element in the array and the rest the elements, if it is nonempty, failing with an error if it is empty.
uncons' (cons x xs) === (x,xs)
As set
insertBy :: (a -> a -> Ordering) -> a -> Braun a -> Braun a Source #
O(n). Insert an element into the Braun tree, using the comparison function provided.
deleteBy :: (a -> a -> Ordering) -> a -> Braun a -> Braun a Source #
O(n). Delete an element from the Braun tree, using the comparison function provided.
Querying
glb :: (a -> b -> Ordering) -> a -> Braun b -> Maybe b Source #
O(log^2 n). Find the greatest lower bound for an element.