lens-1.3.1: Lenses, Folds and Traversals

PortabilityRankNTypes
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellSafe-Infered

Control.Lens.Representable

Contents

Description

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.Representable
 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

Synopsis

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.

Methods

rep :: (Rep f -> a) -> f aSource

Instances

Representable Identity 
Eq e => Representable ((->) e)

NB: The Eq requirement on this instance is a consequence of a lens rather than e as the representation.

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

fmapRep is a valid default definition for fmap for a representable functor.

 fmapRep f m = rep $ \i -> f (m^.i)

Usage for a representable functor Foo:

 instance Functor Foo where
   fmap = fmapRep

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 functor Foo:

 instance Applicative Foo where
    pure = pureRep
    (<*>) = apRep
 instance Monad Foo where
   return = pureRep
   (>>=) = bindRep

apRep :: Representable f => f (a -> b) -> f a -> f bSource

apRep is a valid default definition for '(*)' for a representable functor.

 apRep mf ma = rep $ \i -> mf^.i $ ma^.i

Usage for a representable functor Foo:

 instance Applicative Foo where
    pure = pureRep
   (<*>) = apRep

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

newtype Key f Source

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.

Constructors

Key 

Fields

turn :: Rep f
 

keys :: Representable f => f (Key f)Source

A Representable Functor has a fixed shape. This fills each position in it with a Key

tabulated :: Representable f => (Key f -> a) :~> f aSource

A version of rep that is an isomorphism. Predicativity requires that we wrap the Rep as a Key, however.

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)