representable-tries-2.0.1.1: Tries from representations of polynomial functors

Stabilityexperimental
Maintainerekmett@gmail.com

Data.Functor.Representable.Trie

Contents

Description

 

Synopsis

Representations of polynomial functors

class (Adjustable (BaseTrie a), TraversableWithKey1 (BaseTrie a), Representable (BaseTrie a)) => HasTrie a whereSource

Associated Types

type BaseTrie a :: * -> *Source

Methods

embedKey :: a -> Key (BaseTrie a)Source

projectKey :: Key (BaseTrie a) -> aSource

Memoizing functions

mup :: HasTrie t => (b -> c) -> (t -> b) -> t -> cSource

Lift a memoizer to work with one more argument.

memo :: HasTrie t => (t -> a) -> t -> aSource

memo2 :: (HasTrie s, HasTrie t) => (s -> t -> a) -> s -> t -> aSource

Memoize a binary function, on its first argument and then on its second. Take care to exploit any partial evaluation.

memo3 :: (HasTrie r, HasTrie s, HasTrie t) => (r -> s -> t -> a) -> r -> s -> t -> aSource

Memoize a ternary function on successive arguments. Take care to exploit any partial evaluation.

inTrie :: (HasTrie a, HasTrie c) => ((a -> b) -> c -> d) -> (a :->: b) -> c :->: dSource

Apply a unary function inside of a tabulate

inTrie2 :: (HasTrie a, HasTrie c, HasTrie e) => ((a -> b) -> (c -> d) -> e -> f) -> (a :->: b) -> (c :->: d) -> e :->: fSource

Apply a binary function inside of a tabulate

inTrie3 :: (HasTrie a, HasTrie c, HasTrie e, HasTrie g) => ((a -> b) -> (c -> d) -> (e -> f) -> g -> h) -> (a :->: b) -> (c :->: d) -> (e :->: f) -> g :->: hSource

Apply a ternary function inside of a tabulate

Workarounds for current GHC limitations

trie :: HasTrie t => (t -> a) -> t :->: aSource

untrie :: HasTrie t => (t :->: a) -> t -> aSource

newtype a :->: b Source

Constructors

Trie 

Fields

runTrie :: BaseTrie a b
 

Instances

HasTrie a => MonadReader a (:->: a) 
HasTrie a => Monad (:->: a) 
HasTrie a => Functor (:->: a) 
HasTrie a => Applicative (:->: a) 
HasTrie a => Foldable (:->: a) 
HasTrie a => Traversable (:->: a) 
(HasTrie m, Semigroup m, Monoid m) => Comonad (:->: m) 
(HasTrie m, Semigroup m) => Extend (:->: m) 
HasTrie e => Distributive (:->: e) 
HasTrie a => Foldable1 (:->: a) 
HasTrie a => Traversable1 (:->: a) 
HasTrie a => Keyed (:->: a) 
HasTrie e => Zip (:->: e) 
HasTrie e => ZipWithKey (:->: e) 
HasTrie e => Indexable (:->: e) 
HasTrie e => Lookup (:->: e) 
HasTrie e => Adjustable (:->: e) 
HasTrie a => FoldableWithKey (:->: a) 
HasTrie a => FoldableWithKey1 (:->: a) 
HasTrie a => TraversableWithKey (:->: a) 
HasTrie a => TraversableWithKey1 (:->: a) 
HasTrie e => Representable (:->: e) 
HasTrie a => Apply (:->: a) 
HasTrie a => Bind (:->: a) 
HasTrie e => Adjunction (Entry e) (:->: e) 
(HasTrie a, Eq b) => Eq (:->: a b) 
(HasTrie a, Ord b) => Ord (:->: a b) 
(HasTrie a, Show a, Show b) => Show (:->: a b) 

data Entry a b Source

Constructors

Entry a b 

Instances

Functor (Entry a) 
HasTrie e => Adjunction (Entry e) (:->: e) 
(HasTrie a, HasTrie b) => HasTrie (Entry a b)