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

Data.Radix1Tree.Word8.Strict

Description

StrictRadix1Tree a is a spine-strict radix tree that uses byte-aligned non-empty byte sequences as keys.

Laziness

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

Functions do not perform any additional evaluations unless their documentation directly specifies so.

Performance

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

\(x\) is the length of the input key.

\(k\) is the length of the longest key stored in the tree.

\(n\) refers to the total number of entries 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_M\) to entries collected with the use of a Monoid.

Inlining

Functions that produce and consume Feed1s are treated specially within the library, as when combined they can be reduced in a manner similar to the destroy/unfoldr elimination rule.

The elimination in this library is achieved by inlining both types of functions heavily. To avoid unnecessary code duplication during compilation consider creating helper functions that apply these functions one to another, e.g.

updateBS f bs = update f (unsafeFeedByteString bs)

N.B. To inline properly functions that consume Feed1s must mention all of the arguments except for the tree.

Implementation

See the implementation section in Data.RadixTree.Word8.Strict.Unsafe for the explanation of the innerworkings.

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

Synopsis

Documentation

type StrictRadix1Tree = Radix1Tree Source #

Convenience type synonym.

data Radix1Tree a Source #

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

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 #

data RadixTree a Source #

Spine-strict radix tree with byte sequences as keys.

Constructors

RadixTree 

Fields

Instances

Instances details
Foldable RadixTree Source # 
Instance details

Defined in Data.RadixNTree.Word8.Strict

Methods

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

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

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

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

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

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

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

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

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

toList :: RadixTree a -> [a] #

null :: RadixTree a -> Bool #

length :: RadixTree a -> Int #

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

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

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

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

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

Eq1 RadixTree Source # 
Instance details

Defined in Data.RadixNTree.Word8.Strict

Methods

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

Show1 RadixTree Source # 
Instance details

Defined in Data.RadixNTree.Word8.Strict

Methods

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

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

Traversable RadixTree Source # 
Instance details

Defined in Data.RadixNTree.Word8.Strict

Methods

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

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

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

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

Functor RadixTree Source #

Uses map.

Instance details

Defined in Data.RadixNTree.Word8.Strict

Methods

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

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

NFData1 RadixTree Source # 
Instance details

Defined in Data.RadixNTree.Word8.Strict

Methods

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

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

Defined in Data.RadixNTree.Word8.Strict

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

Defined in Data.RadixNTree.Word8.Strict

Methods

rnf :: RadixTree a -> () #

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

Defined in Data.RadixNTree.Word8.Strict

Methods

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

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

Key

Construct

empty :: Radix1Tree a Source #

\(\mathcal{O}(1)\). Empty tree.

singleton :: Feed1 -> a -> Radix1Tree a Source #

\(\mathcal{O}(x)\). Tree with a single entry.

Convert

toLazy :: StrictRadix1Tree a -> LazyRadix1Tree a Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(n)\). Create a lazy Patricia tree from a strict one.

The resulting tree does not share its data representation with the original.

Single-key

Lookup

lookup :: Feed1 -> Radix1Tree a -> Maybe a Source #

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

find :: a -> Feed1 -> Radix1Tree a -> a Source #

\(\mathcal{O}(\min(x,k))\). Look up the value at a key in the tree, falling back to the given default value if it does not exist.

member :: Feed1 -> Radix1Tree a -> Bool Source #

\(\mathcal{O}(\min(x,k))\). Check whether the value exists at a key in the tree.

subtree :: Feed1 -> Radix1Tree a -> RadixTree a Source #

\(\mathcal{O}(\min(x,k))\). Look up the part of the tree below the given prefix.

Chunked

Chunked lookup allows providing the key piece by piece while retaining the ability to check for early failure.

Note that while subtree can be used to achieve the same result, it is more expensive allocation-wise, as it must ensure that the resulting tree is well-formed after each chunk application.

data Cursor a Source #

A particular point in the tree.

Instances

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

Defined in Data.RadixNTree.Word8.Strict

Methods

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

show :: Cursor a -> String #

showList :: [Cursor a] -> ShowS #

cursor :: Radix1Tree a -> Cursor a Source #

\(\mathcal{O}(1)\). Make a cursor that points to the root of the tree.

move :: Feed1 -> Cursor a -> Cursor a Source #

\(\mathcal{O}(\min(x,k))\). Move the cursor down by the extent of the given key.

stop :: Cursor a -> Maybe a Source #

\(\mathcal{O}(1)\). Retrieve the value at which the cursor points.

data Location Source #

Whether the cursor point to a point within the tree.

Constructors

Inside 
Outside 

Instances

Instances details
Show Location Source # 
Instance details

Defined in Radix.Word8.Common

locate :: Cursor a -> Location Source #

\(\mathcal{O}(1)\). Determine whether the cursor points to a point within the tree.

Insert

insert :: Feed1 -> a -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k))\). Insert a new value in the tree at the given key. If a value already exists at that key, it is replaced.

insertWith :: (a -> a) -> Feed1 -> a -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k))\). Insert a new value in the tree at the given key. If a value already exists at that key, the function is used instead.

insertWith' :: (a -> a) -> Feed1 -> a -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k))\). Insert a new value in the tree at the given key. If a value already exists at that key, the function is used instead.

New value is evaluated to WHNF.

Map

adjust :: (a -> a) -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k))\). Apply a function to a value in the tree at the given key.

adjust' :: (a -> a) -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k))\). Apply a function to a value in the tree at the given key.

New value is evaluated to WHNF.

Delete

delete :: Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k))\). Delete a value in the tree at the given key.

prune :: Openness -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k))\). Delete values in the tree below the given key.

Update

update :: (a -> Maybe a) -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k))\). Update or delete a value in the tree at the given key.

The Maybe is evaluated to WHNF.

alter :: (Maybe a -> Maybe a) -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k))\). Insert, update or delete a value in the tree at the given key.

The resulting Maybe is evaluated to WHNF.

shape :: (RadixTree a -> RadixTree a) -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k))\). Update the part of the tree at the given prefix.

The resulting Radix1Tree is evaluated to WHNF.

Take

data SplitLookup1 l x r Source #

Result of a tree split with a lookup.

Constructors

SplitLookup1 !(Radix1Tree l) !(Maybe x) !(Radix1Tree r) 

splitLookup :: Feed1 -> Radix1Tree a -> SplitLookup1 a a a Source #

\(\mathcal{O}(\min(x,k))\). Split1 the tree into two, such that values with keys smaller than the given one are on the left, values with keys greater than the given one are on the right, and the value at the given key is returned separately.

Directional

data Openness Source #

Whether the endpoint itself is included in the interval.

Constructors

Open

Excluding the point.

Closed

Including the point.

Instances

Instances details
Show Openness Source # 
Instance details

Defined in Data.RadixNTree.Word8.Common

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 #

lookupL :: Openness -> Feed1 -> Radix1Tree a -> Maybe (Lookup1 a) Source #

\(\mathcal{O}(\min(x,k))\). Look up a value at a largest key smaller than (or equal to) the given key.

lookupR :: Openness -> Feed1 -> Radix1Tree a -> Maybe (Lookup1 a) Source #

\(\mathcal{O}(\min(x,k))\). Look up a value at a smallest key greater than (or equal to) the given key.

Map

Left

adjustL :: (a -> a) -> Openness -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k) + n_L)\). Apply a function to every value for which the key is smaller than (or equal to) the given one.

adjustL' :: (a -> a) -> Openness -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k) + n_L)\). Apply a function to every value for which the key is smaller than (or equal to) the given one.

New value is evaluated to WHNF.

adjustLWithKey :: (Build1 -> a -> a) -> Openness -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k) + n_L)\). Apply a function to every value for which the key is smaller than (or equal to) the given one.

adjustLWithKey' :: (Build1 -> a -> a) -> Openness -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k) + n_L)\). Apply a function to every value for which the key is smaller than (or equal to) the given one.

New value is evaluated to WHNF.

Right

adjustR :: (a -> a) -> Openness -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k) + n_R)\). Apply a function to every value for which the key is greater than (or equal to) the given one.

adjustR' :: (a -> a) -> Openness -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k) + n_R)\). Apply a function to every value for which the key is greater than (or equal to) the given one.

New value is evaluated to WHNF.

adjustRWithKey :: (Build1 -> a -> a) -> Openness -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k) + n_R)\). Apply a function to every value for which the key is greater than (or equal to) the given one.

adjustRWithKey' :: (Build1 -> a -> a) -> Openness -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k) + n_R)\). Apply a function to every value for which the key is greater than (or equal to) the given one.

New value is evaluated to WHNF.

Update

Left

updateL :: (a -> Maybe a) -> Openness -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k) + n_L)\). Update every value for which the key is smaller than (or equal to) the given one.

updateLWithKey :: (Build1 -> a -> Maybe a) -> Openness -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k) + n_L)\). Update every value for which the key is smaller than (or equal to) the given one.

The Maybe is evaluated to WHNF.

Right

updateR :: (a -> Maybe a) -> Openness -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k) + n_R)\). Update every value for which the key is greater than (or equal to) the given one.

updateRWithKey :: (Build1 -> a -> Maybe a) -> Openness -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k) + n_R)\). Update every value for which the key is greater than (or equal to) the given one.

The Maybe is evaluated to WHNF.

Take

data Split1 l r Source #

Result of a tree split.

Constructors

Split1 !(Radix1Tree l) !(Radix1Tree r) 

Left

takeL :: Openness -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k))\). Take values for which keys are smaller than (or equal to) the given one.

splitL :: Openness -> Feed1 -> Radix1Tree a -> Split1 a a Source #

\(\mathcal{O}(\min(x,k))\). Split1 the tree into two, such that values with keys smaller than (or equal to) the given one are on the left, and the rest are on the right.

Right

takeR :: Openness -> Feed1 -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(\min(x,k))\). Take values for which keys are greater than (or equal to) the given one.

Edges

Lookup

Min

lookupMin :: Radix1Tree a -> Maybe a Source #

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

lookupMinWithKey :: Radix1Tree a -> Maybe (Lookup1 a) Source #

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

Max

lookupMax :: Radix1Tree a -> Maybe a Source #

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

lookupMaxWithKey :: Radix1Tree a -> Maybe (Lookup1 a) Source #

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

Map

Min

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

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

adjustMin' :: (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.

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

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

adjustMinWithKey' :: (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.

Max

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

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

adjustMax' :: (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.

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

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

adjustMaxWithKey' :: (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.

Delete

deleteMin :: Radix1Tree a -> Radix1Tree a Source #

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

deleteMax :: Radix1Tree a -> Radix1Tree a Source #

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

Update

Min

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

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

updateMinWithKey :: (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

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

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

updateMaxWithKey :: (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 #

minView :: Radix1Tree a -> Maybe (ViewL1 a) Source #

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

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 #

maxView :: Radix1Tree a -> Maybe (ViewR1 a) Source #

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

Full tree

Size

null :: Radix1Tree a -> Bool Source #

\(\mathcal{O}(1)\). Check if the tree is empty.

size :: Radix1Tree a -> Int Source #

\(\mathcal{O}(n)\). Calculate the number of elements stored in the tree. The returned number is guaranteed to be non-negative.

Extend

prefix :: Feed1 -> RadixTree a -> Radix1Tree a Source #

\(\mathcal{O}(x)\). Prefix the root of the tree with the given key.

Map

map :: (a -> b) -> Radix1Tree a -> Radix1Tree b Source #

\(\mathcal{O}(n)\). Apply a function to every value in the tree.

map' :: (a -> b) -> Radix1Tree a -> Radix1Tree b Source #

\(\mathcal{O}(n)\). Apply a function to every value in the tree.

mapWithKey :: (Build1 -> a -> b) -> Radix1Tree a -> Radix1Tree b Source #

\(\mathcal{O}(n)\). Apply a function to every value in the tree.

mapWithKey' :: (Build1 -> a -> b) -> Radix1Tree a -> Radix1Tree b Source #

\(\mathcal{O}(n)\). Apply a function to every value in the tree.

Fold

Left-to-right

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

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

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

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

foldlWithKey :: (b -> Build1 -> a -> b) -> b -> Radix1Tree a -> b Source #

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

foldlWithKey' :: (b -> Build1 -> a -> b) -> b -> Radix1Tree a -> b Source #

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

Right-to-left

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

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

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

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

foldrWithKey :: (Build1 -> a -> b -> b) -> b -> Radix1Tree a -> b Source #

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

foldrWithKey' :: (Build1 -> a -> b -> b) -> b -> Radix1Tree a -> b Source #

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

Monoid

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

\(\mathcal{O}(n_M)\). Map each element in the tree to a monoid and combine the results.

foldMapWithKey :: Monoid m => (Build1 -> a -> m) -> Radix1Tree a -> m Source #

\(\mathcal{O}(n_M)\). Map each element in the tree to a monoid and combine the results.

Traverse

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

\(\mathcal{O}(n)\). Map each element in the tree to an action, evaluate these actions left-to-right and collect the results.

traverseWithKey :: Applicative f => (Build1 -> a -> f b) -> Radix1Tree a -> f (Radix1Tree b) Source #

\(\mathcal{O}(n)\). Map each element in the tree to an action, evaluate these actions left-to-right and collect the results.

Filter

One side

filter :: (a -> Bool) -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(n)\). Filter values that satisfy the value predicate.

filterWithKey :: (Build1 -> a -> Bool) -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(n)\). Filter values that satisfy the value predicate.

mapMaybe :: (a -> Maybe b) -> Radix1Tree a -> Radix1Tree b Source #

\(\mathcal{O}(n)\). Apply a function to every value in the tree and create one out of Just values.

The Maybe is evaluated to WHNF.

mapMaybeWithKey :: (Build1 -> a -> Maybe b) -> Radix1Tree a -> Radix1Tree b Source #

\(\mathcal{O}(n)\). Apply a function to every value in the tree and create one out of Just values.

The Maybe is evaluated to WHNF.

Both sides

partition :: (a -> Bool) -> Radix1Tree a -> Split1 a a Source #

\(\mathcal{O}(n)\). Split1 the tree into two, such that values that satisfy the predicate are on the left and values that do not are on the right.

partitionWithKey :: (Build1 -> a -> Bool) -> Radix1Tree a -> Split1 a a Source #

\(\mathcal{O}(n)\). Split1 the tree into two, such that values that satisfy the predicate are on the left and values that do not are on the right.

mapEither :: (a -> Either b c) -> Radix1Tree a -> Split1 b c Source #

\(\mathcal{O}(n)\). Apply a function to every value in the tree and create two trees, one out of Left results and one out of Right ones.

The Either is evaluated to WHNF.

mapEitherWithKey :: (Build1 -> a -> Either b c) -> Radix1Tree a -> Split1 b c Source #

\(\mathcal{O}(n)\). Apply a function to every value in the tree and create two trees, one out of Left results and one out of Right ones.

The Either is evaluated to WHNF.

Comparison

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 :: (a -> b -> Bool) -> Radix1Tree a -> Radix1Tree b -> PartialOrdering Source #

\(\mathcal{O}(n_A k_A + n_B k_B)\). Compare two trees with respect to set inclusion, using the given equality function for intersecting keys. If any intersecting keys hold unequal values, the trees are Incomparable.

Union

union :: Radix1Tree a -> Radix1Tree a -> Radix1Tree a Source #

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

unionL :: Radix1Tree a -> Radix1Tree a -> Radix1Tree a Source #

\(\mathcal{O}(n_A k_A + n_B k_B)\). Left-biased union of two trees.

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

\(\mathcal{O}(n_A k_A + n_B k_B)\). Union of two trees with a combining function.

New values are evaluated to WHNF.

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

\(\mathcal{O}(n_A k_A + n_B k_B)\). Union of two trees with a combining function.

New values are evaluated to WHNF.

Difference

difference :: Radix1Tree a -> Radix1Tree b -> Radix1Tree a Source #

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

differenceWith :: (a -> b -> Maybe a) -> Radix1Tree a -> Radix1Tree b -> Radix1Tree a Source #

\(\mathcal{O}(n_A k_A + n_B k_B)\). Difference of two trees with a combining function.

The Maybe is evaluated to WHNF.

differenceWithKey :: (Build1 -> a -> b -> Maybe a) -> Radix1Tree a -> Radix1Tree b -> Radix1Tree a Source #

\(\mathcal{O}(n_A k_A + n_B k_B)\). Difference of two trees with a combining function.

The Maybe is evaluated to WHNF.

Intersection

disjoint :: Radix1Tree a -> Radix1Tree b -> Bool Source #

\(\mathcal{O}(n_A k_A + n_B k_B)\). Determine whether two trees' key sets are disjoint.

intersection :: Radix1Tree a -> Radix1Tree a -> Radix1Tree a Source #

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

intersectionL :: Radix1Tree a -> Radix1Tree b -> Radix1Tree a Source #

\(\mathcal{O}(n_A k_A + n_B k_B)\). Left-biased intersection of two trees.

intersectionWith' :: (a -> b -> c) -> Radix1Tree a -> Radix1Tree b -> Radix1Tree c Source #

\(\mathcal{O}(n_A k_A + n_B k_B)\). Intersection of two trees with a combining function.

New values are evaluated to WHNF.

intersectionWithKey' :: (Build1 -> a -> b -> c) -> Radix1Tree a -> Radix1Tree b -> Radix1Tree c Source #

\(\mathcal{O}(n_A k_A + n_B k_B)\). Intersection of two trees with a combining function.

New values are evaluated to WHNF.

Merge

See merge.