radix-tree-1.0.0.0: Radix trees.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Zebra.Word

Description

Zebra is a fully-strict one-dimensional space partitioning tree, using Words as keys.

Laziness

Evaluating the root of the tree (i.e. (_ :: Zebra)) to weak head normal form evaluates the entire tree to normal form.

Performance

Each function's time complexity is provided in the documentation.

\(n\) refers to the total number of space partitions in the tree. Parts of the tree are denoted using subscripts: \(n_L\) refers to the left side, \(n_R\) to the right side, and \(n_I\) to a range (interval).

\(W\) is the size of Word in bits, i.e. finiteBitSize (0 :: Word).

Implementation

See the implementation section in Data.Zebra.Word.Unsafe for the explanation of the innerworkings.

See the implementation section in Data.Patricia.Word.Strict for literary references.

Synopsis

Documentation

data Zebra Source #

Fully-strict one-dimensional space partitioning tree.

Instances

Instances details
Show Zebra Source #

Tree is represented as a list of closed intervals of all White keys.

Instance details

Defined in Data.Zebra.Word.Internal

Methods

showsPrec :: Int -> Zebra -> ShowS #

show :: Zebra -> String #

showList :: [Zebra] -> ShowS #

Eq Zebra Source # 
Instance details

Defined in Data.Zebra.Word.Internal

Methods

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

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

data Color Source #

Space partition colors.

Constructors

Black 
White 

Instances

Instances details
Show Color Source # 
Instance details

Defined in Data.Zebra.Word.Internal

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Eq Color Source # 
Instance details

Defined in Data.Zebra.Word.Internal

Methods

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

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

Construct

pattern Mono :: Color -> Zebra Source #

\(\mathcal{O}(1)\). All keys are the same color.

Single-key

Lookup

lookup :: Word -> Zebra -> Color Source #

\(\mathcal{O}(\min(n,W))\). Look up the color of the key.

Directional

Size

Left

monoL :: Word -> Zebra -> Maybe Color Source #

\(\mathcal{O}(\min(n,W))\). Check whether all keys smaller than or equal to the given key are of the same color.

sizeL :: Color -> Word -> Zebra -> Natural Source #

\(\mathcal{O}(\min(n,W) + n_L)\). Calculate the number of keys of the given color that are smaller than or equal to the given key. The returned number is guaranteed to be in the \([0, 2^W]\) interval.

Right

monoR :: Word -> Zebra -> Maybe Color Source #

\(\mathcal{O}(\min(n,W))\). Check whether all keys greater than or equal to the given key are of the same color.

sizeR :: Color -> Word -> Zebra -> Natural Source #

\(\mathcal{O}(\min(n,W) + n_R)\). Calculate the number of keys of the given color that are greater than or equal to the given key. The returned number is guaranteed to be in the \([0, 2^W]\) interval.

Lookup

Left

lookupL :: Color -> Word -> Zebra -> Maybe Word Source #

\(\mathcal{O}(\min(n,W))\). Look up the key of the given color that is smaller than or equal to the given key.

findL Source #

Arguments

:: Word

Default value

-> Color 
-> Word

Key

-> Zebra 
-> Word 

\(\mathcal{O}(\min(n,W))\). Look up the key of the given color that is smaller than or equal to the given key, falling back to the default value if no such key exists.

Right

lookupR :: Color -> Word -> Zebra -> Maybe Word Source #

\(\mathcal{O}(\min(n,W))\). Look up the key of the given color that is greater than or equal to the given key.

findR Source #

Arguments

:: Word

Default value

-> Color 
-> Word

Key

-> Zebra 
-> Word 

\(\mathcal{O}(\min(n,W))\). Look up the key of the given color that is greater than or equal to the given key, falling back to the default value if no such key exists.

Insert

Left

fillL :: Word -> Color -> Zebra -> Zebra Source #

\(\mathcal{O}(\min(n,W))\). Set every key smaller than or equal to the given one to the given color.

Right

fillR :: Word -> Color -> Zebra -> Zebra Source #

\(\mathcal{O}(\min(n,W))\). Set every key greater than or equal to the given one to the given color.

Fold

Left-to-right

Left

foldlL :: Word -> (a -> Range -> Color -> a) -> a -> Zebra -> a Source #

\(\mathcal{O}(n_R)\). Fold left-to-right over the ranges of all the keys smaller than or equal to the given one.

foldlL' :: Word -> (a -> Range -> Color -> a) -> a -> Zebra -> a Source #

\(\mathcal{O}(n)\). Fold left-to-right over the ranges of all the keys smaller than or equal to the given one.

Right

foldlR :: Word -> (a -> Range -> Color -> a) -> a -> Zebra -> a Source #

\(\mathcal{O}(n_R)\). Fold left-to-right over the ranges of all the keys greater than or equal to the given one.

foldlR' :: Word -> (a -> Range -> Color -> a) -> a -> Zebra -> a Source #

\(\mathcal{O}(n)\). Fold left-to-right over the ranges of all the keys greater than or equal to the given one.

Right-to-left

Left

foldrL :: Word -> (Range -> Color -> a -> a) -> a -> Zebra -> a Source #

\(\mathcal{O}(n_L)\). Fold right-to-left over the ranges of all the keys smaller than or equal to the given one.

foldrL' :: Word -> (Range -> Color -> a -> a) -> a -> Zebra -> a Source #

\(\mathcal{O}(n)\). Fold right-to-left over the ranges of all the keys smaller than or equal to the given one.

Right

foldrR :: Word -> (Range -> Color -> a -> a) -> a -> Zebra -> a Source #

\(\mathcal{O}(n_L)\). Fold right-to-left over the ranges of all the keys greater than or equal to the given one.

foldrR' :: Word -> (Range -> Color -> a -> a) -> a -> Zebra -> a Source #

\(\mathcal{O}(n)\). Fold right-to-left over the ranges of all the keys greater than or equal to the given one.

Range

data Range where Source #

A closed interval between two keys.

Bundled Patterns

pattern Range

Reorders endpoints to fit mathematical notation: \([12, 3]\) will be converted to \([3, 12]\).

Pattern matching guarantees \(k_1 \le k_2\).

Fields

Instances

Instances details
Show Range Source # 
Instance details

Defined in Radix.Word.Common

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

Size

monoRange :: Range -> Zebra -> Maybe Color Source #

\(\mathcal{O}(\min(n,W))\). Check whether all keys in the range are of the same color.

sizeRange :: Color -> Range -> Zebra -> Natural Source #

\(\mathcal{O}(\min(n,W) + n_I)\). Calculate the number of keys of the given color in the range.

Insert

fillRange :: Range -> Color -> Zebra -> Zebra Source #

\(\mathcal{O}(\min(n,W))\). Set every key in the range to the given color.

Fold

Left-to-right

foldlRange :: Range -> (a -> Range -> Color -> a) -> a -> Zebra -> a Source #

\(\mathcal{O}(\min(n,W) + n_{I_R})\). Fold left-to-right over the ranges of all the keys in the given range.

foldlRange' :: Range -> (a -> Range -> Color -> a) -> a -> Zebra -> a Source #

\(\mathcal{O}(\min(n,W) + n_I)\). Fold left-to-right over the ranges of all the keys in the given range.

Right-to-left

foldrRange :: Range -> (Range -> Color -> a -> a) -> a -> Zebra -> a Source #

\(\mathcal{O}(\min(n,W) + n_{I_L})\). Fold right-to-left over the ranges of all the keys in the given range.

foldrRange' :: Range -> (Range -> Color -> a -> a) -> a -> Zebra -> a Source #

\(\mathcal{O}(\min(n,W) + n_I)\). Fold right-to-left with a strict accumulator over the ranges of all the keys in the given range.

Full tree

Size

size :: Color -> Zebra -> Natural Source #

\(\mathcal{O}(n)\). Calculate the number of keys of the given color. The returned number is guaranteed to be in the \([0, 2^W]\) interval.

Fold

Left-to-right

foldl :: (a -> Range -> Color -> a) -> a -> Zebra -> a Source #

\(\mathcal{O}(n_R)\). Fold left-to-right over the ranges.

foldl' :: (a -> Range -> Color -> a) -> a -> Zebra -> a Source #

\(\mathcal{O}(n)\). Fold left-to-right over the ranges with a strict accumulator.

Right-to-right

foldr :: (Range -> Color -> a -> a) -> a -> Zebra -> a Source #

\(\mathcal{O}(n_L)\). Fold right-to-left over the ranges.

foldr' :: (Range -> Color -> a -> a) -> a -> Zebra -> a Source #

\(\mathcal{O}(n)\). Fold right-to-left over the ranges.

Complement

complement :: Zebra -> Zebra Source #

\(\mathcal{O}(n)\). Invert the colors of all keys.

Compare

data PartialOrdering Source #

Comparison of two sets, \(A\) and \(B\) respectively.

Constructors

Subset

\(A \subset B\).

Superset

\(A \supset B\).

Equal

\(A = B\).

Incomparable

\(A \parallel B\).

Instances

Instances details
Show PartialOrdering Source # 
Instance details

Defined in Radix.Common

Eq PartialOrdering Source # 
Instance details

Defined in Radix.Common

compare :: Color -> Zebra -> Zebra -> PartialOrdering Source #

\(\mathcal{O}(n_A + n_B)\). Compare two trees with respect to set inclusion over the given color.

Union

union :: Color -> Zebra -> Zebra -> Zebra Source #

\(\mathcal{O}(n_A + n_B)\). Union of two trees over the given color.

Difference

difference :: Color -> Zebra -> Zebra -> Zebra Source #

\(\mathcal{O}(n_A + n_B)\). Difference of two trees over the given color.

symmetricDifference :: Color -> Zebra -> Zebra -> Zebra Source #

\(\mathcal{O}(n_A + n_B)\). Symmetric difference of two trees over the given color.

Intersection

disjoint :: Color -> Zebra -> Zebra -> Bool Source #

\(\mathcal{O}(n_A + n_B)\). Determine whether two trees are disjoint over the given color.

intersection :: Color -> Zebra -> Zebra -> Zebra Source #

\(\mathcal{O}(n_A + n_B)\). Intersection of two trees over the given color.