vcache-trie-0.2.3: patricia tries modeled above VCache

Safe HaskellNone
LanguageHaskell2010

Data.VCache.Trie

Description

A compact bytestring trie implemented above VCache.

Synopsis

Documentation

data Trie a Source

A trie data structure with bytestring keys, above VCache.

A trie supports keys of arbitrary size, though very large keys may cause performance degradation. Values are directly serialized into nodes, so very large values should use indirection.

Instances

empty :: VSpace -> Trie a Source

Construct Trie with no elements.

singleton :: VCacheable a => VSpace -> ByteString -> a -> Trie a Source

Construct Trie with one element.

null :: Trie a -> Bool Source

O(1), test whether trie is empty.

size :: Trie a -> Int Source

O(n). Compute size of the trie.

lookup :: ByteString -> Trie a -> Maybe a Source

Lookup an object by key

lookup' :: DerefNode a -> ByteString -> Trie a -> Maybe a Source

Lookup an object by key with user-provided deref.

prefixKeys :: VCacheable a => ByteString -> Trie a -> Trie a Source

O(1). Add a common prefix to all keys currently in the Trie

lookupPrefix :: VCacheable a => ByteString -> Trie a -> Trie a Source

Obtain a trie rooted at a given prefix.

This operation may need to allocate in VCache, e.g. to delete some fraction of the requested prefix. This isn't optimal for performance.

lookupPrefix' :: VCacheable a => DerefNode a -> ByteString -> Trie a -> Trie a Source

lookup prefix with user-provided deref function.

lookupPrefixNode :: VCacheable a => ByteString -> Trie a -> Maybe (Node a) Source

Obtain a trie node rooted at a given prefix, if any content exists at this prefix. This operation allows some performance benefits compared to lookupPrefix because it never allocates at the VCache layer.

lookupPrefixNode' :: VCacheable a => DerefNode a -> ByteString -> Trie a -> Maybe (Node a) Source

lookup prefix node with user-provided deref function

deletePrefix :: VCacheable a => ByteString -> Trie a -> Trie a Source

Delete all keys sharing a given prefix.

insert :: VCacheable a => ByteString -> a -> Trie a -> Trie a Source

Insert a single key,value pair into the trie, replacing any existing value at that location.

delete :: VCacheable a => ByteString -> Trie a -> Trie a Source

Remove a single key from the trie.

adjust :: VCacheable a => (Maybe a -> Maybe a) -> ByteString -> Trie a -> Trie a Source

Update an element in the Trie with a given function. Capable of inserts, modifies, and deletes.

insertList :: VCacheable a => [(ByteString, a)] -> Trie a -> Trie a Source

Insert a list of (key,value) pairs into the trie. At the moment this is just a linear insert, but it may later be replaced by an efficient batch-insert model. If a key appears more than once in this list, the last entry will win.

deleteList :: VCacheable a => [ByteString] -> Trie a -> Trie a Source

Remove a collection of keys from the trie. At the moment this is just a sequential deletion, but it may later be replaced by a more efficient batch-deletion model.

toList :: Trie a -> [(ByteString, a)] Source

O(n). Obtain a list of (key,val) pairs, sorted by key.

toListBy :: (ByteString -> a -> b) -> Trie a -> [b] Source

elems :: Trie a -> [a] Source

O(n). Obtain list of elements in the trie.

keys :: Trie a -> [ByteString] Source

O(n). Obtain a sorted list of of keys.

foldr :: (a -> b -> b) -> b -> Trie a -> b Source

foldr' :: (a -> b -> b) -> b -> Trie a -> b Source

foldrM :: Monad m => (a -> b -> m b) -> b -> Trie a -> m b Source

foldrWithKey :: (ByteString -> a -> b -> b) -> b -> Trie a -> b Source

foldrWithKey' :: (ByteString -> a -> b -> b) -> b -> Trie a -> b Source

foldrWithKeyM :: Monad m => (ByteString -> a -> b -> m b) -> b -> Trie a -> m b Source

foldl :: (b -> a -> b) -> b -> Trie a -> b Source

foldl' :: (b -> a -> b) -> b -> Trie a -> b Source

foldlM :: Monad m => (b -> a -> m b) -> b -> Trie a -> m b Source

foldlWithKey :: (b -> ByteString -> a -> b) -> b -> Trie a -> b Source

foldlWithKey' :: (b -> ByteString -> a -> b) -> b -> Trie a -> b Source

foldlWithKeyM :: Monad m => (b -> ByteString -> a -> m b) -> b -> Trie a -> m b Source

map :: VCacheable b => (a -> b) -> Trie a -> Trie b Source

mapM :: (VCacheable b, Monad m) => (a -> m b) -> Trie a -> m (Trie b) Source

mapWithKey :: VCacheable b => (ByteString -> a -> b) -> Trie a -> Trie b Source

mapWithKeyM :: (Monad m, VCacheable b) => (ByteString -> a -> m b) -> Trie a -> m (Trie b) Source

toListOnKey :: ByteString -> Trie a -> ([(ByteString, a)], [(ByteString, a)]) Source

Quickly find keys to the left or right of a given key. If the given key is matched, it appears at the head of the right list. The left list is reverse-ordered, finding keys to the left of the requested key.

The intention here is to support efficient ranged searches or lookups. The lists returned are computed lazily.

diff :: Eq a => Trie a -> Trie a -> [(ByteString, Diff a)] Source

Compute differences between two tries. The provided functions determine the difference type for values in just the left or right or both.

data Diff a Source

a simple difference data structure. We're either just in the left, just in the right, or have some simple difference in both (e.g. based on Eq).

Constructors

InL a 
Diff a a 
InR a 

Instances

Eq a => Eq (Diff a) Source 
Show a => Show (Diff a) Source 

validate :: Trie a -> Bool Source

Validate the invariant structure of the Trie. Every node must branch or contain a value.

unsafeTrieAddr :: Trie a -> Word64 Source

Obtain unique address for Trie value. As with VRef addresses, this should be stable while the Trie is reachable, but may change if the value is GC'd and later reconstructed at a new address. Exposed for memoization and similar purposes.

type DerefNode a = VRef (Node a) -> Node a Source

function to dereference a Trie cache node. This improves user control over caching on lookup.