Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Trie a
- valid :: Trie a -> Bool
- lookup :: Bytes -> Trie a -> Maybe a
- lookupTrie :: Bytes -> Trie a -> Trie a
- lookupPrefixes :: Bytes -> Trie a -> [a]
- multiFindReplace :: Semigroup b => (Bytes -> b) -> (a -> b) -> Trie a -> Bytes -> b
- search :: Trie a -> Bytes -> Bool
- replace :: Trie Bytes -> Bytes -> Chunks
- stripPrefix :: Trie a -> Bytes -> Maybe (a, Bytes)
- stripPrefixWithKey :: forall a. Trie a -> Bytes -> Maybe ((Bytes, a), Bytes)
- null :: Trie a -> Bool
- size :: Trie a -> Int
- empty :: Trie a
- singleton :: Bytes -> a -> Trie a
- fromList :: [(Bytes, a)] -> Trie a
- toList :: Trie a -> [(Bytes, a)]
- foldl' :: (b -> a -> b) -> b -> Trie a -> b
- traverse_ :: Applicative m => (a -> m b) -> Trie a -> m ()
- insert :: Bytes -> a -> Trie a -> Trie a
- insertWith :: (a -> a -> a) -> Bytes -> a -> Trie a -> Trie a
- delete :: Bytes -> Trie a -> Trie a
- union :: Trie a -> Trie a -> Trie a
- unionWith :: (a -> a -> a) -> Trie a -> Trie a -> Trie a
- append :: Semigroup a => Trie a -> Trie a -> Trie a
- prepend :: Bytes -> Trie a -> Trie a
Trie Type
Tries implemented using a 256-entry bitmap as given in Data.Map.Word8. This means that each branch point can be navigated with only some bit manipulations and adding an offset. On sparse data, this should save a lot of space relative to holding a 256-entry pointer array.
This data type has Tip
, Run
, and Branch
nodes.
Branches always have at least two children,
and Runs always have at least one byte.
Leaves are Tip
s.
Once the invariants are met (see below),
there is exactly one Trie
representation for each trie.
In each constructor, the U.Maybe a
is a possible entry;
it comes before any child bytes.
INVARIANT: The Run constructor never has a linear child. Linear nodes are those with no value and exactly one child, which in this implementation is only valueless runs. INVARIANT: The Run constructor never has zero bytes. INVARIANT: The Branch constructor has at least two children. INVARIANT: No child of a node has size zero. That includes: The next node after a run is never null. No child of a branch is ever null.
Query
Lookup
lookupTrie :: Bytes -> Trie a -> Trie a Source #
Lookup the trie at the Bytes
key in the trie. Returns the subtrie
at this position.
>>>
(k1 <> k2 == k) ==> (lookup k v t == lookup k2 (lookupTrie k1 t))
lookupPrefixes :: Bytes -> Trie a -> [a] Source #
Lookup the value at the Bytes
key in the trie. Returns the value
of the exact match and the values for any keys that are prefixes of
the search key. The shortest prefix is first. The exact match (if there
is one) is last.
Search
:: Semigroup b | |
=> (Bytes -> b) | construct a portion of the result from unmatched bytes |
-> (a -> b) | construct a replacement from the found value |
-> Trie a | the dictionary of all replacements |
-> Bytes | input to be edited |
-> b | result of replacement |
The raison-d'etre of this library: repeatedly search in a byte string for the longest of multiple patterns and make replacements.
stripPrefix :: Trie a -> Bytes -> Maybe (a, Bytes) Source #
Find the longest prefix of the input Bytes
which has a value in the trie.
Returns the associated value and the remainder of the input after the prefix.
stripPrefixWithKey :: forall a. Trie a -> Bytes -> Maybe ((Bytes, a), Bytes) Source #
Find the longest prefix of the input Bytes
which has a value in the trie.
Returns the prefix and associated value found as a key/value tuple,
and also the remainder of the input after the prefix.
Size
Construction
Conversion
fromList :: [(Bytes, a)] -> Trie a Source #
Build a trie from a list of key/value pairs. If more than one value for the same key appears, the last value for that key is retained.
toList :: Trie a -> [(Bytes, a)] Source #
Convert the trie to a list of key/value pairs. The resulting list has its keys sorted in ascending order.
traverse_ :: Applicative m => (a -> m b) -> Trie a -> m () Source #
Insertion
insert :: Bytes -> a -> Trie a -> Trie a Source #
Insert a new key/value into the trie.
If the key is already present in the trie, the associated value is
replaced with the new one.
insert
is equivalent to insertWith
const
.
insertWith :: (a -> a -> a) -> Bytes -> a -> Trie a -> Trie a Source #
Insert with a function, combining new value and old value.
will insert the pair insertWith
f key value trie(key, value)
into trie
if key
does not exist in the trie.
If the key does exist, the function will insert the pair
(key, f new_value old_value)
.
Deletion
Combine
union :: Trie a -> Trie a -> Trie a Source #
The left-biased union of the two tries.
It prefers the first when duplicate keys are encountered,
i.e. union == unionWith const
.