Portability | RankNTypes |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Safe |
Corepresentable endofunctors represented by their polymorphic lenses
The polymorphic lenses of the form (forall x. Lens (f x) x)
each
represent a distinct path into a functor f
. If the functor is entirely
characterized by assigning values to these paths, then the functor is
representable.
Consider the following example.
import Control.Lens import Control.Lens.Rep import Control.Lens.TH import Data.Distributive
data Pair a = Pair { _x :: a, _y :: a }
makeLenses ''Pair
instance Representable Pair where rep f = Pair (f x) (f y)
From there, you can get definitions for a number of instances for free.
instance Applicative Pair where pure = pureRep (<*>) = apRep
instance Monad Pair where return = pureRep (>>=) = bindRep
instance Distributive Pair where distribute = distributeRep
- class Functor f => Representable f where
- type Rep f = forall a. Lens (f a) a
- fmapRep :: Representable f => (a -> b) -> f a -> f b
- pureRep :: Representable f => a -> f a
- apRep :: Representable f => f (a -> b) -> f a -> f b
- bindRep :: Representable f => f a -> (a -> f b) -> f b
- distributeRep :: (Representable f, Functor w) => w (f a) -> f (w a)
- newtype Key f = Key {}
- keys :: Representable f => f (Key f)
- mapWithRep :: Representable f => (Rep f -> a -> b) -> f a -> f b
- foldMapWithRep :: (Representable f, Foldable f, Monoid m) => (Rep f -> a -> m) -> f a -> m
- foldrWithRep :: (Representable f, Foldable f) => (Rep f -> a -> b -> b) -> b -> f a -> b
- traverseWithRep :: (Representable f, Traversable f, Applicative g) => (Rep f -> a -> g b) -> f a -> g (f b)
- traverseWithRep_ :: (Representable f, Foldable f, Applicative g) => (Rep f -> a -> g b) -> f a -> g ()
- forWithRep :: (Representable f, Traversable f, Applicative g) => f a -> (Rep f -> a -> g b) -> g (f b)
- mapMWithRep :: (Representable f, Traversable f, Monad m) => (Rep f -> a -> m b) -> f a -> m (f b)
- mapMWithRep_ :: (Representable f, Foldable f, Monad m) => (Rep f -> a -> m b) -> f a -> m ()
- forMWithRep :: (Representable f, Traversable f, Monad m) => f a -> (Rep f -> a -> m b) -> m (f b)
Representable Functors
class Functor f => Representable f whereSource
Representable Functors.
A Functor
f
is Representable
if it is isomorphic to (x -> a)
for some x. All such functors can be represented by choosing x
to be
the set of lenses that are polymorphic in the contents of the Functor
,
that is to say x = Rep f
is a valid choice of x
for every
Representable
Functor
.
Note: Some sources refer to covariant representable functors as
corepresentable functors, and leave the "representable" name to
contravariant functors (those are isomorphic to (a -> x)
for some x
).
As the covariant case is vastly more common, and both are often referred to
as representable functors, we choose to call these functors Representable
here.
Representable Identity | |
Eq e => Representable ((->) e) | NB: The Eq requirement on this instance is a consequence of a lens
rather than |
Using Lenses as Representations
type Rep f = forall a. Lens (f a) aSource
The representation of a Representable
Functor
as Lenses
Default definitions
fmapRep :: Representable f => (a -> b) -> f a -> f bSource
pureRep :: Representable f => a -> f aSource
apRep :: Representable f => f (a -> b) -> f a -> f bSource
bindRep :: Representable f => f a -> (a -> f b) -> f bSource
bindRep
is a valid default default definition for '(>>=)' for a
representable functor.
bindRep m f = rep $ \i -> f(m^.i)^.i
Usage for a representable functor Foo
:
instance Monad ... where return = pureRep (>>=) = bindRep
distributeRep :: (Representable f, Functor w) => w (f a) -> f (w a)Source
A default definition for distribute
for a Representable
Functor
distributeRep wf = rep $ \i -> fmap (^.i) wf
Typical Usage:
instance Distributive ... where distribute = distributeRep
Wrapped Representations
Sometimes you need to store a path lens into a container, but at least at this time, impredicative polymorphism in GHC is somewhat lacking.
This type provides a way to, say, store a list of polymorphic lenses.
keys :: Representable f => f (Key f)Source
A Representable
Functor
has a fixed shape. This fills each position
in it with a Key
Traversal with representation
mapWithRep :: Representable f => (Rep f -> a -> b) -> f a -> f bSource
Map over a Representable
Functor
with access to the lens for the
current position
mapWithKey f m = rep $ \i -> f i (m^.i)
foldMapWithRep :: (Representable f, Foldable f, Monoid m) => (Rep f -> a -> m) -> f a -> mSource
Fold over a Representable
Functor
with access to the current path
as a lens, yielding a Monoid
foldrWithRep :: (Representable f, Foldable f) => (Rep f -> a -> b -> b) -> b -> f a -> bSource
Fold over a Representable
Functor
with access to the current path
as a lens.
traverseWithRep :: (Representable f, Traversable f, Applicative g) => (Rep f -> a -> g b) -> f a -> g (f b)Source
Traverse a Representable
Functor
with access to the current path
traverseWithRep_ :: (Representable f, Foldable f, Applicative g) => (Rep f -> a -> g b) -> f a -> g ()Source
Traverse a Representable
Functor
with access to the current path
as a lens, discarding the result
forWithRep :: (Representable f, Traversable f, Applicative g) => f a -> (Rep f -> a -> g b) -> g (f b)Source
Traverse a Representable
Functor
with access to the current path
and a lens (and the arguments flipped)
mapMWithRep :: (Representable f, Traversable f, Monad m) => (Rep f -> a -> m b) -> f a -> m (f b)Source
mapM
over a Representable
Functor
with access to the current path
as a lens
mapMWithRep_ :: (Representable f, Foldable f, Monad m) => (Rep f -> a -> m b) -> f a -> m ()Source
mapM
over a Representable
Functor
with access to the current path
as a lens, discarding the result
forMWithRep :: (Representable f, Traversable f, Monad m) => f a -> (Rep f -> a -> m b) -> m (f b)Source
mapM
over a Representable
Functor
with access to the current path
as a lens (with the arguments flipped)