uniquely-represented-sets-0.1.0.0

Safe HaskellNone
LanguageHaskell2010

Data.Tree.Braun

Contents

Description

This module provides functions for manipulating and using Braun trees.

Synopsis

Construction

fromList :: [a] -> Tree 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.

Inlined sufficiently, the implementation is:

fromList :: [a] -> Tree a
fromList xs = foldr f b xs 1 1 (const head) where
  f e a !k 1  p = a (k*2) k     (ys zs -> p n (g e ys zs (drop k zs)))
  f e a !k !m p = a k     (m-1) (p . g e)

  g x a (y:ys) (z:zs) = Node x y    z    : a ys zs
  g x a []     (z:zs) = Node x Leaf z    : a [] zs
  g x a (y:ys) []     = Node x y    Leaf : a ys []
  g x a []     []     = Node x Leaf Leaf : a [] []
  {-# NOINLINE g #-}

  n _ _ = []
  b _ _ p = p n [Leaf]
{-# INLINABLE fromList #-}
toList (fromList xs) == xs

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

O(log^2 n). replicate n x creates a Braun tree from n copies of x.

\(NonNegative n) -> size (replicate n ()) == n

singleton :: a -> Tree a Source #

A Braun tree with one element.

empty :: Tree a Source #

A Braun tree with no elements.

Building

type Builder a b = Int -> Int -> (([Tree a] -> [Tree a] -> [Tree a]) -> [Tree a] -> b) -> b Source #

A type suitable for building a Braun tree by repeated applications of consB.

consB :: a -> Builder a b -> Builder a b Source #

O(1). Push an element to the front of a Builder.

nilB :: Builder a b Source #

An empty Builder.

runB :: Builder a (Tree a) -> Tree a Source #

Convert a Builder to a Braun tree.

Modification

cons :: a -> Tree a -> Tree a Source #

O(log n). Append an element to the beginning of the Braun tree.

uncons' (cons x xs) === (x,xs)

uncons :: Tree a -> Maybe (a, Tree 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 => Tree a -> (a, Tree 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)

tail :: Tree a -> Tree a Source #

O(log n). Get all elements except the first from the Braun tree. Returns an empty tree when called on an empty tree.

>>> tail empty
Leaf
tail (cons x xs) === xs
tail (cons undefined xs) === xs

Consuming

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

Perform a right fold, in Braun order, over a tree.

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

O(n). Convert a Braun tree to a list.

fromList (toList xs) === xs

Querying

(!) :: HasCallStack => Tree a -> Int -> a Source #

O(log n). Retrieve the element at the specified position, raising an error if it's not present.

\(NonNegative n) xs -> n < length xs ==> fromList xs ! n == xs !! n

(!?) :: Tree a -> Int -> Maybe a Source #

O(log n). Retrieve the element at the specified position, or Nothing if the index is out of range.

size :: Tree a -> Int Source #

O(log^2 n). Calculate the size of a Braun tree.

data UpperBound a Source #

Result of an upper bound operation.

Constructors

Exact a 
TooHigh Int 
Finite 

ub :: (a -> b -> Ordering) -> a -> Tree b -> UpperBound b Source #

Find the upper bound for a given element.