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

Stabilityexperimental
Maintainerekmett@gmail.com
Safe HaskellNone

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

Instances

HasTrie Bool 
HasTrie Char 
HasTrie Int 
HasTrie Int8 
HasTrie Int16 
HasTrie Int32 
HasTrie Int64 
HasTrie Word 
HasTrie Word8 
HasTrie Word16 
HasTrie Word32 
HasTrie Word64 
HasTrie () 
HasTrie Any 
(Adjustable (BaseTrie [a]), TraversableWithKey1 (BaseTrie [a]), Representable (BaseTrie [a]), HasTrie a) => HasTrie [a] 
(Adjustable (BaseTrie (Dual a)), TraversableWithKey1 (BaseTrie (Dual a)), Representable (BaseTrie (Dual a)), HasTrie a) => HasTrie (Dual a) 
(Adjustable (BaseTrie (Sum a)), TraversableWithKey1 (BaseTrie (Sum a)), Representable (BaseTrie (Sum a)), HasTrie a) => HasTrie (Sum a) 
(Adjustable (BaseTrie (Product a)), TraversableWithKey1 (BaseTrie (Product a)), Representable (BaseTrie (Product a)), HasTrie a) => HasTrie (Product a) 
(Adjustable (BaseTrie (Maybe a)), TraversableWithKey1 (BaseTrie (Maybe a)), Representable (BaseTrie (Maybe a)), HasTrie a) => HasTrie (Maybe a) 
(Adjustable (BaseTrie (Seq a)), TraversableWithKey1 (BaseTrie (Seq a)), Representable (BaseTrie (Seq a)), HasTrie a) => HasTrie (Seq a) 
(Adjustable (BaseTrie (IntMap v)), TraversableWithKey1 (BaseTrie (IntMap v)), Representable (BaseTrie (IntMap v)), HasTrie v) => HasTrie (IntMap v) 
(Adjustable (BaseTrie (Either a b)), TraversableWithKey1 (BaseTrie (Either a b)), Representable (BaseTrie (Either a b)), HasTrie a, HasTrie b) => HasTrie (Either a b) 
(Adjustable (BaseTrie (a, b)), TraversableWithKey1 (BaseTrie (a, b)), Representable (BaseTrie (a, b)), HasTrie a, HasTrie b) => HasTrie (a, b) 
(Adjustable (BaseTrie (Map k v)), TraversableWithKey1 (BaseTrie (Map k v)), Representable (BaseTrie (Map k v)), HasTrie k, HasTrie v) => HasTrie (Map k v) 
(Adjustable (BaseTrie (Entry a b)), TraversableWithKey1 (BaseTrie (Entry a b)), Representable (BaseTrie (Entry a b)), HasTrie a, HasTrie b) => HasTrie (Entry a b) 
(Adjustable (BaseTrie (a, b, c)), TraversableWithKey1 (BaseTrie (a, b, c)), Representable (BaseTrie (a, b, c)), HasTrie a, HasTrie b, HasTrie c) => HasTrie (a, b, c) 
(Adjustable (BaseTrie (a, b, c, d)), TraversableWithKey1 (BaseTrie (a, b, c, d)), Representable (BaseTrie (a, b, c, d)), HasTrie a, HasTrie b, HasTrie c, HasTrie d) => HasTrie (a, b, c, d) 

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

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