generic-trie-0.1: A map, where the keys may be complex structured data.

Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.GenericTrie

Contents

Description

This module implements an interface for working with "tries". A key in the trie represents a distinct path through the trie. This can provide benefits when using very large and possibly very similar keys where comparing for order can become expensive, and storing the various keys could be inefficient.

For primitive types like Int, this library will select efficient implementations automatically.

All methods of TrieKey can be derived automatically using a Generic instance.

data Demo = DemoC1 Int | DemoC2 Int Char  deriving Generic

instance TrieKey Demo

Synopsis

Trie interface

newtype Trie k a Source

Effectively an associated datatype of tries indexable by keys of type k. By using a separate newtype wrapper around the associated type synonym we're able to use the same MkTrie constructor for all of the generic implementations while still getting the injectivity of a new type.

Constructors

MkTrie (TrieRep k a) 

Instances

TrieKey k => Functor (Trie k) 
TrieKey k => Foldable (Trie k) 
TrieKey k => Traversable (Trie k) 
(Show a, TrieKey k) => Show (Trie k a) 

alter :: TrieKey k => k -> (Maybe a -> Maybe a) -> Trie k a -> Trie k a Source

Alter the values of a trie. The function will take the value stored as the given key if one exists and should return a value to insert at that location or Nothing to delete from that location.

member :: TrieKey k => k -> Trie k a -> Bool Source

Returns True when the Trie has a value stored at the given key.

notMember :: TrieKey k => k -> Trie k a -> Bool Source

Returns False when the Trie has a value stored at the given key.

fromList :: TrieKey k => [(k, v)] -> Trie k v Source

Construct a trie from a list of key/value pairs

class TrieKey k where Source

Keys that support prefix-trie map operations.

All operations can be automatically derived from a Generic instance.

Minimal complete definition

Nothing

Associated Types

type TrieRep k a Source

Type of the representation of tries for this key.

Methods

empty :: Trie k a Source

Construct an empty trie

trieNull :: Trie k a -> Bool Source

Test for an empty trie

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

Lookup element from trie

insert :: k -> a -> Trie k a -> Trie k a Source

Insert element into trie

delete :: k -> Trie k a -> Trie k a Source

Delete element from trie

singleton :: k -> a -> Trie k a Source

Construct a trie holding a single value

trieMap :: (a -> b) -> Trie k a -> Trie k b Source

Apply a function to all values stored in a trie

trieFold :: (a -> b -> b) -> Trie k a -> b -> b Source

Fold all the values store in a trie

trieTraverse :: Applicative f => (a -> f b) -> Trie k a -> f (Trie k b) Source

Traverse the values stored in a trie

trieShowsPrec :: Show a => Int -> Trie k a -> ShowS Source

Show the representation of a trie

Instances

TrieKey Bool 
TrieKey Char

'Char tries are implemented with IntMap.

TrieKey Int

Int tries are implemented with IntMap.

TrieKey Integer

Integer tries are implemented with Map.

TrieKey () 
TrieKey k => TrieKey [k] 
TrieKey k => TrieKey (Maybe k) 
(TrieKey a, TrieKey b) => TrieKey (Either a b) 
(TrieKey a, TrieKey b) => TrieKey (a, b) 
(TrieKey a, TrieKey b, TrieKey c) => TrieKey (a, b, c) 

Generic derivation implementation

type TrieRepDefault k a = Maybe (GTrie (Rep k) a) Source

The default implementation of a TrieRep is GTrie wrapped in a Maybe. This wrapping is due to the GTrie being a non-empty trie allowing all the of the "emptiness" to be represented at the top level for any given generically implemented key.

class GTrieKey f where Source

TrieKey operations on Generic representations used to provide the default implementations of tries.

Methods

gtrieLookup :: f p -> GTrie f a -> Maybe a Source

gtrieInsert :: f p -> a -> GTrie f a -> GTrie f a Source

gtrieSingleton :: f p -> a -> GTrie f a Source

gtrieDelete :: f p -> GTrie f a -> Maybe (GTrie f a) Source

gtrieMap :: (a -> b) -> GTrie f a -> GTrie f b Source

gtrieFold :: (a -> b -> b) -> GTrie f a -> b -> b Source

gtrieTraverse :: Applicative m => (a -> m b) -> GTrie f a -> m (GTrie f b) Source

Instances

GTrieKey V1

Tries of types without constructors are represented by a unit.

GTrieKey U1

Tries of constructors without fields are represented by a single value.

TrieKey k => GTrieKey (K1 i k)

Generic fields are represented by tries of the field type.

(GTrieKey f, GTrieKey g) => GTrieKey ((:+:) f g)

Generic sums are represented by up to a pair of sub-tries.

(GTrieKey f, GTrieKey g) => GTrieKey ((:*:) f g)

Generic products are represented by tries of tries.

GTrieKey f => GTrieKey (M1 i c f)

Generic metadata is skipped in trie representation and operations.

data family GTrie f a Source

Mapping of generic representation of keys to trie structures.

Instances

(Show a, GTrieKeyShow f) => Show (GTrie f a) 
data GTrie V1 = VTrie 
data GTrie U1 = UTrie a 
data GTrie (K1 i k) = KTrie (Trie k a) 
data GTrie ((:+:) f g)  
data GTrie ((:*:) f g) = PTrie (GTrie f (GTrie g a)) 
data GTrie (M1 i c f) = MTrie {}