| Portability | RankNTypes |
|---|---|
| Stability | provisional |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Safe Haskell | Safe-Infered |
Control.Lens.Representable
Contents
Description
Corepresentable endofunctors represented by their polymorphic lenses
The polymorphic lenses of the form (forall x. each
represent a distinct path into a functor Lens (f x) x)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 Data.Distributive
data Pair a = Pair { _x :: a, _y :: a }
makeLenses ''PairinstanceRepresentablePair whererepf = Pair (f x) (f y)
From there, you can get definitions for a number of instances for free.
instanceApplicativePair wherepure=pureRep(<*>) =apRep
instanceMonadPair wherereturn=pureRep(>>=) =bindRep
instanceDistributivePair wheredistribute=distributeRep
- class Functor f => Representable f where
- type Rep f = forall a. Simple 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 Path f = Path {}
- paths :: Representable f => f (Path f)
- tabulated :: (Isomorphic k, Representable f) => k (Path f -> a) (f a)
- 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. Nearly 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 = is a valid choice of Rep fx for (nearly) 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.
Instances
| Representable Identity | |
| Eq e => Representable ((->) e) | NB: The |
Using Lenses as Representations
type Rep f = forall a. Simple 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
pureRep is a valid default definition for pure and return for a
Representable functor.
pureRep=rep.const
Usage for a :
Representable Foo
instanceApplicativeFoo wherepure=pureRep...
instanceMonadFoo wherereturn=pureRep...
apRep :: Representable f => f (a -> b) -> f a -> f bSource
apRep is a valid default definition for (<*>) for a Representable
functor.
apRepmf ma =rep$i -> mf^.i$ma^.i
Usage for a :
Representable Foo
instanceApplicativeFoo wherepure=pureRep(<*>) =apRep
bindRep :: Representable f => f a -> (a -> f b) -> f bSource
distributeRep :: (Representable f, Functor w) => w (f a) -> f (w a)Source
A default definition for distribute for a Representable Functor
distributeRepwf =rep$i ->fmap(^.i) wf
Usage for a :
Representable Foo
instanceDistributiveFoo wheredistribute=distributeRep
Wrapped Representations
Sometimes you need to store a path lens into a container, but at least
at this time, ImpredicativePolymorphism in GHC is somewhat lacking.
This type provides a way to, say, store a [] of polymorphic lenses.
paths :: Representable f => f (Path f)Source
A Representable Functor has a fixed shape. This fills each position
in it with a Path
tabulated :: (Isomorphic k, Representable f) => k (Path f -> a) (f a)Source
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
mapWithRepf 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)