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

Data.Patricia.Word.Lazy

Description

LazyPatricia a is a spine-lazy big-endian PATRICIA tree, a compressed trie with a radix of 2, using Words 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.

\(n\) refers to the number of evaluated entries in the resulting tree. Parts of the tree are denoted using subscripts: \(n_L\) refers to the left side, \(n_R\) to the right side, \(n_I\) to a range (interval), and \(n_M\) to entries collected with the use of a Monoid.

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

Implementation

See the implementation section in Data.Patricia.Word.Strict.

Synopsis

Documentation

type LazyPatricia = Patricia Source #

Convenience synonym.

data Patricia a Source #

Spine-lazy PATRICIA tree.

Instances

Instances details
Foldable Patricia Source # 
Instance details

Defined in Data.Patricia.Word.Lazy.Internal

Methods

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

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

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

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

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

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

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

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

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

toList :: Patricia a -> [a] #

null :: Patricia a -> Bool #

length :: Patricia a -> Int #

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

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

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

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

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

Eq1 Patricia Source # 
Instance details

Defined in Data.Patricia.Word.Lazy.Internal

Methods

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

Read1 Patricia Source # 
Instance details

Defined in Data.Patricia.Word.Lazy.Internal

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Patricia a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Patricia a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Patricia a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Patricia a] #

Show1 Patricia Source # 
Instance details

Defined in Data.Patricia.Word.Lazy.Internal

Methods

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

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

Traversable Patricia Source # 
Instance details

Defined in Data.Patricia.Word.Lazy.Internal

Methods

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

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

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

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

Functor Patricia Source # 
Instance details

Defined in Data.Patricia.Word.Lazy.Internal

Methods

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

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

NFData1 Patricia Source # 
Instance details

Defined in Data.Patricia.Word.Lazy.Internal

Methods

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

Lift a => Lift (Patricia a :: Type) Source # 
Instance details

Defined in Data.Patricia.Word.Lazy.Internal

Methods

lift :: Quote m => Patricia a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Patricia a -> Code m (Patricia a) #

Read a => Read (Patricia a) Source # 
Instance details

Defined in Data.Patricia.Word.Lazy.Internal

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

Defined in Data.Patricia.Word.Lazy.Internal

Methods

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

show :: Patricia a -> String #

showList :: [Patricia a] -> ShowS #

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

Defined in Data.Patricia.Word.Lazy.Internal

Methods

rnf :: Patricia a -> () #

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

Defined in Data.Patricia.Word.Lazy.Internal

Methods

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

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

Construct

empty :: Patricia a Source #

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

singleton :: Word -> a -> Patricia a Source #

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

Convert

toStrict :: LazyPatricia a -> StrictPatricia 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 :: Word -> Patricia a -> Maybe a Source #

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

find :: a -> Word -> Patricia a -> a Source #

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

member :: Word -> Patricia a -> Bool Source #

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

Insert

insert :: Word -> a -> Patricia a -> Patricia a Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(\min(n,W))\). 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) -> Word -> a -> Patricia a -> Patricia a Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(\min(n,W))\). 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) -> Word -> Patricia a -> Patricia a Source #

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

Delete

delete :: Word -> Patricia a -> Patricia a Source #

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

Update

update :: (a -> Maybe a) -> Word -> Patricia a -> Patricia a Source #

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

alter :: (Maybe a -> Maybe a) -> Word -> Patricia a -> Patricia a Source #

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

Take

splitLookup :: Word -> Patricia a -> (Patricia a, Maybe a, Patricia a) Source #

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

Lookup

data Lookup a Source #

Key together with the value.

Constructors

Lookup !Word a 

Instances

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

Defined in Data.Patricia.Word.Common

Methods

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

show :: Lookup a -> String #

showList :: [Lookup a] -> ShowS #

lookupL :: Word -> Patricia a -> Maybe (Lookup a) Source #

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

lookupR :: Word -> Patricia a -> Maybe (Lookup a) Source #

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

Map

Left

adjustL :: (a -> a) -> Word -> Patricia a -> Patricia a Source #

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

adjustLWithKey :: (Word -> a -> a) -> Word -> Patricia a -> Patricia a Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(\min(n,W) + 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) -> Word -> Patricia a -> Patricia a Source #

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

adjustRWithKey :: (Word -> a -> a) -> Word -> Patricia a -> Patricia a Source #

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

Delete

deleteL :: Word -> Patricia a -> Patricia a Source #

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

deleteR :: Word -> Patricia a -> Patricia a Source #

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

Update

Left

updateL :: (a -> Maybe a) -> Word -> Patricia a -> Patricia a Source #

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

updateLWithKey :: (Word -> a -> Maybe a) -> Word -> Patricia a -> Patricia a Source #

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

Right

updateR :: (a -> Maybe a) -> Word -> Patricia a -> Patricia a Source #

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

updateRWithKey :: (Word -> a -> Maybe a) -> Word -> Patricia a -> Patricia a Source #

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

Take

Left

takeL :: Word -> Patricia a -> Patricia a Source #

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

splitL :: Word -> Patricia a -> (Patricia a, Patricia a) Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(\min(n,W))\). Split the tree into two, such that values with keys smaller than or equal to the given one are on the left, and values with keys greater than the given one are on the right.

Right

takeR :: Word -> Patricia a -> Patricia a Source #

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

splitR :: Word -> Patricia a -> (Patricia a, Patricia a) Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(\min(n,W))\). Split the tree into two, such that values with keys smaller than the given one are on the left, and values with keys greater than or equal to the given one are on the right.

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 #

Map

adjustRange :: (a -> a) -> Range -> Patricia a -> Patricia a Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(\min(n,W) + n_I)\). Apply a function to every value for which the key is in the given range.

adjustRangeWithKey :: (Word -> a -> a) -> Range -> Patricia a -> Patricia a Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(\min(n,W) + n_I)\). Apply a function to every value for which the key is in the given range.

Delete

deleteRange :: Range -> Patricia a -> Patricia a Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(\min(n,W))\). Delete values for which keys are in the given range.

Update

updateRange :: (a -> Maybe a) -> Range -> Patricia a -> Patricia a Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(\min(n,W) + n_I)\). Update every value for which the key is in the given range.

updateRangeWithKey :: (Word -> a -> Maybe a) -> Range -> Patricia a -> Patricia a Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(\min(n,W) + n_I)\). Update every value for which the key is in the given range.

Take

takeRange :: Range -> Patricia a -> Patricia a Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(\min(n,W))\). Take values for which keys are in the given range.

Edges

Lookup

Min

lookupMin :: Patricia a -> Maybe a Source #

\(\mathcal{O}(\min(n,W))\). Look up a value at the leftmost key in the tree.

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

\(\mathcal{O}(\min(n,W))\). Look up a value at the leftmost key in the tree.

Max

lookupMax :: Patricia a -> Maybe a Source #

\(\mathcal{O}(\min(n,W))\). Look up a value at the rightmost key in the tree.

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

\(\mathcal{O}(\min(n,W))\). Look up a value at the rightmost key in the tree.

Map

Min

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

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

adjustMinWithKey :: (Word -> a -> a) -> Patricia a -> Patricia a Source #

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

Max

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

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

adjustMaxWithKey :: (Word -> a -> a) -> Patricia a -> Patricia a Source #

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

Delete

deleteMin :: Patricia a -> Patricia a Source #

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

deleteMax :: Patricia a -> Patricia a Source #

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

Update

Min

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

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

updateMinWithKey :: (Word -> a -> Maybe a) -> Patricia a -> Patricia a Source #

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

Max

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

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

updateMaxWithKey :: (Word -> a -> Maybe a) -> Patricia a -> Patricia a Source #

\(\mathcal{O}(1)\texttt{+}, \mathcal{O}(\min(n,W))\). 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 !(Lookup a) !(Patricia a) 

Instances

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

Defined in Data.Patricia.Word.Lazy.Internal

Methods

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

show :: ViewL a -> String #

showList :: [ViewL a] -> ShowS #

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

\(\mathcal{O}(\min(n,W))\). 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 !(Patricia a) !(Lookup a) 

Instances

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

Defined in Data.Patricia.Word.Lazy.Internal

Methods

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

show :: ViewR a -> String #

showList :: [ViewR a] -> ShowS #

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

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

Full tree

Size

null :: Patricia a -> Bool Source #

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

size :: Patricia a -> Int Source #

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

Map

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

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

mapWithKey :: (Word -> a -> b) -> Patricia a -> Patricia 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 -> Patricia a -> b Source #

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

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

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

foldlWithKey :: (b -> Word -> a -> b) -> b -> Patricia a -> b Source #

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

foldlWithKey' :: (b -> Word -> a -> b) -> b -> Patricia a -> b Source #

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

Right-to-left

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

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

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

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

foldrWithKey :: (Word -> a -> b -> b) -> b -> Patricia a -> b Source #

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

foldrWithKey' :: (Word -> a -> b -> b) -> b -> Patricia a -> b Source #

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

Monoid

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

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

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

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

filterWithKey :: (Word -> a -> Bool) -> Patricia a -> Patricia a Source #

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

mapMaybe :: (a -> Maybe b) -> Patricia a -> Patricia 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 :: (Word -> a -> Maybe b) -> Patricia a -> Patricia b Source #

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

Both sides

partition :: (a -> Bool) -> Patricia a -> (Patricia a, Patricia 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 :: (Word -> a -> Bool) -> Patricia a -> (Patricia a, Patricia 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) -> Patricia a -> (Patricia b, Patricia 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 :: (Word -> a -> Either b c) -> Patricia a -> (Patricia b, Patricia 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) -> Patricia a -> Patricia b -> PartialOrdering Source #

\(\mathcal{O}(n_A + n_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 :: Patricia a -> Patricia a -> Patricia a Source #

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

unionL :: Patricia a -> Patricia a -> Patricia a Source #

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

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

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

unionWithKey :: (Word -> a -> a -> a) -> Patricia a -> Patricia a -> Patricia a Source #

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

Difference

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

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

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

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

differenceWithKey :: (Word -> a -> b -> Maybe a) -> Patricia a -> Patricia b -> Patricia a Source #

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

Intersection

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

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

intersection :: Patricia a -> Patricia a -> Patricia a Source #

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

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

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

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

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

intersectionWithKey :: (Word -> a -> b -> c) -> Patricia a -> Patricia b -> Patricia c Source #

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

Merge

See merge.