Haskell/Lenses and functional references
This chapter is about functional references. By "references", we mean they point at parts of values, allowing us to access and modify them. By "functional", we mean they do so in a way that provides the flexibility and composability we came to expect from functions. We will study functional references as implemented by the powerful lens library. lens is named after lenses, a particularly well known kind of functional reference. Beyond being very interesting from a conceptual point of view, lenses and other functional references allow for several convenient and increasingly common idioms, put into use by a number of useful libraries.
A taste of lenses
editAs a warm-up, we will demonstrate the simplest use case for lenses: as a nicer alternative to the vanilla Haskell records. There will be little in the way of explanations in this section; we will fill in the gaps through the remainder of the chapter.
Consider the following types, which are not unlike something you might find in a 2D drawing library:
-- A point in the plane.
data Point = Point
{ positionX :: Double
, positionY :: Double
} deriving (Show)
-- A line segment from one point to another.
data Segment = Segment
{ segmentStart :: Point
, segmentEnd :: Point
} deriving (Show)
-- Helpers to create points and segments.
makePoint :: (Double, Double) -> Point
makePoint (x, y) = Point x y
makeSegment :: (Double, Double) -> (Double, Double) -> Segment
makeSegment start end = Segment (makePoint start) (makePoint end)
Record syntax gives us functions for accessing the fields. With them, getting the coordinates of the points that define a segment is easy enough:
GHCi> let testSeg = makeSegment (0, 1) (2, 4)
GHCi> positionY . segmentEnd $ testSeg
GHCi> 4.0
Updates, however, are clunkier...
GHCi> testSeg { segmentEnd = makePoint (2, 3) }
Segment {segmentStart = Point {positionX = 0.0, positionY = 1.0}
, segmentEnd = Point {positionX = 2.0, positionY = 3.0}}
... and get downright ugly when we need to reach a nested field. Here is what it takes to double the value of the y coordinate of the end point:
GHCi> :set +m -- Enabling multi-line input in GHCi.
GHCi> let end = segmentEnd testSeg
GHCi| in testSeg { segmentEnd = end { positionY = 2 * positionY end } }
Segment {segmentStart = Point {positionX = 0.0, positionY = 1.0}
, segmentEnd = Point {positionX = 2.0, positionY = 8.0}}
Lenses allow us to avoid such nastiness, so let's start over with them:
-- Some of the examples in this chapter require a few GHC extensions:
-- TemplateHaskell is needed for makeLenses; RankNTypes is needed for
-- a few type signatures later on.
{-# LANGUAGE TemplateHaskell, RankNTypes #-}
import Control.Lens
data Point = Point
{ _positionX :: Double
, _positionY :: Double
} deriving (Show)
makeLenses ''Point
data Segment = Segment
{ _segmentStart :: Point
, _segmentEnd :: Point
} deriving (Show)
makeLenses ''Segment
makePoint :: (Double, Double) -> Point
makePoint (x, y) = Point x y
makeSegment :: (Double, Double) -> (Double, Double) -> Segment
makeSegment start end = Segment (makePoint start) (makePoint end)
The only real change here is the use of makeLenses
, which automatically generates lenses for the fields of Point
and Segment
(the extra underscores are required by the naming conventions of makeLenses
). As we will see, writing lenses definitions by hand is not difficult at all; however, it can be tedious if there are lots of fields to make lenses for, and thus automatic generation is very convenient.
Thanks to makeLenses
, we now have a lens for each field. Their names match that of the fields, except with the leading underscore removed:
GHCi> :info positionY
positionY :: Lens' Point Double
-- Defined at WikibookLenses.hs:9:1
GHCi> :info segmentEnd
segmentEnd :: Lens' Segment Point
-- Defined at WikibookLenses.hs:15:1
The type positionY :: Lens' Point Double
tells us that positionY
is a reference to a Double
within a Point
. To work with such references, we use the combinators provided by the lens library. One of them is view
, which gives us the value pointed at by a lens, just like a record accessor:
GHCi> let testSeg = makeSegment (0, 1) (2, 4)
GHCi> view segmentEnd testSeg
Point {_positionX = 2.0, _positionY = 4.0}
Another one is set
, which overwrites the value pointed at:
GHCi> set segmentEnd (makePoint (2, 3)) testSeg
Segment {_segmentStart = Point {_positionX = 0.0, _positionY = 1.0}
, _segmentEnd = Point {_positionX = 2.0, _positionY = 3.0}}
One of the great things about lenses is that they are easy to compose:
GHCi> view (segmentEnd . positionY) testSeg
GHCi> 4.0
Note that when writing composed lenses, such as segmentEnd . positionY
, the order is from large to small. In this case, the lens that focuses on a point of the segment comes before the one that focuses on a coordinate of that point. While that might look a little surprising in contrast to how record accessors work (compare with the equivalent lens-less example at the beginning of this section), the (.)
used here is just the function composition operator we know and love.
Composition of lenses provide a way out of the nested record update quagmire. Here is a translation of the coordinate-doubling example using over
, through which we can apply a function to the value pointed at by a lens:
GHCi> over (segmentEnd . positionY) (2 *) testSeg
Segment {_segmentStart = Point {_positionX = 0.0, _positionY = 1.0}
, _segmentEnd = Point {_positionX = 2.0, _positionY = 8.0}}
These initial examples might look a bit magical at first. What makes it possible to use one and the same lens to get, set and modify a value? How come composing lenses with (.)
just works? Is it really so easy to write lenses without the help of makeLenses
? We will answer such questions by going behind the curtains to find what lenses are made of.
The scenic route to lenses
editThere are many ways to make sense of lenses. We will follow a sinuous yet gentle path, one which avoids conceptual leaps. Along the way, we will introduce a few different kinds of functional references. Following lens terminology, from now on we will use the word "optics" to refer collectively to the various species of functional references. As we will see, the optics in lens are interrelated, forming a hierarchy. It is this hierarchy which we are now going to explore.
Traversals
editWe will begin not with lenses, but with a closely related optic: traversals. The Traversable chapter discussed how traverse
makes it possible to walk across a structure while producing an overall effect:
traverse
:: (Applicative f, Traversable t) => (a -> f b) -> t a -> f (t b)
With traverse
, you can use any Applicative
you like to produce the effect. In particular, we have seen how fmap
can be obtained from traverse
simply by picking Identity
as the applicative functor, and that the same goes for foldMap
and Const m
, using Monoid m => Applicative (Const m)
:
fmap f = runIdentity . traverse (Identity . f)
foldMap f = getConst . traverse (Const . f)
lens takes this idea and lets it blossom.
Manipulating values within a Traversable
structure, as traverse
allows us to, is an example of targeting parts of a whole. As flexible as it is, however, traverse
only handles a rather limited range of targets. For one, we might want to walk across structures that are not Traversable
functors. Here is an entirely reasonable function that does so with our Point
type:
pointCoordinates
:: Applicative f => (Double -> f Double) -> Point -> f Point
pointCoordinates g (Point x y) = Point <$> g x <*> g y
pointCoordinates
is a traversal of Point
. It looks a lot like a typical implementation of traverse
, and can be used in pretty much the same way. The only difference is that Point
has a fixed type inside (Double
) instead of being a polymorphic type. Here is an adaptation of the rejectWithNegatives
example from the Traversable chapter:
GHCi> let deleteIfNegative x = if x < 0 then Nothing else Just x
GHCi> pointCoordinates deleteIfNegative (makePoint (1, 2))
Just (Point {_positionX = 1.0, _positionY = 2.0})
GHCi> pointCoordinates deleteIfNegative (makePoint (-1, 2))
Nothing
This generalised notion of a traversal that pointCoordinates
exemplifies is captured by one of the core types of lens: Traversal
.
type Traversal s t a b =
forall f. Applicative f => (a -> f b) -> s -> f t
Note
The forall f.
on the right side of the type
declaration means that any Applicative
can be used to replace f
. That makes it unnecessary to mention f
on the left side, or to specify which f
to pick when using a Traversal
.
With the Traversal
synonym, the type of pointCoordinates
can be expressed as:
Traversal Point Point Double Double
Let's have a closer look at what became of each type variable in Traversal s t a b
:
s
becomesPoint
:pointCoordinates
is a traversal of aPoint
.t
becomesPoint
:pointCoordinates
produces aPoint
(in someApplicative
context).a
becomesDouble
:pointCoordinates
targetsDouble
values in aPoint
(the X and Y coordinates of the points).b
becomesDouble
: the targetedDouble
values becomeDouble
values (possibly different than the original ones).
In the case of pointCoordinates
, s
is the same as t
, and a
is the same as b
. pointCoordinates
does not change the type of the traversed structure, or that of the targets in it, but that need not be the case. One example is good old traverse
, whose type can be expressed as:
Traversable t => Traversal (t a) (t b) a b
traverse
is able to change the types of the targeted values in the Traversable
structure and, by extension, the type of the structure itself.
The Control.Lens.Traversal module includes generalisations of Data.Traversable functions and various other tools for working with traversals.
Exercises |
---|
|
Setters
editNext in our programme comes the generalisation of the links between Traversable
, Functor
and Foldable
. We shall begin with Functor
.
To recover fmap
from traverse
, we picked Identity
as the applicative functor. That choice allowed us to modify the targeted values without producing any extra effects. We can reach similar results by picking the definition of a Traversal
...
forall f. Applicative f => (a -> f b) -> s -> f t
... and specialising f
to Identity
:
(a -> Identity b) -> s -> Identity t
In lens parlance, that is how you get a Setter
. For technical reasons, the definition of Setter
in Control.Lens.Setter is a little different...
type Setter s t a b =
forall f. Settable f => (a -> f b) -> s -> f t
... but if you dig into the documentation you will find that a Settable
functor is either Identity
or something very much like it, so the difference need not concern us.
When we take Traversal
and restrict the choice of f
we actually make the type more general. Given that a Traversal
works with any Applicative
functor, it will also work with Identity
, and therefore any Traversal
is a Setter
and can be used as one. The reverse, however, is not true: not all setters are traversals.
over
is the essential combinator for setters. It works a lot like fmap
, except that you pass a setter as its first argument in order to specify which parts of the structure you want to target:
GHCi> over pointCoordinates negate (makePoint (1, 2))
Point {_positionX = -1.0, _positionY = -2.0}
In fact, there is a Setter
called mapped
that allows us to recover fmap
:
GHCi> over mapped negate [1..4]
[-1,-2,-3,-4]
GHCi> over mapped negate (Just 3)
Just (-3)
Another very important combinator is set
, which replaces all targeted values with a constant. set setter x = over setter (const x)
, analogously to how (x <$) = fmap (const x)
:
GHCi> set pointCoordinates 7 (makePoint (1, 2))
Point {_positionX = 7.0, _positionY = 7.0}
Exercises |
---|
|
Folds
editHaving generalised the fmap
-as-traversal trick, it is time to do the same with the foldMap
-as-traversal one. We will use Const
to go from...
forall f. Applicative f => (a -> f b) -> s -> f t
... to:
forall r. Monoid r => (a -> Const r a) -> s -> Const r s
Since the second parameter of Const
is irrelevant, we replace b
with a
and t
with s
to make our life easier.
Just like we have seen for Setter
and Identity
, Control.Lens.Fold uses something slightly more general than Monoid r => Const r
:
type Fold s a =
forall f. (Contravariant f, Applicative f) => (a -> f a) -> s -> f s
Note
Contravariant
is a type class for contravariant functors. The key Contravariant
method is contramap
...
contramap :: Contravariant f => (a -> b) -> f b -> f a
... which looks a lot like fmap
, except that it, so to say, turns the function arrow around on mapping. Types parametrised over function arguments are typical examples of Contravariant
. For instance, Data.Functor.Contravariant defines a Predicate
type for boolean tests on values of type a
:
newtype Predicate a = Predicate { getPredicate :: a -> Bool }
GHCi> :m +Data.Functor.Contravariant
GHCi> let largerThanFour = Predicate (> 4)
GHCi> getPredicate largerThanFour 6
True
Predicate
is a Contravariant
, and so you can use contramap
to modify a Predicate
so that the values are adjusted in some way before being submitted to the test:
GHCi> getPredicate (contramap length largerThanFour) "orange"
True
Contravariant
has laws which are analogous to the Functor
ones:
contramap id = id
contramap (g . f) = contramap f . contramap g
Monoid r => Const r
is both a Contravariant
and an Applicative
. Thanks to the functor and contravariant laws, anything that is both a Contravariant
and a Functor
is, just like Const r
, a vacuous functor, with both fmap
and contramap
doing nothing. The additional Applicative
constraint corresponds to the Monoid r
; it allows us to actually perform the fold by combining the Const
-like contexts created from the targets.
Every Traversal
can be used as a Fold
, given that a Traversal
must work with any Applicative
, including those that are also Contravariant
. The situation parallels exactly what we have seen for Traversal
and Setter
.
Control.Lens.Fold
offers analogues to everything in Data.Foldable. Two commonly seen combinators from that module are toListOf
, which produces a list of the Fold
targets...
GHCi> -- Using the solution to the exercise in the traversals subsection.
GHCi> toListOf extremityCoordinates (makeSegment (0, 1) (2, 3))
[0.0,1.0,2.0,3.0]
... and preview
, which extracts the first target of a Fold
using the First
monoid from Data.Monoid.
GHCi> preview traverse [1..10]
Just 1
Getters
editSo far we have moved from Traversal
to more general optics (Setter
and Fold
) by restricting the functors available for traversing. We can also go in the opposite direction, that is, making more specific optics by broadening the range of functors they have to deal with. For instance, if we take Fold
...
type Fold s a =
forall f. (Contravariant f, Applicative f) => (a -> f a) -> s -> f s
... and relax the Applicative
constraint to merely Functor
, we obtain Getter
:
type Getter s a =
forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s
As f
still has to be both Contravariant
and Functor
, it remains being a Const
-like vacuous functor. Without the Applicative
constraint, however, we can't combine results from multiple targets. The upshot is that a Getter
always has exactly one target, unlike a Fold
(or, for that matter, a Setter
, or a Traversal
) which can have any number of targets, including zero.
The essence of Getter
can be brought to light by specialising f
to the obvious choice, Const r
:
someGetter :: (a -> Const r a) -> s -> Const r s
Since a Const r whatever
value can be losslessly converted to a r
value and back, the type above is equivalent to:
someGetter' :: (a -> r) -> s -> r
someGetter' k x = getConst (someGetter (Const . k) x)
someGetter g x = Const (someGetter' (getConst . g) x)
An (a -> r) -> s -> r
function, however, is just an s -> a
function in disguise (the camouflage being continuation passing style):
someGetter'' :: s -> a
someGetter'' x = someGetter' id x
someGetter' k x = k (someGetter'' x)
Thus we conclude that a Getter s a
is equivalent to a s -> a
function. From this point of view, it is only natural that it takes exactly one target to exactly one result. It is not surprising either that two basic combinators from Control.Lens.Getter are to
, which makes a Getter
out of an arbitrary function, and view
, which converts a Getter
back to an arbitrary function.
GHCi> -- The same as fst (4, 1)
GHCi> view (to fst) (4, 1)
4
Note
Given what we have just said about Getter
being less general than Fold
, it may come as a surprise that view
can work Fold
s and Traversal
s as well as with Getter
s:
GHCi> :m +Data.Monoid
GHCi> view traverse (fmap Sum [1..10])
Sum {getSum = 55}
GHCi> -- both traverses the components of a pair.
GHCi> view both ([1,2],[3,4,5])
[1,2,3,4,5]
That is possible thanks to one of the many subtleties of the type signatures of lens. The first argument of view
is not exactly a Getter
, but a Getting
:
type Getting r s a = (a -> Const r a) -> s -> Const r s
view :: MonadReader s m => Getting a s a -> m a
Getting
specialises the functor parameter to Const r
, the obvious choice for Getter
, but leaves it open whether there will be an Applicative
instance for it (i.e. whether r
will be a Monoid
). Using view
as an example, as long as a
is a Monoid
Getting a s a
can be used as a Fold
, and so Fold
s can be used with view
as long as the fold targets are monoidal.
Many combinators in both Control.Lens.Getter
and Control.Lens.Fold
are defined in terms of Getting
rather than Getter
or Fold
. One advantage of using Getting
is that the resulting type signatures tell us more about the folds that might be performed. For instance, consider hasn't
from Control.Lens.Fold
:
hasn't :: Getting All s a -> s -> Bool
It is a generalised test for emptiness:
GHCi> hasn't traverse [1..4]
False
GHCi> hasn't traverse Nothing
True
Fold s a -> s -> Bool
would work just as well as a signature for hasn't
. However, the Getting All
in the actual signature is quite informative, in that it strongly suggests what hasn't
does: it converts all a
targets in s
to the All
monoid (more precisely, to All False
), folds them and extracts a Bool
from the overall All
result.
Lenses at last
editIf we go back to Traversal
...
type Traversal s t a b =
forall f. Applicative f => (a -> f b) -> s -> f t
... and relax the Applicative
constraint to Functor
, just as we did when going from Fold
to Getter
...
type Lens s t a b =
forall f. Functor f => (a -> f b) -> s -> f t
... we finally reach the Lens
type.
What changes when moving from Traversal
to Lens
? As before, relaxing the Applicative
constraint costs us the ability to traverse multiple targets. Unlike a Traversal
, a Lens
always focuses on a single target. As usual in such cases, there is a bright side to the restriction: with a Lens
, we can be sure that exactly one target will be found, while with a Traversal
we might end up with many, or none at all.
The absence of the Applicative
constraint and the uniqueness of targets point towards another key fact about lenses: they can be used as getters. Contravariant
plus Functor
is a strictly more specific constraint than just Functor
, and so Getter
is strictly more general than Lens
. As every Lens
is also a Traversal
and therefore a Setter
, we conclude that lenses can be used as both getters and setters. That explains why lenses can replace record labels.
Note
On close reading, our claim that every Lens
can be used as a Getter
might seem rash. Placing the types side by side...
type Lens s t a b =
forall f. Functor f => (a -> f b) -> s -> f t
type Getter s a =
forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s
... shows that going from Lens s t a b
to Getter s a
involves making s
equal to t
and a
equal to b
. How can we be sure that is possible for any lens? An analogous issue might be raised about the relationship between Traversal
and Fold
. For the moment, this question will be left suspended; we will return to it in the section about optic laws.
Here is a quick demonstration of the flexibility of lenses using _1
, a lens that focuses on the first component of a tuple:
GHCi> _1 (\x -> [0..x]) (4, 1) -- Traversal
[(0,1),(1,1),(2,1),(3,1),(4,1)]
GHCi> set _1 7 (4, 1) -- Setter
(7,1)
GHCi> over _1 length ("orange", 1) -- Setter, changing the types
(6,1)
GHCi> toListOf _1 (4, 1) -- Fold
[4]
GHCi> view _1 (4, 1) -- Getter
4
Exercises |
---|
|
Composition
editThe optics we have seen so far fit the shape...
(a -> f b) -> (s -> f t)
... in which:
f
is aFunctor
of some sort;s
is the type of the whole, that is, the full structure the optic works with;t
is the type of what the whole becomes through the optic;a
is the type of the parts, that is, the targets withins
that the optic focuses on; andb
is the type of what the parts becomes through the optic.
One key thing those optics have in common is that they are all functions. More specifically, they are mapping functions that turn a function acting on a part (a -> f b
) into a function acting on the whole (s -> f t
). Being functions, they can be composed in the usual manner. Let's have a second look at the lens composition example from the introduction:
GHCi> let testSeg = makeSegment (0, 1) (2, 4)
GHCi> view (segmentEnd . positionY) testSeg
GHCi> 4.0
An optic modifies the function it receives as argument to make it act on a larger structure. Given that (.)
composes functions from right to left, we find that, when reading code from left to right, the components of an optic assembled with (.)
focus on progressively smaller parts of the original structure. The conventions used by the lens type synonyms match this large-to-small order, with s
and t
coming before a
and b
. The table below illustrates how we can look at what an optic does either a mapping (from small to large) or as a focusing (from large to small), using segmentEnd . positionY
as an example:
Lens | segmentEnd
|
positionY
|
segmentEnd . positionY
|
Bare type | Functor f => (Point -> f Point) -> (Segment -> f Segment) |
Functor f => (Double -> f Double) -> (Point -> f Point) |
Functor f => (Double -> f Double) -> (Segment -> f Segment) |
"Mapping" interpretation | From a function on Point to a function on Segment .
|
From a function on Double to a function on Point .
|
From a function on Double to a function on Segment .
|
Type with Lens |
Lens Segment Segment Point Point
|
Lens Point Point Double Double
|
Lens Segment Segment Double Double
|
Type with Lens' |
Lens' Segment Point
|
Lens' Point Double
|
Lens' Segment Double
|
"Focusing" interpretation | Focuses on a Point within a Segment
|
Focuses on a Double within a Point
|
Focuses on a Double within a Segment
|
Note
The Lens'
synonym is just convenient shorthand for lenses that do not change types (that is, lenses with s
equal to t
and a
equal to b
).
type Lens' s a = Lens s s a a
There are analogous Traversal'
and Setter'
synonyms as well.
The types behind synonyms such as Lens
and Traversal
only differ in which functors they allow in place of f
. As a consequence, optics of different kinds can be freely mixed, as long as there is a type which all of them fit. Here are some examples:
GHCi> -- A Traversal on a Lens is a Traversal.
GHCi> (_2 . traverse) (\x -> [-x, x]) ("foo", [1,2])
[("foo",[-1,-2]),("foo",[-1,2]),("foo",[1,-2]),("foo",[1,2])]
GHCi> -- A Getter on a Lens is a Getter.
GHCi> view (positionX . to negate) (makePoint (2,4))
-2.0
GHCi> -- A Getter on a Traversal is a Fold.
GHCi> toListOf (both . to negate) (2,-3)
[-2,3]
GHCi> -- A Getter on a Setter does not exist (there is no unifying optic).
GHCi> set (mapped . to length) 3 ["orange", "apple"]
<interactive>:49:15:
No instance for (Contravariant Identity) arising from a use of ‘to’
In the second argument of ‘(.)’, namely ‘to length’
In the first argument of ‘set’, namely ‘(mapped . to length)’
In the expression: set (mapped . to length) 3 ["orange", "apple"]
Operators
editSeveral lens combinators have infix operator synonyms, or at least operators nearly equivalent to them. Here are the correspondences for some of the combinators we have already seen:
Prefix | Infix |
---|---|
view _1 (1,2) |
(1,2) ^. _1
|
set _1 7 (1,2) |
(_1 .~ 7) (1,2)
|
over _1 (2 *) (1,2) |
(_1 %~ (2 *)) (1,2)
|
toListOf traverse [1..4] |
[1..4] ^.. traverse
|
preview traverse [] |
[] ^? traverse
|
lens operators that extract values (e.g. (^.)
, (^..)
and (^?)
) are flipped with respect to the corresponding prefix combinators, so that they take the structure from which the result is extracted as the first argument. That improves readability of code using them, as writing the full structure before the optics targeting parts of it mirrors how composed optics are written in large-to-small order. With the help of the (&)
operator, which is defined simply as flip ($)
, the structure can also be written first when using modifying operators (e.g. (.~)
and (%~)
). (&)
is particularly convenient when there are many fields to modify:
sextupleTest = (0,1,0,1,0,1)
& _1 .~ 7
& _2 %~ (5 *)
& _3 .~ (-1)
& _4 .~ "orange"
& _5 %~ (2 +)
& _6 %~ (3 *)
GHCi> sextupleTest
(7,5,-1,"orange",2,3)
A Swiss army knife
editThus far we have covered enough of lens to introduce lenses and show that they aren't arcane magic. That, however, is only the tip of the iceberg. lens is a large library providing a rich assortment of tools, which in turn realise a colourful palette of concepts. The odds are that if you think of anything in the core libraries there will be a combinator somewhere in lens that works with it. It is no exaggeration to say that a book exploring every corner of lens might be made as long as this one you are reading. Unfortunately, we cannot undertake such an endeavour right here. What we can do is briefly discussing a few other general-purpose lens tools you are bound to encounter in the wild at some point.
State
manipulation
edit
There are quite a few combinators for working with state functors peppered over the lens
modules. For instance:
use
fromControl.Lens.Getter
is an analogue ofgets
fromControl.Monad.State
that takes a getter instead of a plain function.Control.Lens.Setter
includes suggestive-looking operators that modify parts of a state targeted a setter (e.g..=
is analogous toset
,%=
toover
and(+= x)
toover (+x)
).- Control.Lens.Zoom offers the remarkably handy
zoom
combinator, which uses a traversal (or a lens) to zoom into a part of a state. It does so by lifiting a stateful computation into one that works with a larger state, of which the original state is a part.
Such combinators can be used to write highly intention-revealing code that transparently manipulates deep parts of a state:
import Control.Monad.State
stateExample :: State Segment ()
stateExample = do
segmentStart .= makePoint (0,0)
zoom segmentEnd $ do
positionX += 1
positionY *= 2
pointCoordinates %= negate
GHCi> execState stateExample (makeSegment (1,2) (5,3))
Segment {_segmentStart = Point {_positionX = 0.0, _positionY = 0.0}
, _segmentEnd = Point {_positionX = -6.0, _positionY = -6.0}}
Isos
editIn our series of Point
and Segment
examples, we have been using the makePoint
function as a convenient way to make a Point
out of (Double, Double)
pair.
makePoint :: (Double, Double) -> Point
makePoint (x, y) = Point x y
The X and Y coordinates of the resulting Point
correspond exactly to the two components of the original pair. That being so, we can define an unmakePoint
function...
unmakePoint :: Point -> (Double, Double)
unmakePoint (Point x y) = (x,y)
... so that makePoint
and unmakePoint
are a pair of inverses, that is, they undo each other:
unmakePoint . makePoint = id
makePoint . unmakePoint = id
In other words, makePoint
and unmakePoint
provide a way to losslessly convert a pair to a point and vice-versa. Using jargon, we can say that makePoint
and unmakePoint
form an isomorphism.
unmakePoint
might be made into a Lens' Point (Double, Double)
. Symmetrically. makePoint
would give rise to a Lens' (Double, Double) Point
, and the two lenses would be a pair of inverses. Lenses with inverses have a type synonym of their own, Iso
, as well as some extra tools defined in Control.Lens.Iso.
An Iso
can be built from a pair of inverses through the iso
function:
iso :: (s -> a) -> (b -> t) -> Iso s t a b
pointPair :: Iso' Point (Double, Double)
pointPair = iso unmakePoint makePoint
Iso
s are Lens
es, and so the familiar lens combinators work as usual:
GHCi> import Data.Tuple (swap)
GHCi> let testPoint = makePoint (2,3)
GHCi> view pointPair testPoint -- Equivalent to unmakePoint
(2.0,3.0)
GHCi> view (pointPair . _2) testPoint
3.0
GHCi> over pointPair swap testPoint
Point {_positionX = 3.0, _positionY = 2.0}
Additionally, Iso
s can be inverted using from
:
GHCi> :info from pointPair
from :: AnIso s t a b -> Iso b a t s
-- Defined in ‘Control.Lens.Iso’
pointPair :: Iso' Point (Double, Double)
-- Defined at WikibookLenses.hs:77:1
GHCi> view (from pointPair) (2,3) -- Equivalent to makePoint
Point {_positionX = 2.0, _positionY = 3.0}
GHCi> view (from pointPair . positionY) (2,3)
3.0
Another interesting combinator is under
. As the name suggests, it is just like over
, except that it uses the inverted Iso
that from
would give us. We will demonstrate it by using the enum
isomorphism to play with the Int
representation of Char
s without using chr
and ord
from Data.Char
explicitly:
GHCi> :info enum
enum :: Enum a => Iso' Int a -- Defined in ‘Control.Lens.Iso’
GHCi> under enum (+7) 'a'
'h'
newtype
s and other single-constructor types give rise to isomorphisms. Control.Lens.Wrapped exploits that fact to provide Iso
-based tools which, for instance, make it unnecessary to remember record label names for unwrapping newtype
s...
GHCi> let testConst = Const "foo"
GHCi> -- getConst testConst
GHCi> op Const testConst
"foo"
GHCi> let testIdent = Identity "bar"
GHCi> -- runIdentity testIdent
GHCi> op Identity testIdent
"bar"
... and that make newtype
wrapping for instance selection less messy:
GHCi> :m +Data.Monoid
GHCi> -- getSum (foldMap Sum [1..10])
GHCi> ala Sum foldMap [1..10]
55
GHCi> -- getProduct (foldMap Product [1..10])
GHCi> ala Product foldMap [1..10]
3628800
Prisms
editWith Iso
, we have reached for the first time a rank below Lens
in the hierarchy of optics: every Iso
is a Lens
, but not every Lens
is an Iso
. By going back to Traversal
, we can observe how the optics get progressively less precise in what they point to:
- An
Iso
is an optic that has exactly one target and is invertible. - A
Lens
also has exactly one target but is not invertible. - A
Traversal
can have any number of targets and is not invertible.
Along the way, we first dropped invertibility and then the uniqueness of targets. If we follow a different path by dropping uniqueness before invertibility, we find a second kind of optic between isomorphisms and traversals: prisms. A Prism
is an invertible optic that need not have exactly one target. As invertibility is incompatible with multiple targets, we can be more precise: a Prism
can reach either no targets or exactly one target.
Aiming at a single target with the possibility of failure sounds a lot like pattern matching, and prisms are indeed able to capture that. If tuples and records provide natural examples of lenses, Maybe
, Either
and other types with multiple constructors play the same role for prisms.
Every Prism
is a Traversal
, and so the usual combinators for traversals, setters and folds all work with prisms:
GHCi> set _Just 5 (Just "orange")
Just 5
GHCi> set _Just 5 Nothing
Nothing
GHCi> over _Right (2 *) (Right 5)
Right 10
GHCi> over _Right (2 *) (Left 5)
Left 5
GHCi> toListOf _Left (Left 5)
[5]
A Prism
is not a Getter
, though: the target might not be there. For that reason, we use preview
rather than view
to retrieve the target:
GHCi> preview _Right (Right 5)
Just 5
GHCi> preview _Right (Left 5)
Nothing
For inverting a Prism
, we use re
and review
from Control.Lens.Review. re
is analogous to from
, though it gives merely a Getter
. review
is equivalent to view
with the inverted prism.
GHCi> view (re _Right) 3
Right 3
GHCi> review _Right 3
Right 3
Just like there is more to lenses than reaching record fields, prisms are not limited to matching constructors. For instance, Control.Lens.Prism defines only
, which encodes equality tests as a Prism
:
GHCi> :info only
only :: Eq a => a -> Prism' a ()
-- Defined in ‘Control.Lens.Prism’
GHCi> preview (only 4) (2 + 2)
Just ()
GHCi> preview (only 5) (2 + 2)
Nothing
The prism
and prism'
functions allow us to build our own prisms. Here is an example using stripPrefix
from Data.List
:
GHCi> :info prism
prism :: (b -> t) -> (s -> Either t a) -> Prism s t a b
-- Defined in ‘Control.Lens.Prism’
GHCi> :info prism'
prism' :: (b -> s) -> (s -> Maybe a) -> Prism s s a b
-- Defined in ‘Control.Lens.Prism’
GHCi> import Data.List (stripPrefix)
GHCi> :t stripPrefix
stripPrefix :: Eq a => [a] -> [a] -> Maybe [a]
prefixed :: Eq a => [a] -> Prism' [a] [a]
prefixed prefix = prism' (prefix ++) (stripPrefix prefix)
GHCi> preview (prefixed "tele") "telescope"
Just "scope"
GHCi> preview (prefixed "tele") "orange"
Nothing
GHCi> review (prefixed "tele") "graph"
"telegraph"
prefixed
is available from lens, in the Data.List.Lens module.
Exercises |
---|
|
Laws
editThere are laws specifying how sensible optics should behave. We will now survey those that apply to the optics that we covered here.
Starting from the top of the taxonomy, Fold
does not have laws, just like the Foldable
class. Getter
does not have laws either, which is not surprising, given that any function can be made into a Getter
via to
.
Setter
, however, does have laws. over
is a generalisation of fmap
, and is therefore subject to the functor laws:
over s id = id
over s g . over s f = over s (g . f)
As set s x = over s (const x)
, a consequence of the second functor law is that:
set s y . set s x = set s y
That is, setting twice is the same as setting once.
Traversal
laws, similarly, are generalisations of the Traversable
laws:
t pure = pure
fmap (t g) . t f = getCompose . t (Compose . fmap g . f)
The consequences discussed in the Traversable chapter follow as well: a traversal visits all of its targets exactly once, and must either preserve the surrounding structure or destroy it wholly.
Every Lens
is a Traversal
and a Setter
, and so the laws above also hold for lenses. In addition, every Lens
is also a Getter
. Given that a lens is both a getter and a setter, it should get the same target that it sets. This common sense requirement is expressed by the following laws:
view l (set l x z) = x
set l (view l z) z = z
Together with the "setting twice" law of setters presented above, those laws are commonly referred to as the lens laws.
Analogous laws hold for Prism
s, with preview
instead of view
and review
instead of set
:
preview p (review p x) = Just x
review p <$> preview p z = Just z -- If preview p z isn't Nothing.
Iso
s are both lenses and prisms, so all of the laws above hold for them. The prism laws, however, can be simplified, given that for isomorphisms preview i = Just . view i
(that is, preview
never fails):
view i (review i x) = x
review i (view i z) = z
Polymorphic updates
editWhen we look at optic types such as Setter s t a b
and Lens s t a b
we see four independent type variables. However, if we take the various optic laws into account we find out that not all choices of s
, t
, a
and b
are reasonable. For instance, consider the "setting twice" law of setters:
set s y . set s x = set s y
For "setting twice is the same than setting once" to make sense, it must be possible to set twice using the same setter. As a consequence, the law can only hold for a Setter s t a b
if t
can somehow be specialised so that it becomes equal to s
(otherwise the type of the whole would change on every set
, leading to a type mismatch).
From considerations about the types involved in the laws such as the one above, it follows that the four type parameters in law-abiding Setter
s, Traversal
s, Prism
s and Lens
es are not fully independent from each other. We won't examine the interdependency in detail, but merely point out some of its consequences. Firstly, a
and b
are cut from the same cloth, in that even if an optic can change types there must be a way of specialising a
and b
to make them equal; furthermore, the same holds for s
and t
. Secondly, if a
and b
are equal then s
and t
must be equal as well.
In practice, those restrictions mean that valid optics that can change types usually have s
and t
parametrised in terms of a
and b
. Type-changing updates in this fashion are often referred to as polymorphic updates. For the sake of illustration, here are a few arbitrary examples taken from lens:
-- To avoid distracting details,
-- we specialised the types of argument and _1.
mapped :: Functor f => Setter (f a) (f b) a b
contramapped :: Contravariant f => Setter (f b) (f a) a b
argument :: Setter (b -> r) (a -> r) a b
traverse :: Traversable t => Traversal (t a) (t b) a b
both :: Bitraversable r => Traversal (r a a) (r b b) a b
_1 :: Lens (a, c) (b, c) a b
_Just :: Prism (Maybe a) (Maybe b) a b
At this point, we can return to the question left open when we presented the Lens
type. Given that Lens
and Traversal
allow type changing while Getter
and Fold
do not, it would be indeed rash to say that every Lens
is a Getter
, or that every Traversal
is a Fold
. However, the interdependence of the type variables mean that every lawful Lens
can be used as a Getter
, and every lawful Traversal
can be used as a Fold
, as lawful lenses and traversals can always be used in non type-changing ways.
No strings attached
editAs we have seen, we can use lens to define optics through functions such as lens
and auto-generation tools such as makeLenses
. Strictly speaking, though, these are merely convenience helpers. Given that Lens
, Traversal
and so forth are just type synonyms, their definitions are not needed when writing optics − for instance, we can always write Functor f => (a -> f b) -> (s -> f t)
instead of Lens s t a b
. That means we can define optics compatible with lens without using lens at all! In fact, any Lens
, Traversal
, Setter
or Getting
can be defined with no dependencies other than the base package.
The ability to define optics without depending on the lens library provides considerable flexibility in how they can be leveraged. While there are libraries that do depend on lens, library authors are often wary of acquiring a dependency on large packages with several dependencies such as lens, especially when writing small, general-purpose libraries. Such concerns can be sidestepped by defining the optics without using the type synonyms or the helper tools in lens. Furthermore, the types being only synonyms makes it possible to have multiple optic frameworks (i.e. lens and similar libraries) that can be used interchangeably.
Further reading
edit- Several paragraphs above, we said that lens easily provides enough material for a full book. The closest thing to that we currently have is Artyom Kazak's "lens over tea" series of blog posts. It explores the implementation of functional references in lens and the concepts behind it in far more depth than what we are able to do here. Highly recommended reading.
- Useful information can be reached through lens' GitHub wiki, and of course lens' API documentation is well worth exploring.
- lens is a large and complex library. If you want to study its implementation but would rather begin with something simpler, a good place to start are minimalistic lens-compatible libraries such as microlens and lens-simple.
- Studying (and using!) optic-powered libraries is a good way to get the hang of how functional references are used. Some arbitrary examples:
- diagrams, a vector graphics library that uses lens extensively to deal with properties of graphic elements.
- wreq, a web client library with a lens-based interface.
- xml-lens, which provides optics for manipulating XML.
- formattable, a library for date, time and number formatting. Formattable.NumFormat is an example of a module that provides lens-compatible lenses without depending on the lens package.