| Stability | experimental | 
|---|---|
| Maintainer | ekmett@gmail.com | 
| Safe Haskell | Safe-Infered | 
Data.Functor.Representable.Trie
Contents
Description
- class (Adjustable (BaseTrie a), TraversableWithKey1 (BaseTrie a), Representable (BaseTrie a)) => HasTrie a where
 - mup :: HasTrie t => (b -> c) -> (t -> b) -> t -> c
 - memo :: HasTrie t => (t -> a) -> t -> a
 - memo2 :: (HasTrie s, HasTrie t) => (s -> t -> a) -> s -> t -> a
 - memo3 :: (HasTrie r, HasTrie s, HasTrie t) => (r -> s -> t -> a) -> r -> s -> t -> a
 - inTrie :: (HasTrie a, HasTrie c) => ((a -> b) -> c -> d) -> (a :->: b) -> c :->: d
 - inTrie2 :: (HasTrie a, HasTrie c, HasTrie e) => ((a -> b) -> (c -> d) -> e -> f) -> (a :->: b) -> (c :->: d) -> e :->: f
 - inTrie3 :: (HasTrie a, HasTrie c, HasTrie e, HasTrie g) => ((a -> b) -> (c -> d) -> (e -> f) -> g -> h) -> (a :->: b) -> (c :->: d) -> (e :->: f) -> g :->: h
 - trie :: HasTrie t => (t -> a) -> t :->: a
 - untrie :: HasTrie t => (t :->: a) -> t -> a
 - newtype a :->: b = Trie {}
 - data Entry a b = Entry a b
 
Representations of polynomial functors
class (Adjustable (BaseTrie a), TraversableWithKey1 (BaseTrie a), Representable (BaseTrie a)) => HasTrie a whereSource
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 | |
| HasTrie a => HasTrie [a] | |
| HasTrie a => HasTrie (Dual a) | |
| HasTrie a => HasTrie (Sum a) | |
| HasTrie a => HasTrie (Product a) | |
| HasTrie a => HasTrie (Maybe a) | |
| HasTrie a => HasTrie (Seq a) | |
| HasTrie v => HasTrie (IntMap v) | |
| (HasTrie a, HasTrie b) => HasTrie (Either a b) | |
| (HasTrie a, HasTrie b) => HasTrie (a, b) | |
| (HasTrie k, HasTrie v) => HasTrie (Map k v) | |
| (HasTrie a, HasTrie b) => HasTrie (Entry a b) | |
| (HasTrie a, HasTrie b, HasTrie c) => HasTrie (a, b, c) | |
| (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.
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
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 => 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 => Traversable1 (:->: a) | |
| HasTrie a => Foldable1 (:->: a) | |
| 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) |