TrieMap-2.0.3: Automatic type inference of generalized tries with Template Haskell.

Data.TrieMap.Class

Synopsis

Documentation

newtype TMap k a Source

Constructors

TMap 

Fields

getTMap :: TrieMap (Rep k) (Assoc k a)
 

Instances

TKey k => Functor (TMap k) 
TKey k => Foldable (TMap k) 
TKey k => Traversable (TMap k) 
(Eq k, TKey k, Eq a) => Eq (TMap k a) 
(Ord k, TKey k, Ord a) => Ord (TMap k a) 
(Show k, Show a, TKey k) => Show (TMap k a) 
TKey k => Monoid (TMap k a) 

newtype TSet a Source

Constructors

TSet (TMap a ()) 

Instances

TKey a => Eq (TSet a) 
(TKey a, Ord a) => Ord (TSet a) 
(TKey a, Show a) => Show (TSet a) 
TKey a => Monoid (TSet a) 

class (Repr k, TrieKey (Rep k)) => TKey k Source

TKey k is a handy alias for (Repr k, TrieKey (Rep k)). To make a type an instance of TKey, use the methods available in Data.TrieMap.Representation.TH to generate a Repr instance that will satisfy TrieKey (Rep k).

Instances

(Repr k, TrieKey (Rep k)) => TKey k 

class TrieKey k Source

A TrieKey k instance implies that k is a standardized representation for which a generalized trie structure can be derived.

Associated Types

data TrieMap k :: * -> *Source

Instances

TrieKey Word

TrieMap Word a is based on Data.IntMap.

TrieKey ()

TrieMap () a is implemented as Maybe a.

TrieKey k => TrieKey (Vector k)

TrieMap (Vector k) a is a traditional radix trie.

TrieKey (Vector Word)

TrieMap (Vector Word) a is a traditional radix trie specialized for word arrays.

Ord k => TrieKey (Ordered k)

TrieMap (Ordered k) a is based on Data.Map.

TrieKey k => TrieKey (Rev k)

TrieMap (Rev k) a is a wrapper around a TrieMap k a that reverses the order of the operations.

TKey k => TrieKey (Key k)

TrieMap (Key k) a is a wrapper around a TrieMap (Rep k) a.

(TrieKey k1, TrieKey k2) => TrieKey (Either k1 k2)

TrieMap (Either k1 k2) a is essentially a (TrieMap k1 a, TrieMap k2 a), but specialized for the cases where one or both maps are empty.

(TrieKey k1, TrieKey k2) => TrieKey (k1, k2)

TrieMap (k1, k2) a is implemented as a TrieMap k1 (TrieMap k2 a).