Copyright | (c) Edward Kmett 2011-2014 |
---|---|
License | BSD3 |
Maintainer | ekmett@gmail.com |
Stability | experimental |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
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.
Synopsis
- class Distributive f => Representable f where
- tabulated :: (Representable f, Representable g, Profunctor p, Functor h) => p (f a) (h (g b)) -> p (Rep f -> a) (h (Rep g -> b))
- newtype Co f a = Co {
- unCo :: f a
- fmapRep :: Representable f => (a -> b) -> f a -> f b
- distributeRep :: (Representable f, Functor w) => w (f a) -> f (w a)
- collectRep :: (Representable f, Functor w) => (a -> f b) -> w a -> f (w 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
- mfixRep :: Representable f => (a -> f a) -> f a
- mzipRep :: Representable f => f a -> f b -> f (a, b)
- mzipWithRep :: Representable f => (a -> b -> c) -> f a -> f b -> f c
- askRep :: Representable f => f (Rep f)
- localRep :: Representable f => (Rep f -> Rep f) -> f a -> f a
- duplicatedRep :: (Representable f, Semigroup (Rep f)) => f a -> f (f a)
- extendedRep :: (Representable f, Semigroup (Rep f)) => (f a -> b) -> f a -> f b
- duplicateRep :: (Representable f, Monoid (Rep f)) => f a -> f (f a)
- extendRep :: (Representable f, Monoid (Rep f)) => (f a -> b) -> f a -> f b
- extractRep :: (Representable f, Monoid (Rep f)) => f a -> a
- duplicateRepBy :: Representable f => (Rep f -> Rep f -> Rep f) -> f a -> f (f a)
- extendRepBy :: Representable f => (Rep f -> Rep f -> Rep f) -> (f a -> b) -> f a -> f b
- extractRepBy :: Representable f => Rep f -> f a -> a
- imapRep :: Representable r => (Rep r -> a -> a') -> r a -> r a'
- ifoldMapRep :: forall r m a. (Representable r, Foldable r, Monoid m) => (Rep r -> a -> m) -> r a -> m
- itraverseRep :: forall r f a a'. (Representable r, Traversable r, Applicative f) => (Rep r -> a -> f a') -> r a -> f (r a')
- type GRep f = GRep' (Rep1 f)
- gindex :: (Generic1 f, GRep f ~ Rep f, GIndex (Rep1 f)) => f a -> Rep f -> a
- gtabulate :: (Generic1 f, GRep f ~ Rep f, GTabulate (Rep1 f)) => (Rep f -> a) -> f a
- newtype WrappedRep f = WrapRep {}
Representable Functors
class Distributive f => Representable f where Source #
A Functor
f
is Representable
if tabulate
and index
witness an isomorphism to (->) x
.
Every Distributive
Functor
is actually Representable
.
Every Representable
Functor
from Hask to Hask is a right adjoint.
tabulate
.index
≡ idindex
.tabulate
≡ idtabulate
.return
≡return
Nothing
If no definition is provided, this will default to GRep
.
tabulate :: (Rep f -> a) -> f a Source #
default tabulate :: (Generic1 f, GRep f ~ Rep f, GTabulate (Rep1 f)) => (Rep f -> a) -> f a Source #
index :: f a -> Rep f -> a Source #
If no definition is provided, this will default to gindex
.
Instances
tabulated :: (Representable f, Representable g, Profunctor p, Functor h) => p (f a) (h (g b)) -> p (Rep f -> a) (h (Rep g -> b)) Source #
tabulate
and index
form two halves of an isomorphism.
This can be used with the combinators from the lens
package.
tabulated
::Representable
f =>Iso'
(Rep
f -> a) (f a)
Wrapped representable functors
Instances
ComonadTrans Co Source # | |
Defined in Data.Functor.Rep | |
(Representable f, Rep f ~ a) => MonadReader a (Co f) Source # | |
Representable f => Monad (Co f) Source # | |
Functor f => Functor (Co f) Source # | |
Representable f => Applicative (Co f) Source # | |
(Representable f, Monoid (Rep f)) => Comonad (Co f) Source # | |
Representable f => Distributive (Co f) Source # | |
Representable f => Apply (Co f) Source # | |
Representable f => Bind (Co f) Source # | |
(Representable f, Semigroup (Rep f)) => Extend (Co f) Source # | |
Representable f => Representable (Co f) Source # | |
type Rep (Co f) Source # | |
Defined in Data.Functor.Rep |
Default definitions
Functor
fmapRep :: Representable f => (a -> b) -> f a -> f b Source #
Distributive
distributeRep :: (Representable f, Functor w) => w (f a) -> f (w a) Source #
collectRep :: (Representable f, Functor w) => (a -> f b) -> w a -> f (w b) Source #
Apply/Applicative
apRep :: Representable f => f (a -> b) -> f a -> f b Source #
pureRep :: Representable f => a -> f a Source #
liftR2 :: Representable f => (a -> b -> c) -> f a -> f b -> f c Source #
liftR3 :: Representable f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d Source #
Bind/Monad
bindRep :: Representable f => f a -> (a -> f b) -> f b Source #
MonadFix
mfixRep :: Representable f => (a -> f a) -> f a Source #
MonadZip
mzipRep :: Representable f => f a -> f b -> f (a, b) Source #
mzipWithRep :: Representable f => (a -> b -> c) -> f a -> f b -> f c Source #
MonadReader
askRep :: Representable f => f (Rep f) Source #
Extend
duplicatedRep :: (Representable f, Semigroup (Rep f)) => f a -> f (f a) Source #
extendedRep :: (Representable f, Semigroup (Rep f)) => (f a -> b) -> f a -> f b Source #
Comonad
duplicateRep :: (Representable f, Monoid (Rep f)) => f a -> f (f a) Source #
extractRep :: (Representable f, Monoid (Rep f)) => f a -> a Source #
Comonad, with user-specified monoid
duplicateRepBy :: Representable f => (Rep f -> Rep f -> Rep f) -> f a -> f (f a) Source #
extendRepBy :: Representable f => (Rep f -> Rep f -> Rep f) -> (f a -> b) -> f a -> f b Source #
extractRepBy :: Representable f => Rep f -> f a -> a Source #
WithIndex
imapRep :: Representable r => (Rep r -> a -> a') -> r a -> r a' Source #
ifoldMapRep :: forall r m a. (Representable r, Foldable r, Monoid m) => (Rep r -> a -> m) -> r a -> m Source #
itraverseRep :: forall r f a a'. (Representable r, Traversable r, Applicative f) => (Rep r -> a -> f a') -> r a -> f (r a') Source #
Generics
type GRep f = GRep' (Rep1 f) Source #
A default implementation of Rep
for a datatype that is an instance of
Generic1
. This is usually composed of Either
, tuples, unit tuples, and
underlying Rep
values. For instance, if you have:
data Foo a = MkFoo a (Bar a) (Baz (Quux a)) deriving (Functor
,Generic1
) instanceRepresentable
Foo
Then you'll get:
GRep
Foo = Either () (Either (WrappedRep
Bar) (WrappedRep
Baz,WrappedRep
Quux))
(See the Haddocks for WrappedRep
for an explanation of its purpose.)
newtype WrappedRep f Source #
On the surface, WrappedRec
is a simple wrapper around Rep
. But it plays
a very important role: it prevents generic Representable
instances for
recursive types from sending the typechecker into an infinite loop. Consider
the following datatype:
data Stream a = a :< Stream a deriving (Functor
,Generic1
) instanceRepresentable
Stream
With WrappedRep
, we have its Rep
being:
Rep
Stream =Either
() (WrappedRep
Stream)
If WrappedRep
didn't exist, it would be:
Rep
Stream = Either () (Either () (Either () ...))
An infinite type! WrappedRep
breaks the potentially infinite loop.