Stability | experimental |
---|---|
Maintainer | ekmett@gmail.com |
Safe Haskell | None |
Representable endofunctors over the category of Haskell types are isomorphic to the reader monad and so inherit a very large number of properties for free.
- class (Functor f, Indexable f) => Representable f where
- newtype Rep f a = Rep {
- unrep :: f a
- fmapRep :: Representable f => (a -> b) -> f a -> f b
- distributeRep :: (Representable f, Functor w) => w (f a) -> f (w a)
- mapWithKeyRep :: Representable f => (Key f -> a -> b) -> f a -> f b
- apRep :: Representable f => f (a -> b) -> f a -> f b
- pureRep :: Representable f => a -> f a
- liftR2 :: Representable f => (a -> b -> c) -> f a -> f b -> f c
- liftR3 :: Representable f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
- bindRep :: Representable f => f a -> (a -> f b) -> f b
- bindWithKeyRep :: Representable f => f a -> (Key f -> a -> f b) -> f b
- zipWithRep :: Representable f => (a -> b -> c) -> f a -> f b -> f c
- zipWithKeyRep :: Representable f => (Key f -> a -> b -> c) -> f a -> f b -> f c
- askRep :: Representable f => f (Key f)
- localRep :: Representable f => (Key f -> Key f) -> f a -> f a
- duplicatedRep :: (Representable f, Semigroup (Key f)) => f a -> f (f a)
- extendedRep :: (Representable f, Semigroup (Key f)) => (f a -> b) -> f a -> f b
- duplicateRep :: (Representable f, Monoid (Key f)) => f a -> f (f a)
- extendRep :: (Representable f, Monoid (Key f)) => (f a -> b) -> f a -> f b
- extractRep :: (Indexable f, Monoid (Key f)) => f a -> a
Representable Functors
class (Functor f, Indexable f) => Representable f whereSource
A Functor
f
is Representable
if tabulate
and index
witness an isomorphism to (->) x
.
tabulate . index = id index . tabulate = id tabulate . return f = return f
Representable Identity | |
(Functor ((->) e), Indexable ((->) e)) => Representable ((->) e) | |
(Functor (IdentityT m), Indexable (IdentityT m), Representable m) => Representable (IdentityT m) | |
(Functor (Cofree f), Indexable (Cofree f), Representable f) => Representable (Cofree f) | |
(Functor (Rep f), Indexable (Rep f), Representable f) => Representable (Rep f) | |
(Functor (TracedT s w), Indexable (TracedT s w), Representable w) => Representable (TracedT s w) | |
(Functor (ReaderT e m), Indexable (ReaderT e m), Representable m) => Representable (ReaderT e m) | |
(Functor (Compose f g), Indexable (Compose f g), Representable f, Representable g) => Representable (Compose f g) | |
(Functor (Product f g), Indexable (Product f g), Representable f, Representable g) => Representable (Product f g) | |
(Functor (ReaderT f m), Indexable (ReaderT f m), Representable f, Representable m) => Representable (ReaderT f m) |
Wrapped representable functors
ComonadTrans Rep | |
(Monad (Rep f), Representable f, ~ * (Key f) a) => MonadReader a (Rep f) | |
Representable f => Monad (Rep f) | |
Representable f => Functor (Rep f) | |
(Functor (Rep f), Representable f) => Applicative (Rep f) | |
(Functor (Rep f), Representable f, Monoid (Key f)) => Comonad (Rep f) | |
(Functor (Rep f), Representable f) => Distributive (Rep f) | |
(Functor (Rep f), Representable f) => Keyed (Rep f) | |
(Functor (Rep f), Representable f) => Zip (Rep f) | |
(Keyed (Rep f), Zip (Rep f), Representable f) => ZipWithKey (Rep f) | |
(Lookup (Rep f), Indexable f) => Indexable (Rep f) | |
Indexable f => Lookup (Rep f) | |
(Functor (Rep f), Representable f) => Apply (Rep f) | |
(Apply (Rep f), Representable f) => Bind (Rep f) | |
(Functor (Rep f), Representable f, Semigroup (Key f)) => Extend (Rep f) | |
(Functor (Rep f), Indexable (Rep f), Representable f) => Representable (Rep f) |
Default definitions
Functor
fmapRep :: Representable f => (a -> b) -> f a -> f bSource
Distributive
distributeRep :: (Representable f, Functor w) => w (f a) -> f (w a)Source
Keyed
mapWithKeyRep :: Representable f => (Key f -> a -> b) -> f a -> f bSource
Apply/Applicative
apRep :: Representable f => f (a -> b) -> f a -> f bSource
pureRep :: Representable f => a -> f aSource
liftR2 :: Representable f => (a -> b -> c) -> f a -> f b -> f cSource
liftR3 :: Representable f => (a -> b -> c -> d) -> f a -> f b -> f c -> f dSource
Bind/Monad
bindRep :: Representable f => f a -> (a -> f b) -> f bSource
bindWithKeyRep :: Representable f => f a -> (Key f -> a -> f b) -> f bSource
Zip/ZipWithKey
zipWithRep :: Representable f => (a -> b -> c) -> f a -> f b -> f cSource
zipWithKeyRep :: Representable f => (Key f -> a -> b -> c) -> f a -> f b -> f cSource
MonadReader
askRep :: Representable f => f (Key f)Source
localRep :: Representable f => (Key f -> Key f) -> f a -> f aSource
Extend
duplicatedRep :: (Representable f, Semigroup (Key f)) => f a -> f (f a)Source
extendedRep :: (Representable f, Semigroup (Key f)) => (f a -> b) -> f a -> f bSource
Comonad
duplicateRep :: (Representable f, Monoid (Key f)) => f a -> f (f a)Source
extendRep :: (Representable f, Monoid (Key f)) => (f a -> b) -> f a -> f bSource
extractRep :: (Indexable f, Monoid (Key f)) => f a -> aSource