rbst-0.0.0.1: Randomized Binary Search Trees

Copyright(c) 2020 Arnau Abella Dmitrii Kovanikov
LicenseMIT (see the file LICENSE)
MaintainerArnau Abella arnauabell@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

RBST

Contents

Description

General description

Package rbst implements a self-balancing-tree-like data structure called Randomized Binary Search Tree. This data structure behave exactly like a random_binary_search_tree, irrespectively of the input data distribution, with fast (logarithmic time complexity) insert / delete / lookup / union / etc. operations.

Package structure

This package contains the following modules:

Module RBST reexports ony RBST.Pretty and exports all RBST functionalities.

Usage example

A balanced Tree can be created from a list of keys/values:

>>> import GHC.Exts (IsList (..))
>>> let empty = empty :: RBST Int String
>>> let single = one 1 'v'
>>> let tree = fromList [("x", 2),("y", 3), ("z", 1)] :: RBST String Int
>>> prettyPrint tree
      ("y",3) [3]
           ╱╲
          ╱  ╲
         ╱    ╲
        ╱      ╲
       ╱        ╲
      ╱          ╲
("x",2) [1] ("z",1) [1]

Each node shows:

  1. The key.
  2. The associated value.
  3. The size of the tree.

You can try it yourself:

> insert "w" 5 tree
> delete "u" tree
>>> lookup "y" tree
Just 3
>>> lookup "w" tree
Nothing
>>> compactPrint tree
("y",3) [3]
     |
     |-- ("z",1) [1]
     |
     \__ ("x",2) [1]

Implementation

The implementation of Randomized Binary Search Trees is based on:

Synopsis

Data structure & Instances

newtype Size Source #

Size of the Tree data structure.

Constructors

Size 

Fields

Instances
Eq Size Source # 
Instance details

Defined in RBST.Internal

Methods

(==) :: Size -> Size -> Bool #

(/=) :: Size -> Size -> Bool #

Num Size Source # 
Instance details

Defined in RBST.Internal

Methods

(+) :: Size -> Size -> Size #

(-) :: Size -> Size -> Size #

(*) :: Size -> Size -> Size #

negate :: Size -> Size #

abs :: Size -> Size #

signum :: Size -> Size #

fromInteger :: Integer -> Size #

Ord Size Source # 
Instance details

Defined in RBST.Internal

Methods

compare :: Size -> Size -> Ordering #

(<) :: Size -> Size -> Bool #

(<=) :: Size -> Size -> Bool #

(>) :: Size -> Size -> Bool #

(>=) :: Size -> Size -> Bool #

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

Read Size Source # 
Instance details

Defined in RBST.Internal

Show Size Source # 
Instance details

Defined in RBST.Internal

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

Generic Size Source # 
Instance details

Defined in RBST.Internal

Associated Types

type Rep Size :: Type -> Type #

Methods

from :: Size -> Rep Size x #

to :: Rep Size x -> Size #

NFData Size Source # 
Instance details

Defined in RBST.Internal

Methods

rnf :: Size -> () #

type Rep Size Source # 
Instance details

Defined in RBST.Internal

type Rep Size = D1 (MetaData "Size" "RBST.Internal" "rbst-0.0.0.1-65lZlm8Xqg8CU5M7iQrOXY" True) (C1 (MetaCons "Size" PrefixI True) (S1 (MetaSel (Just "unSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)))

data Tree k a Source #

Tree data structure. The node contains the rank of the tree.

Constructors

Node !Size !k !(Tree k a) !a !(Tree k a) 
Empty 
Instances
Foldable (Tree k) Source # 
Instance details

Defined in RBST.Internal

Methods

fold :: Monoid m => Tree k m -> m #

foldMap :: Monoid m => (a -> m) -> Tree k a -> m #

foldr :: (a -> b -> b) -> b -> Tree k a -> b #

foldr' :: (a -> b -> b) -> b -> Tree k a -> b #

foldl :: (b -> a -> b) -> b -> Tree k a -> b #

foldl' :: (b -> a -> b) -> b -> Tree k a -> b #

foldr1 :: (a -> a -> a) -> Tree k a -> a #

foldl1 :: (a -> a -> a) -> Tree k a -> a #

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

null :: Tree k a -> Bool #

length :: Tree k a -> Int #

elem :: Eq a => a -> Tree k a -> Bool #

maximum :: Ord a => Tree k a -> a #

minimum :: Ord a => Tree k a -> a #

sum :: Num a => Tree k a -> a #

product :: Num a => Tree k a -> a #

(Eq k, Eq a) => Eq (Tree k a) Source # 
Instance details

Defined in RBST.Internal

Methods

(==) :: Tree k a -> Tree k a -> Bool #

(/=) :: Tree k a -> Tree k a -> Bool #

(Read k, Read a) => Read (Tree k a) Source # 
Instance details

Defined in RBST.Internal

Methods

readsPrec :: Int -> ReadS (Tree k a) #

readList :: ReadS [Tree k a] #

readPrec :: ReadPrec (Tree k a) #

readListPrec :: ReadPrec [Tree k a] #

(Show k, Show a) => Show (Tree k a) Source # 
Instance details

Defined in RBST.Internal

Methods

showsPrec :: Int -> Tree k a -> ShowS #

show :: Tree k a -> String #

showList :: [Tree k a] -> ShowS #

Generic (Tree k a) Source # 
Instance details

Defined in RBST.Internal

Associated Types

type Rep (Tree k a) :: Type -> Type #

Methods

from :: Tree k a -> Rep (Tree k a) x #

to :: Rep (Tree k a) x -> Tree k a #

(NFData k, NFData a) => NFData (Tree k a) Source # 
Instance details

Defined in RBST.Internal

Methods

rnf :: Tree k a -> () #

type Rep (Tree k a) Source # 
Instance details

Defined in RBST.Internal

data RBST k a Source #

RBST data structure.

Constructors

RBST 

Fields

Instances
Foldable (RBST k) Source # 
Instance details

Defined in RBST.Internal

Methods

fold :: Monoid m => RBST k m -> m #

foldMap :: Monoid m => (a -> m) -> RBST k a -> m #

foldr :: (a -> b -> b) -> b -> RBST k a -> b #

foldr' :: (a -> b -> b) -> b -> RBST k a -> b #

foldl :: (b -> a -> b) -> b -> RBST k a -> b #

foldl' :: (b -> a -> b) -> b -> RBST k a -> b #

foldr1 :: (a -> a -> a) -> RBST k a -> a #

foldl1 :: (a -> a -> a) -> RBST k a -> a #

toList :: RBST k a -> [a] #

null :: RBST k a -> Bool #

length :: RBST k a -> Int #

elem :: Eq a => a -> RBST k a -> Bool #

maximum :: Ord a => RBST k a -> a #

minimum :: Ord a => RBST k a -> a #

sum :: Num a => RBST k a -> a #

product :: Num a => RBST k a -> a #

Ord k => IsList (RBST k a) Source #

Create a tree from a list of key/value pairs, and viceversa.

NOTE: This requires -XOverloadedLists enabled.

Functions have the following time complexity:

  1. fromList: \( O(n \cdot \log \ n) \)
  2. toList: \( O(n) \).
>>> import GHC.Exts
>>> let tree = (fromList $ zip ['a'..'e'] [1..5]) :: RBST Char Int
>>> Pretty.prettyPrint tree
               ('d',4) [5]
                       ╱╲
                      ╱  ╲
                     ╱    ╲
                    ╱      ╲
                   ╱        ╲
                  ╱          ╲
                 ╱            ╲
                ╱              ╲
               ╱                ╲
      ('b',2) [3]       ('e',5) [1]
           ╱╲
          ╱  ╲
         ╱    ╲
        ╱      ╲
       ╱        ╲
      ╱          ╲
('a',1) [1] ('c',3) [1]
>>> toList tree
[('a',1),('b',2),('c',3),('d',4),('e',5)]
Instance details

Defined in RBST.Internal

Associated Types

type Item (RBST k a) :: Type #

Methods

fromList :: [Item (RBST k a)] -> RBST k a #

fromListN :: Int -> [Item (RBST k a)] -> RBST k a #

toList :: RBST k a -> [Item (RBST k a)] #

(Eq k, Eq a) => Eq (RBST k a) Source #

(==) is implemented via (==) of the underlying Tree.

Instance details

Defined in RBST.Internal

Methods

(==) :: RBST k a -> RBST k a -> Bool #

(/=) :: RBST k a -> RBST k a -> Bool #

(Show k, Show a) => Show (RBST k a) Source # 
Instance details

Defined in RBST.Internal

Methods

showsPrec :: Int -> RBST k a -> ShowS #

show :: RBST k a -> String #

showList :: [RBST k a] -> ShowS #

Generic (RBST k a) Source # 
Instance details

Defined in RBST.Internal

Associated Types

type Rep (RBST k a) :: Type -> Type #

Methods

from :: RBST k a -> Rep (RBST k a) x #

to :: Rep (RBST k a) x -> RBST k a #

Ord k => Semigroup (RBST k a) Source #

(<>) is implemented via merge.

Note: Unlawful instance.

TODO: require Semigroup a and use unionWith

Instance details

Defined in RBST.Internal

Methods

(<>) :: RBST k a -> RBST k a -> RBST k a #

sconcat :: NonEmpty (RBST k a) -> RBST k a #

stimes :: Integral b => b -> RBST k a -> RBST k a #

Ord k => Monoid (RBST k a) Source #

mempty is implemented via empty.

Instance details

Defined in RBST.Internal

Methods

mempty :: RBST k a #

mappend :: RBST k a -> RBST k a -> RBST k a #

mconcat :: [RBST k a] -> RBST k a #

(NFData k, NFData a) => NFData (RBST k a) Source # 
Instance details

Defined in RBST.Internal

Methods

rnf :: RBST k a -> () #

type Rep (RBST k a) Source # 
Instance details

Defined in RBST.Internal

type Rep (RBST k a) = D1 (MetaData "RBST" "RBST.Internal" "rbst-0.0.0.1-65lZlm8Xqg8CU5M7iQrOXY" False) (C1 (MetaCons "RBST" PrefixI True) (S1 (MetaSel (Just "rbstGen") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PureMT) :*: S1 (MetaSel (Just "rbstTree") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Tree k a))))
type Item (RBST k a) Source # 
Instance details

Defined in RBST.Internal

type Item (RBST k a) = (k, a)

Construction functions

empty :: RBST k a Source #

The empty Tree.

> empty      == fromList []
> size empty == 0

one :: k -> a -> RBST k a Source #

Single node RBST.

>>> size (one 1 'a')
1

Query functions

size :: RBST k a -> Int Source #

\( O(1) \). Return the size of the RBST.

height :: RBST k a -> Int Source #

\( O(n) \). Height of the tree.

>>> height (empty :: RBST Char Int)
-1
>>> height (one 'x' 1)
0
>>> height (one 'x' 1 <> one 'y' 2)
1

lookup :: Ord k => k -> RBST k a -> Maybe a Source #

\( O(\log \ n) \). Lookup the value at the key in the tree.

>>> lookup 'A' (empty :: RBST Char Int)
Nothing
>>> lookup 'A' (one 'A' 7)
Just 7

at :: Int -> RBST k a -> Maybe (k, a) Source #

\( O(\log \ n) \). Get the i-th element of the tree.

NOTE: \(0 \leq i \leq n\), where n is the size of the tree.

>>> let tree = fromList [('a',1), ('b', 2), ('c',3)] :: RBST Char Int
>>> at 0 tree
Just ('a',1)
>>> at 2 tree
Just ('c',3)

Modification functions

insert :: Ord k => k -> a -> RBST k a -> RBST k a Source #

\( O(\log \ n) \). Insert a new key/value pair in the tree.

If the key is already present in the map, the associated value is replaced with the supplied value.

> insert x 1 empty == one x 1

delete :: Ord k => k -> RBST k a -> RBST k a Source #

\( O(\log \ n) \). Delete a key and its value from the map. When the key is not a member of the map, the original map is returned.

> delete 1 (one (1, A)) == empty

remove :: Int -> RBST k a -> RBST k a Source #

\( O(\log \ n) \). Delete the i-th element of the tree.

NOTE: \(0 \leq i \leq n\), where n is the size of the tree.

>>> let tree = fromList [('a',1), ('b', 2), ('c',3)] :: RBST Char Int
>>> toList $ remove 0 tree
[('b',2),('c',3)]

take :: Int -> RBST k a -> RBST k a Source #

\( O(\log n) \). Returns the first i-th elements of the given tree t of size n.

Note:

  1. If \( i \leq 0 \), then the result is empty.
  2. If \( i \geq n \), then the result is t.

drop :: Int -> RBST k a -> RBST k a Source #

\( O(\log n) \). Returns the tree t without the first i-th elements.

Note:

  1. If \( i \leq 0 \), then the result is t.
  2. If \( i \geq n \), then the result is empty.

Set operations

union :: Ord k => RBST k a -> RBST k a -> RBST k a Source #

\( \theta(m + n) \). Union of two RBST.

In case of duplication, only one key remains by a random choice.

intersection :: Ord k => RBST k a -> RBST k a -> RBST k a Source #

\( \theta(m + n) \). Intersection of two RBST.

subtraction :: Ord k => RBST k a -> RBST k a -> RBST k a Source #

\( \theta(m + n) \). Difference (subtraction) of two RBST.

difference :: Ord k => RBST k a -> RBST k a -> RBST k a Source #

\( \theta(m + n) \). Difference (disjunctive union) of two RBST.

Reexports