chr-data-0.1.0.0: Datatypes required for chr library

Safe HaskellNone
LanguageHaskell2010

CHR.Data.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

data Key k Source #

Full key

Instances

Eq k => Eq (Key k) Source # 

Methods

(==) :: Key k -> Key k -> Bool #

(/=) :: Key k -> Key k -> Bool #

Ord k => Ord (Key k) Source # 

Methods

compare :: Key k -> Key k -> Ordering #

(<) :: Key k -> Key k -> Bool #

(<=) :: Key k -> Key k -> Bool #

(>) :: Key k -> Key k -> Bool #

(>=) :: Key k -> Key k -> Bool #

max :: Key k -> Key k -> Key k #

min :: Key k -> Key k -> Key k #

Show k => Show (Key k) Source # 

Methods

showsPrec :: Int -> Key k -> ShowS #

show :: Key k -> String #

showList :: [Key k] -> ShowS #

Generic (Key k) Source # 

Associated Types

type Rep (Key k) :: * -> * #

Methods

from :: Key k -> Rep (Key k) x #

to :: Rep (Key k) x -> Key k #

PP k => PP (Key k) Source # 

Methods

pp :: Key k -> PP_Doc #

ppList :: [Key k] -> PP_Doc #

type Rep (Key k) Source # 
type Rep (Key k)

Keyable

type family TrTrKey x :: * Source #

Instances

type TrTrKey [x] Source # 
type TrTrKey [x] = TrTrKey x
type TrTrKey (Maybe x) Source # 
type TrTrKey (Maybe x) = TrTrKey x

class TreeTrieKeyable x where Source #

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

Minimal complete definition

toTreeTriePreKey1

prekey1 :: TrTrKey x -> PreKey1 x Source #

Single key

prekey1Wild :: PreKey1 x Source #

Wildcard, matching anything

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

data TreeTrie k v Source #

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

Instances

(TTCtxt k, 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 #

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

Methods

pp :: TreeTrie k v -> PP_Doc #

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

type TTCtxt a = Ord a Source #

toListByKey :: TTCtxt k => TreeTrie k v -> [(Key k, v)] Source #

toList :: TTCtxt k => TreeTrie k v -> [(Key k, v)] Source #

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

fromList :: Ord k => [(Key k, v)] -> 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

null :: TTCtxt k => TreeTrie k v -> Bool Source #

Construction

singleton :: Ord k => Key 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) -> Key k -> v -> TreeTrie k v -> TreeTrie k v Source #

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