Safe Haskell | None |
---|---|
Language | Haskell2010 |
A TreeTrie is a search structure where the key actually consists of a tree of keys, represented as a list of layers in the tree, 1 for every depth, starting at the top, which are iteratively used for searching. The search structure for common path/prefixes is shared, the trie branches to multiple corresponding to available children, length equality of children is used in searching (should match)
The TreeTrie structure implemented in this module deviates from the usual TreeTrie implementations in that it allows wildcard matches besides the normal full match. The objective is to also be able to retrieve values for which (at insertion time) it has been indicated that part does not need full matching. This intentionally is similar to unification, where matching on a variable will succeed for arbitrary values. Unification is not the job of this TreeTrie implementation, but by returning partial matches as well, a list of possible match candidates is returned.
- data PreKey1 x
- data Key k
- type family TrTrKey x :: *
- class TreeTrieKeyable x where
- toTreeTrieKey :: TreeTrieKeyable x => x -> Key (TrTrKey x)
- prekey1 :: TrTrKey x -> PreKey1 x
- prekey1Wild :: PreKey1 x
- prekey1Nil :: PreKey1 x
- prekey1Delegate :: (TrTrKey y ~ TrTrKey x, TreeTrieKeyable y) => y -> PreKey1 x
- prekey1WithChildren :: (TrTrKey y ~ TrTrKey x, TreeTrieKeyable y) => TrTrKey x -> [y] -> PreKey1 x
- prekey1With2Children :: (TrTrKey y1 ~ TrTrKey x, TrTrKey y2 ~ TrTrKey x, TreeTrieKeyable y1, TreeTrieKeyable y2) => TrTrKey x -> y1 -> y2 -> PreKey1 x
- prekey1WithChild :: (TrTrKey y ~ TrTrKey x, TreeTrieKeyable y) => TrTrKey x -> y -> PreKey1 x
- data TreeTrie k v
- type TTCtxt a = Ord a
- emptyTreeTrie :: TTCtxt k => TreeTrie k v
- empty :: TTCtxt k => TreeTrie k v
- toListByKey :: TTCtxt k => TreeTrie k v -> [(Key k, v)]
- toList :: TTCtxt k => TreeTrie k v -> [(Key k, v)]
- fromListByKeyWith :: Ord k => (v -> v -> v) -> [(Key k, v)] -> TreeTrie k v
- fromList :: Ord k => [(Key k, v)] -> TreeTrie k v
- lookup :: Ord k => Key k -> TreeTrie k v -> LkRes v
- lookupResultToList :: LkRes v -> [v]
- isEmpty :: TTCtxt k => TreeTrie k v -> Bool
- null :: TTCtxt k => TreeTrie k v -> Bool
- singleton :: Ord k => Key k -> v -> TreeTrie k v
- singletonKeyable :: (Ord (TrTrKey v), TreeTrieKeyable v) => v -> TreeTrie (TrTrKey v) v
- unionWith :: Ord k => (v -> v -> v) -> TreeTrie k v -> TreeTrie k v -> TreeTrie k v
- union :: Ord k => TreeTrie k v -> TreeTrie k v -> TreeTrie k v
- unionsWith :: Ord k => (v -> v -> v) -> [TreeTrie k v] -> TreeTrie k v
- unions :: Ord k => [TreeTrie k v] -> TreeTrie k v
- insertByKeyWith :: Ord k => (v -> v -> v) -> Key k -> v -> TreeTrie k v -> TreeTrie k v
- insertByKey :: Ord k => Key k -> v -> TreeTrie k v -> TreeTrie k v
Key into TreeTrie
Full key
Keyable
class TreeTrieKeyable x where Source #
Keyable values, i.e. capable of yielding a TreeTrieKey for retrieval from a trie
toTreeTriePreKey1 :: x -> PreKey1 x Source #
toTreeTrieKey :: TreeTrieKeyable x => x -> Key (TrTrKey x) Source #
prekey1Wild :: PreKey1 x Source #
Wildcard, matching anything
prekey1Nil :: PreKey1 x Source #
No key
prekey1Delegate :: (TrTrKey y ~ TrTrKey x, TreeTrieKeyable y) => y -> PreKey1 x Source #
No key, delegate to next layer
prekey1WithChildren :: (TrTrKey y ~ TrTrKey x, TreeTrieKeyable y) => TrTrKey x -> [y] -> PreKey1 x Source #
Key with children
prekey1With2Children :: (TrTrKey y1 ~ TrTrKey x, TrTrKey y2 ~ TrTrKey x, TreeTrieKeyable y1, TreeTrieKeyable y2) => TrTrKey x -> y1 -> y2 -> PreKey1 x Source #
Key with 2 children
prekey1WithChild :: (TrTrKey y ~ TrTrKey x, TreeTrieKeyable y) => TrTrKey x -> y -> PreKey1 x Source #
Key with single child
TreeTrie
The trie structure, branching out on (1) kind, (2) nr of children, (3) actual key
emptyTreeTrie :: TTCtxt k => TreeTrie k v Source #
Lookup
lookup :: Ord k => Key k -> TreeTrie k v -> LkRes v Source #
Lookup giving back possible precise result and values found whilst descending into trie (corresponding to wildcard in key in trie) and remaining when key is exhausted (corresponding to wildcard in key)
lookupResultToList :: LkRes v -> [v] Source #
Convert the lookup result to a list of results
Properties/observations
Construction
singletonKeyable :: (Ord (TrTrKey v), TreeTrieKeyable v) => v -> TreeTrie (TrTrKey v) v Source #