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

Data.RadixTree.Word8.Lazy

Description

LazyRadixTree a is a spine-lazy radix tree that uses byte-aligned byte sequences as keys.

Laziness

Evaluating any particular entry in the tree to WHNF forces the evaluation of the part of the spine leading up to that entry to normal form.

Performance

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

Laziness-amortized functions specify two time complexities: time to construct the return value (denoted with a \(\texttt{+}\)) and time to fully apply the function to the tree.

\(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 Feeds 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 (feedByteString bs)

N.B. To inline properly functions that consume Feeds 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 LazyRadixTree = RadixTree Source #

Convenience type synonym.

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.Lazy

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.Lazy

Methods

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

Show1 RadixTree Source # 
Instance details

Defined in Data.RadixNTree.Word8.Lazy

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.Lazy

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.Lazy

Methods

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

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

NFData1 RadixTree Source # 
Instance details

Defined in Data.RadixNTree.Word8.Lazy

Methods

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

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

Defined in Data.RadixNTree.Word8.Lazy

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

Defined in Data.RadixNTree.Word8.Lazy

Methods

rnf :: RadixTree a -> () #

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

Defined in Data.RadixNTree.Word8.Lazy

Methods

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

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

Key

Construct

empty :: RadixTree a Source #

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

singleton :: Feed -> a -> RadixTree a Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(x)\). Tree with a single entry.

Convert

toStrict :: LazyRadixTree a -> StrictRadixTree a Source #

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

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

Single-key

Lookup

lookup :: Feed -> RadixTree a -> Maybe a Source #

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

find :: a -> Feed -> RadixTree 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 :: Feed -> RadixTree a -> Bool Source #

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

subtree :: Feed -> RadixTree 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.Lazy

Methods

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

show :: Cursor a -> String #

showList :: [Cursor a] -> ShowS #

cursor :: RadixTree a -> Cursor a Source #

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

move :: Feed -> 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 :: Feed -> a -> RadixTree a -> RadixTree a Source #

\(\mathcal{O}(1)\texttt{+}, \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) -> Feed -> a -> RadixTree a -> RadixTree a Source #

\(\mathcal{O}(1)\texttt{+}, \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.

Map

adjust :: (a -> a) -> Feed -> RadixTree a -> RadixTree a Source #

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

Delete

delete :: Feed -> RadixTree a -> RadixTree a Source #

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

prune :: Openness -> Feed -> RadixTree a -> RadixTree a Source #

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

Update

update :: (a -> Maybe a) -> Feed -> RadixTree a -> RadixTree a Source #

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

alter :: (Maybe a -> Maybe a) -> Feed -> RadixTree a -> RadixTree a Source #

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

shape :: (RadixTree a -> RadixTree a) -> Feed -> RadixTree a -> RadixTree a Source #

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

Take

splitLookup :: Feed -> RadixTree a -> (RadixTree a, Maybe a, RadixTree a) Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(\min(x,k))\). Split 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 Lookup a Source #

Key together with the value.

Constructors

Lookup !Build a 

Instances

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

Defined in Data.RadixNTree.Word8.Common

Methods

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

show :: Lookup a -> String #

showList :: [Lookup a] -> ShowS #

lookupL :: Openness -> Feed -> RadixTree a -> Maybe (Lookup 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 -> Feed -> RadixTree a -> Maybe (Lookup 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 -> Feed -> RadixTree a -> RadixTree a Source #

\(\mathcal{O}(1)\texttt{+}, \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 :: (Build -> a -> a) -> Openness -> Feed -> RadixTree a -> RadixTree a Source #

\(\mathcal{O}(1)\texttt{+}, \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.

Right

adjustR :: (a -> a) -> Openness -> Feed -> RadixTree a -> RadixTree a Source #

\(\mathcal{O}(1)\texttt{+}, \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 :: (Build -> a -> a) -> Openness -> Feed -> RadixTree a -> RadixTree a Source #

\(\mathcal{O}(1)\texttt{+}, \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.

Update

Left

updateL :: (a -> Maybe a) -> Openness -> Feed -> RadixTree a -> RadixTree a Source #

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

updateLWithKey :: (Build -> a -> Maybe a) -> Openness -> Feed -> RadixTree a -> RadixTree a Source #

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

Right

updateR :: (a -> Maybe a) -> Openness -> Feed -> RadixTree a -> RadixTree a Source #

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

updateRWithKey :: (Build -> a -> Maybe a) -> Openness -> Feed -> RadixTree a -> RadixTree a Source #

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

Take

Left

takeL :: Openness -> Feed -> RadixTree a -> RadixTree a Source #

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

splitL :: Openness -> Feed -> RadixTree a -> (RadixTree a, RadixTree a) Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(\min(x,k))\). Split 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 -> Feed -> RadixTree a -> RadixTree a Source #

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

Edges

Lookup

Min

lookupMin :: RadixTree a -> Maybe a Source #

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

lookupMinWithKey :: RadixTree a -> Maybe (Lookup a) Source #

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

Max

lookupMax :: RadixTree a -> Maybe a Source #

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

lookupMaxWithKey :: RadixTree a -> Maybe (Lookup a) Source #

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

Map

Min

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

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

adjustMinWithKey :: (Build -> a -> a) -> RadixTree a -> RadixTree a Source #

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

Max

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

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

adjustMaxWithKey :: (Build -> a -> a) -> RadixTree a -> RadixTree a Source #

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

Delete

deleteMin :: RadixTree a -> RadixTree a Source #

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

deleteMax :: RadixTree a -> RadixTree a Source #

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

Update

Min

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

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

updateMinWithKey :: (Build -> a -> Maybe a) -> RadixTree a -> RadixTree a Source #

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

Max

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

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

updateMaxWithKey :: (Build -> a -> Maybe a) -> RadixTree a -> RadixTree a Source #

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

View

Min

data ViewL a Source #

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

Constructors

ViewL !Build a !(RadixTree a) 

Instances

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

Defined in Data.RadixNTree.Word8.Lazy

Methods

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

show :: ViewL a -> String #

showList :: [ViewL a] -> ShowS #

minView :: RadixTree a -> Maybe (ViewL a) Source #

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

Max

data ViewR a Source #

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

Constructors

ViewR !(RadixTree a) !Build a 

Instances

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

Defined in Data.RadixNTree.Word8.Lazy

Methods

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

show :: ViewR a -> String #

showList :: [ViewR a] -> ShowS #

maxView :: RadixTree a -> Maybe (ViewR a) Source #

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

Full tree

Size

null :: RadixTree a -> Bool Source #

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

size :: RadixTree 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 :: Feed -> RadixTree a -> RadixTree a Source #

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

Map

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

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

mapWithKey :: (Build -> a -> b) -> RadixTree a -> RadixTree b Source #

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

Fold

Left-to-right

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

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

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

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

foldlWithKey :: (b -> Build -> a -> b) -> b -> RadixTree a -> b Source #

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

foldlWithKey' :: (b -> Build -> a -> b) -> b -> RadixTree a -> b Source #

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

Right-to-left

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

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

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

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

foldrWithKey :: (Build -> a -> b -> b) -> b -> RadixTree a -> b Source #

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

foldrWithKey' :: (Build -> a -> b -> b) -> b -> RadixTree a -> b Source #

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

Monoid

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

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

foldMapWithKey :: Monoid m => (Build -> a -> m) -> RadixTree 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) -> RadixTree a -> f (RadixTree 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 => (Build -> a -> f b) -> RadixTree a -> f (RadixTree 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) -> RadixTree a -> RadixTree a Source #

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

filterWithKey :: (Build -> a -> Bool) -> RadixTree a -> RadixTree a Source #

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

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

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

mapMaybeWithKey :: (Build -> a -> Maybe b) -> RadixTree a -> RadixTree b Source #

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

Both sides

partition :: (a -> Bool) -> RadixTree a -> (RadixTree a, RadixTree a) Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(n)\). Split 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 :: (Build -> a -> Bool) -> RadixTree a -> (RadixTree a, RadixTree a) Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(n)\). Split 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) -> RadixTree a -> (RadixTree b, RadixTree c) Source #

\(\mathcal{O}(1)\texttt{+}, \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.

mapEitherWithKey :: (Build -> a -> Either b c) -> RadixTree a -> (RadixTree b, RadixTree c) Source #

\(\mathcal{O}(1)\texttt{+}, \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.

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) -> RadixTree a -> RadixTree 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 :: RadixTree a -> RadixTree a -> RadixTree a Source #

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

unionL :: RadixTree a -> RadixTree a -> RadixTree a Source #

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

unionWith :: (a -> a -> a) -> RadixTree a -> RadixTree a -> RadixTree a Source #

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

unionWithKey :: (Build -> a -> a -> a) -> RadixTree a -> RadixTree a -> RadixTree a Source #

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

Difference

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

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

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

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

differenceWithKey :: (Build -> a -> b -> Maybe a) -> RadixTree a -> RadixTree b -> RadixTree a Source #

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

Intersection

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

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

intersection :: RadixTree a -> RadixTree a -> RadixTree a Source #

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

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

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

intersectionWith :: (a -> b -> c) -> RadixTree a -> RadixTree b -> RadixTree c Source #

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

intersectionWithKey :: (Build -> a -> b -> c) -> RadixTree a -> RadixTree b -> RadixTree c Source #

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

Merge

See merge.