uhc-util-0.1.6.7: UHC utilities

Safe HaskellSafe
LanguageHaskell98

UHC.Util.TreeTrie

Contents

Description

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.

Synopsis

Key into TreeTrie

type TreeTrieMpKey k = [TreeTrieMp1Key k] Source #

The key into a map used internally by the trie

type TreeTrieKey k = [TreeTrieMpKey k] Source #

The key used externally to index into a trie

type family TrTrKey x :: * Source #

Instances

type TrTrKey (Maybe x) Source # 
type TrTrKey (Maybe x) = TTKey x

ppTreeTrieKey :: PP k => TreeTrieKey k -> PP_Doc Source #

Pretty print TrieKey

ttkSingleton :: TreeTrie1Key k -> TreeTrieKey k Source #

Make singleton, which should at end be stripped from bottom layer of empty TTM1K []

ttkAdd' :: TreeTrie1Key k -> TreeTrieKey k -> TreeTrieKey k Source #

Add a new layer with single node on top, combining the rest.

ttkAdd :: TreeTrie1Key k -> [TreeTrieKey k] -> TreeTrieKey k Source #

Add a new layer with single node on top, combining the rest. length ks >= 2

ttkChildren :: [TreeTrieKey k] -> TreeTrieKey k Source #

Construct intermediate structure for children for a new Key length ks >= 2

ttkFixate :: TreeTrieKey k -> TreeTrieKey k Source #

Fixate by removing lowest layer empty children

ttkParentChildren :: TreeTrieKey k -> (TreeTrie1Key k, TreeTrieKey k) Source #

Split key into parent and children components, inverse of ttkAdd'

Keyable

class TreeTrieKeyable x where Source #

Keyable values, i.e. capable of yielding a TreeTrieKey for retrieval from a trie

Minimal complete definition

toTreeTrieKey

TreeTrie

data TreeTrie k v Source #

The trie structure, branching out on (1) kind, (2) nr of children, (3) actual key

Instances

(Show k, Show v) => Show (TreeTrie k v) Source # 

Methods

showsPrec :: Int -> TreeTrie k v -> ShowS #

show :: TreeTrie k v -> String #

showList :: [TreeTrie k v] -> ShowS #

(PP k, PP v) => PP (TreeTrie k v) Source # 

Methods

pp :: TreeTrie k v -> PP_Doc Source #

ppList :: [TreeTrie k v] -> PP_Doc Source #

(Ord k, Serialize k, Serialize v) => Serialize (TreeTrie k v) Source # 

toList :: TreeTrie k v -> [(TreeTrieKey k, v)] Source #

fromListByKeyWith :: Ord k => (v -> v -> v) -> [(TreeTrieKey k, v)] -> TreeTrie k v Source #

fromList :: Ord k => [(TreeTrieKey k, v)] -> TreeTrie k v Source #

Lookup

lookupPartialByKey' :: forall k v v'. (PP k, Ord k) => (TreeTrieKey k -> v -> v') -> TreeTrieLookup -> TreeTrieKey k -> TreeTrie k v -> ([v'], Maybe v') Source #

Normal lookup for exact match + partial matches (which require some sort of further unification, determining whether it was found)

lookupByKey :: (PP k, Ord k) => TreeTrieKey k -> TreeTrie k v -> Maybe v Source #

lookup :: (PP k, Ord k) => TreeTrieKey k -> TreeTrie k v -> Maybe v Source #

lookupResultToList :: ([v], Maybe v) -> [v] Source #

Convert the lookup result to a list of results

Properties/observations

elems :: TreeTrie k v -> [v] Source #

Construction

singleton :: Ord k => TreeTrieKey k -> v -> TreeTrie k v Source #

unionWith :: Ord k => (v -> v -> v) -> TreeTrie k v -> TreeTrie k v -> TreeTrie k v Source #

union :: Ord k => TreeTrie k v -> TreeTrie k v -> TreeTrie k v Source #

unionsWith :: Ord k => (v -> v -> v) -> [TreeTrie k v] -> TreeTrie k v Source #

unions :: Ord k => [TreeTrie k v] -> TreeTrie k v Source #

insertByKeyWith :: Ord k => (v -> v -> v) -> TreeTrieKey k -> v -> TreeTrie k v -> TreeTrie k v Source #

insertByKey :: Ord k => TreeTrieKey k -> v -> TreeTrie k v -> TreeTrie k v Source #

Deletion

delete :: Ord k => TreeTrieKey k -> TreeTrie k v -> TreeTrie k v Source #