lens-3.3: Lenses, Folds and Traversals

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

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 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. 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 = Rep f is a valid choice of x 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.

Methods

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

Instances

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

NB: The Eq requirement on this instance is a consequence of the choice of Lens as a Rep, it isn't fundamental.

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

 instance Applicative Foo where
   pure = pureRep
   ...
 instance Monad Foo where
   return = pureRep
   ...

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

 instance Monad Foo 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

Usage for a Representable Foo:

 instance Distributive Foo where
   distribute = distributeRep

Wrapped Representations

newtype Path f Source

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

Constructors

Path 

Fields

walk :: Rep f
 

paths :: Representable f => f (Path f)Source

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

tabulated :: Representable f => (Path f -> a) -> f aSource

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

Setting with Representation

rmap :: Representable f => (Rep f -> a -> b) -> f a -> f bSource

Map over a Representable functor with access to the Lens for the current position

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

Folding with Representation

rfoldMap :: (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

rfoldr :: (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.

Traversing with Representation

rtraverse :: (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

rtraverse_ :: (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

rfor :: (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)

rmapM :: (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

rmapM_ :: (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

rforM :: (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)

Representable Setters, Folds and Traversals

rmapped :: Representable f => IndexedSetter (Path f) (f a) (f b) a bSource

An IndexedSetter that walks an Representable Functor using a Path for an index.

rfolded :: (Representable f, Foldable f) => IndexedFold (Path f) (f a) aSource

An IndexedFold that walks an Foldable Representable Functor using a Path for an index.