TrieMap-0.0.1.2: An implementation of generalized tries with sophisticated map type inference.

TrieMap.Algebraic

Synopsis

Documentation

class Algebraic k whereSource

Algebraic refers to a type with an algebraic representation, armed with methods to convert in each direction. toAlg and fromAlg should preserve equality and ordering.

Associated Types

type AlgRep k Source

AlgRep k is a fully decomposed representation of k into algebraic pieces.

Methods

toAlg :: k -> AlgRep kSource

fromAlg :: AlgRep k -> kSource

Instances

Algebraic Bool 
Algebraic Char 
Algebraic Double 
Algebraic Float 
Algebraic Int 
Algebraic Integer 
Algebraic Rational 
Algebraic Word8 
Algebraic Word16 
Algebraic Word32 
Algebraic () 
Algebraic ByteString 
Algebraic IntSet 
Algebraic k => Algebraic [k] 
Algebraic a => Algebraic (Maybe a) 
Algebraic v => Algebraic (IntMap v) 
Algebraic a => Algebraic (Set a) 
Algebraic v => Algebraic (Elem v) 
AlgebraicT f => Algebraic (Fix f) 
Algebraic a => Algebraic (Ordered a) 
(Algebraic a, Algebraic b) => Algebraic (Either a b) 
(Algebraic a, Algebraic b) => Algebraic (a, b) 
(Algebraic k, Algebraic v) => Algebraic (Map k v) 
Algebraic (f a) => Algebraic (App f a) 
Algebraic a => Algebraic (Const a b) 
(AlgebraicT t, Algebraic a) => Algebraic (AlgWrap t a) 
(Algebraic a, Algebraic b, Algebraic c) => Algebraic (a, b, c) 
Algebraic (m a) => Algebraic (IdMap k m a) 
(AlgebraicT m, Algebraic k, Algebraic a) => Algebraic (RadixTrie k m a) 
(AlgebraicT m, Algebraic k, Algebraic a) => Algebraic (Edge k m a) 
(Algebraic (f (g a)), Functor f) => Algebraic (O f g a) 
(TrieKeyT f t, AlgebraicT f, Sized a, Algebraic a) => Algebraic (FixMap f t a) 
(AlgebraicT f, AlgebraicT g, Algebraic a) => Algebraic (:+: f g a) 
(AlgebraicT f, AlgebraicT g, Algebraic a) => Algebraic (:*: f g a) 
Algebraic (m (Elem a)) => Algebraic (TrieMap k m a) 
(Algebraic a, Algebraic b, Algebraic c, Algebraic d) => Algebraic (a, b, c, d) 
Algebraic (m a) => Algebraic (ConstMap m k m' a) 
(Algebraic (m1 a), Algebraic (m2 a)) => Algebraic (CUnionMap m1 k2 m2 a) 
Algebraic (m1 (m2 a)) => Algebraic (CProdMap m1 k2 m2 a) 
(Algebraic (t1 k m a), Algebraic (t2 k m a)) => Algebraic (UnionMap t1 t2 k m a) 
Algebraic (t1 k m (t2 k m a)) => Algebraic (ProdMap t1 t2 k m a) 
Algebraic (t1 (App f2 k) (App (t2 k m)) a) => Algebraic (CompMap t1 f2 t2 k m a) 

class Functor (AlgRepT t) => AlgebraicT t whereSource

Associated Types

type AlgRepT t :: * -> *Source

Methods

toAlgT :: t a -> AlgRepT t aSource

fromAlgT :: AlgRepT t a -> t aSource

class Functor (SAlgRepT t) => SAlgebraicT t whereSource

Associated Types

type SAlgRepT t :: * -> *Source

Methods

toSAlgT :: Sized a => t a -> SAlgRepT t aSource

fromSAlgT :: Sized a => SAlgRepT t a -> t aSource

Instances

SAlgebraicT Maybe 
SAlgebraicT IntMap 
Algebraic k => SAlgebraicT (Map k) 
SAlgebraicT f => SAlgebraicT (App f) 
SAlgebraicT m => SAlgebraicT (IdMap k m) 
(Algebraic k, TrieKey k m) => SAlgebraicT (RadixTrie k m) 
TrieKeyT f t => SAlgebraicT (FixMap f t) 
SAlgebraicT m => SAlgebraicT (ConstMap m k m') 
(SAlgebraicT m1, SAlgebraicT m2) => SAlgebraicT (CUnionMap m1 k2 m2) 
(SAlgebraicT m1, SAlgebraicT m2, TrieKey k2 m2) => SAlgebraicT (CProdMap m1 k2 m2) 
(SAlgebraicT (t1 k m), SAlgebraicT (t2 k m)) => SAlgebraicT (UnionMap t1 t2 k m) 
(SAlgebraicT (t1 k m), SAlgebraicT (t2 k m), TrieKey k m, TrieKeyT f2 t2) => SAlgebraicT (ProdMap t1 t2 k m) 
SAlgebraicT (t1 (App f2 k) (App (t2 k m))) => SAlgebraicT (CompMap t1 f2 t2 k m) 

newtype Ordered k Source

Constructors

Ord 

Fields

unOrd :: k
 

Instances

Functor Ordered 
Eq k => Eq (Ordered k) 
Ord k => Ord (Ordered k) 
Show k => Show (Ordered k) 
Algebraic a => Algebraic (Ordered a) 
Ord k => TrieKey (Ordered k) (Map k) 

newtype AlgWrap t a Source

Constructors

AlgWrap 

Fields

unAlgWrap :: t a
 

Instances