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

Data.Radix1Tree.Word8.Strict.Unsafe

Description

Data structure internals, helper operations and unsafe functions.

Synopsis

Documentation

data Radix1Tree a Source #

Spine-strict radix tree with non-empty byte sequences as keys.

Constructors

Bin 

Fields

Tip 

Fields

Nil 

Instances

Instances details
Foldable Radix1Tree Source # 
Instance details

Defined in Data.RadixNTree.Word8.Strict

Methods

fold :: Monoid m => Radix1Tree m -> m #

foldMap :: Monoid m => (a -> m) -> Radix1Tree a -> m #

foldMap' :: Monoid m => (a -> m) -> Radix1Tree a -> m #

foldr :: (a -> b -> b) -> b -> Radix1Tree a -> b #

foldr' :: (a -> b -> b) -> b -> Radix1Tree a -> b #

foldl :: (b -> a -> b) -> b -> Radix1Tree a -> b #

foldl' :: (b -> a -> b) -> b -> Radix1Tree a -> b #

foldr1 :: (a -> a -> a) -> Radix1Tree a -> a #

foldl1 :: (a -> a -> a) -> Radix1Tree a -> a #

toList :: Radix1Tree a -> [a] #

null :: Radix1Tree a -> Bool #

length :: Radix1Tree a -> Int #

elem :: Eq a => a -> Radix1Tree a -> Bool #

maximum :: Ord a => Radix1Tree a -> a #

minimum :: Ord a => Radix1Tree a -> a #

sum :: Num a => Radix1Tree a -> a #

product :: Num a => Radix1Tree a -> a #

Eq1 Radix1Tree Source # 
Instance details

Defined in Data.RadixNTree.Word8.Strict

Methods

liftEq :: (a -> b -> Bool) -> Radix1Tree a -> Radix1Tree b -> Bool #

Show1 Radix1Tree Source # 
Instance details

Defined in Data.RadixNTree.Word8.Strict

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Radix1Tree a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Radix1Tree a] -> ShowS #

Traversable Radix1Tree Source # 
Instance details

Defined in Data.RadixNTree.Word8.Strict

Methods

traverse :: Applicative f => (a -> f b) -> Radix1Tree a -> f (Radix1Tree b) #

sequenceA :: Applicative f => Radix1Tree (f a) -> f (Radix1Tree a) #

mapM :: Monad m => (a -> m b) -> Radix1Tree a -> m (Radix1Tree b) #

sequence :: Monad m => Radix1Tree (m a) -> m (Radix1Tree a) #

Functor Radix1Tree Source #

Uses map.

Instance details

Defined in Data.RadixNTree.Word8.Strict

Methods

fmap :: (a -> b) -> Radix1Tree a -> Radix1Tree b #

(<$) :: a -> Radix1Tree b -> Radix1Tree a #

NFData1 Radix1Tree Source # 
Instance details

Defined in Data.RadixNTree.Word8.Strict

Methods

liftRnf :: (a -> ()) -> Radix1Tree a -> () #

Show a => Show (Radix1Tree a) Source # 
Instance details

Defined in Data.RadixNTree.Word8.Strict

NFData a => NFData (Radix1Tree a) Source # 
Instance details

Defined in Data.RadixNTree.Word8.Strict

Methods

rnf :: Radix1Tree a -> () #

Eq a => Eq (Radix1Tree a) Source # 
Instance details

Defined in Data.RadixNTree.Word8.Strict

Methods

(==) :: Radix1Tree a -> Radix1Tree a -> Bool #

(/=) :: Radix1Tree a -> Radix1Tree a -> Bool #

Bit operations

type Prefix = Word Source #

Part of the Key from the largest bit to the Mask bit, plus the Mask bit.

type Key = Word Source #

Key as stored in the data structure.

Compare

beyond :: Prefix -> Key -> Bool Source #

\(\mathcal{O}(1)\). Whether the key does not match the prefix.

upper :: Prefix -> Key Source #

\(\mathcal{O}(1)\). Largest key that can reside under this prefix.

lower :: Prefix -> Key Source #

\(\mathcal{O}(1)\). Smallest key that can reside under this prefix.

Create

type Mask = Word Source #

Masking bit.

zeroBit :: Key -> Mask -> Bool Source #

\(\mathcal{O}(1)\). Get the state of the masked bit from the Key.

mask :: Key -> Mask -> Word Source #

\(\mathcal{O}(1)\). Trim the Key down to the masking bit.

branchingBit :: Prefix -> Prefix -> Mask Source #

\(\mathcal{O}(1)\). Find the bit two Prefixes disagree on.

Note that using this function on two equal integers yields 1 << (-1), which results in undefined behavior.

Exceptions

data MalformedTree Source #

Exception thrown by functions that need to return a value, but instead find an invariant-breaking empty node.

Constructors

MalformedTree 

Fields

Edges

Lookup

data Lookup1 a Source #

Key together with the value.

Constructors

Lookup1 !Build1 a 

Instances

Instances details
Show a => Show (Lookup1 a) Source # 
Instance details

Defined in Data.RadixNTree.Word8.Common

Methods

showsPrec :: Int -> Lookup1 a -> ShowS #

show :: Lookup1 a -> String #

showList :: [Lookup1 a] -> ShowS #

Min

unsafeLookupMin :: Radix1Tree a -> (# a #) Source #

\(\mathcal{O}(k)\). Look up a value at the leftmost key in the tree.

Throws MalformedTree if the tree is empty.

unsafeLookupMinWithKey :: Radix1Tree a -> Lookup1 a Source #

\(\mathcal{O}(k)\). Look up a value at the leftmost key in the tree.

Throws MalformedTree if the tree is empty.

Max

unsafeLookupMax :: Radix1Tree a -> (# a #) Source #

\(\mathcal{O}(k)\). Look up a value at the rightmost key in the tree.

Throws MalformedTree if the tree is empty.

unsafeLookupMaxWithKey :: Radix1Tree a -> Lookup1 a Source #

\(\mathcal{O}(k)\). Look up a value at the rightmost key in the tree.

Throws MalformedTree if the tree is empty.

Map

Min

unsafeAdjustMin :: (a -> a) -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(k)\). Update a value at the leftmost key in the tree.

Throws MalformedTree if the tree is empty.

unsafeAdjustMin' :: (a -> a) -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(k)\). Update a value at the leftmost key in the tree.

New value is evaluated to WHNF.

Throws MalformedTree if the tree is empty.

unsafeAdjustMinWithKey :: (Build1 -> a -> a) -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(k)\). Update a value at the leftmost key in the tree.

Throws MalformedTree if the tree is empty.

unsafeAdjustMinWithKey' :: (Build1 -> a -> a) -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(k)\). Update a value at the leftmost key in the tree.

New value is evaluated to WHNF.

Throws MalformedTree if the tree is empty.

Max

unsafeAdjustMax :: (a -> a) -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(k)\). Update a value at the rightmost key in the tree.

Throws MalformedTree if the tree is empty.

unsafeAdjustMax' :: (a -> a) -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(k)\). Update a value at the rightmost key in the tree.

New value is evaluated to WHNF.

Throws MalformedTree if the tree is empty.

unsafeAdjustMaxWithKey :: (Build1 -> a -> a) -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(k)\). Update a value at the rightmost key in the tree.

Throws MalformedTree if the tree is empty.

unsafeAdjustMaxWithKey' :: (Build1 -> a -> a) -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(k)\). Update a value at the rightmost key in the tree.

New value is evaluated to WHNF.

Throws MalformedTree if the tree is empty.

Delete

unsafeDeleteMin :: Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(k)\). Delete a value at the leftmost key in the tree.

Throws MalformedTree if the tree is empty.

unsafeDeleteMax :: Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(k)\). Delete a value at the rightmost key in the tree.

Throws MalformedTree if the tree is empty.

Update

Min

unsafeUpdateMin :: (a -> Maybe a) -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(k)\). Update or delete a value at the leftmost key in the tree.

unsafeUpdateMinWithKey :: (Build1 -> a -> Maybe a) -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(k)\). Update or delete a value at the leftmost key in the tree.

Max

unsafeUpdateMax :: (a -> Maybe a) -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(k)\). Update or delete a value at the rightmost key in the tree.

unsafeUpdateMaxWithKey :: (Build1 -> a -> Maybe a) -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(k)\). Update or delete a value at the rightmost key in the tree.

View

Min

data ViewL1 a Source #

The leftmost value with its key and the rest of the tree.

Constructors

ViewL1 !Build1 a !(Radix1Tree a) 

Instances

Instances details
Show a => Show (ViewL1 a) Source # 
Instance details

Defined in Data.RadixNTree.Word8.Strict

Methods

showsPrec :: Int -> ViewL1 a -> ShowS #

show :: ViewL1 a -> String #

showList :: [ViewL1 a] -> ShowS #

unsafeMinView :: Radix1Tree a -> ViewL1 a Source #

\(\mathcal{O}(\min(x,k))\). Look up the leftmost value and return it alongside the tree without it.

Throws MalformedTree if the tree is empty.

Max

data ViewR1 a Source #

The rightmost value with its key and the rest of the tree.

Constructors

ViewR1 !(Radix1Tree a) !Build1 a 

Instances

Instances details
Show a => Show (ViewR1 a) Source # 
Instance details

Defined in Data.RadixNTree.Word8.Strict

Methods

showsPrec :: Int -> ViewR1 a -> ShowS #

show :: ViewR1 a -> String #

showList :: [ViewR1 a] -> ShowS #

unsafeMaxView :: Radix1Tree a -> ViewR1 a Source #

\(\mathcal{O}(\min(x,k))\). Look up the rightmost value and return it alongside the tree without it.

Throws MalformedTree if the tree is empty.

Full-tree

Merge

merge Source #

Arguments

:: (Build1 -> a -> b -> Maybe c)

Single value collision

-> (Build1 -> a -> Maybe c)

Single left value

-> (Build -> Radix1Tree a -> Radix1Tree c)

Left subtree

-> (Build1 -> b -> Maybe c)

Single right value

-> (Build -> Radix1Tree b -> Radix1Tree c)

Right subtree

-> Radix1Tree a 
-> Radix1Tree b 
-> Radix1Tree c 

\(\mathcal{O}(n_A k_A + n_B k_B)\). General merge of two trees.

Resulting Maybes and Radix1Trees in argument functions are evaluated to WHNF.

This functions inlines when all argument functions are provided.