Implementing basic Haskell lenses in twenty exercises
Lenses are purely functional references to pieces of data.
They let us focus on a specific part of a structure, to see it more closely.
The inner workings of lenses have a reputation for being difficult to learn. This isn’t entirely fair—for example, I think monads are harder to gain a good intuition for. However, there are many different things that go into learning lenses, so the difficulty of putting them all together adds up.
Some of the perceived difficulty probably comes from seeing code like this:
a & b %~ (c ^. _1)Admittedly, this is near-impossible for a beginner to understand. Even worse, its components are tough to search for when attempting to piece it apart! However, with enough background for how lenses work, and some helpful mnemonics, even this code will eventually become readable.
Besides strange unreadable operators, lenses often have confusing type signatures, can be autogenerated by Template Haskell (for ease of use, but not ease of understanding), and are called in where your normal tools fall apart—whenever you need to operate on deeply nested, complicated structures.
In this post I’d like to mainly focus not on how to use lenses, but on how to write them yourself. I think this tends to (eventually) lead to deeper levels of understanding.
Many fields don’t have the luxury of being able to pry open the things they’re working with at almost any level of abstraction. Physicists can’t construct alternate universes to play with (yet). Poets who want to invent a new language just for their poetry will have a hard time finding an audience.
Luckily, in programming we can build our own tools as we go along. It’s worth quite a bit of effort to do so, and the rewards in terms of deeper understanding can be impressive.
For these reasons, we’ll be focusing on how lenses work on the
inside. You’ll be building your own little optics library, including
Getter, Setter and of course
Lens.
There are 20 exercises (the bits with the blue backgrounds) strewn throughout. I’ve provided answers for all but one of them, since that one is more open-ended and meant to help you start your own exploration. When answers appear, they’re presented inline, but inside spoiler blocks.
I highly recommend actually following along and writing the code, but I won’t tell anybody if you just want to breeze through.
Code accompanying this post can be found in this github repo
Let’s talk about a function! Functional programmers like those, right? The specific one I have in mind is
get :: s -> awhich takes some “source” structure of type s and gives
us back our desired value of type a.
We can make a fun newtype from this. Since it’s fairly simple and
it’s used for getting values, we’ll call it a
SimpleGetter.
newtype SimpleGetter s a =
SimpleGetter (s -> a)Here’s the first exercise!
Consider the function
fst :: (a, b) -> afrom a tuple to its first element. Use this function to construct a
valid SimpleGetter.
If you wrote SimpleGetter fst then
congratulations! Let’s take a closer look at it, especially at its type
signature
SimpleGetter (a, b) aThis means our type s is (a, b) and our
type a is…well, a. This
SimpleGetter thing is really simple! If you think about it
though, that’s not very surprising. A SimpleGetter is just
a function from s to a. With that in mind,
some other things we can write SimpleGetters to get are
Unfortunately, even though we can do all these things,
SimpleGetter can’t do them with just a type. We need a
function to actually run! This function is traditionally called
view.
Write a function
view :: SimpleGetter s a -> s -> athat actually gets a value of type a back from a
SimpleGetter. You can test it by making sure that
view (SimpleGetter fst) (1, 2)gives back 1
Hopefully this exercise isn’t too bad. We’ve already got all the
components, so we just have to unwrap the newtype to produce
view, our first function that works with a Haskell
optic!
view (SimpleGetter get) s = get sIt’s also time for us to define the first of many operators
(^.), and the first of many mnemonics for remembering
operators. There are a couple mnemonics to choose from here. An
upside-down V (from “view”) looks kind of like a
^. The caret also looks kind of like something being
extracted from the ground (so we can view it). Anyways, we define
^. like
infixl 8 ^.
(^.) :: s -> SimpleGetter s a -> a
(^.) = flip viewThe arguments are flipped in such a way that they kind of match the
order you may be used to from imperative languages. For example,
a.getB() would be something like a ^. b. We’ll
see this ordering thing come up again in a moment.
Before that though, there’s one more thing we should do with our
SimpleGetter, so long as it’s sitting around.
SimpleGetter is isomorphic to a plain function
f :: s -> a. Write a function
toSimpleGetter that can take f and give us
back a SimpleGetter.
Alright, so that one was pretty easy too. But it’s good to be able to write these kinds of functions, since we’ll be writing similar ones as we deal with more complicated optics. A simple solution looks like
toSimpleGetter :: (s -> a) -> SimpleGetter s a
toSimpleGetter f = SimpleGetter fThis also gets us a fun new ability! Or rather, a new way to do
something we were already quite capable of doing. Since ^.
gets an a from a SimpleGetter, and
toSimpleGetter gets a SimpleGetter from an
s -> a, combining the two as
x ^. toSimpleGetter f is just function
application—f x.
Let’s get back to the comment about the order of operations feeling
like object-oriented programming. Haskell lens
libraries—Control.Lens, Lens.Micro, and
others—often feature lens composition (.) that feels
“backwards” to functional programmers, but the right way around to
people from a more object-oriented background.
To understand why this is, we’ll be digging into continuation-passing style a little bit, and then talking about contravariant functors. The “backwardness” of contravariance will then help us explain why optic composition can feel like it goes the wrong way.
Continuation passing converts a function into a function that takes a callback. That is, if we have a function
f :: s -> awe will also pass in a callback, something to do once we have an
a, which changes our function’s type to
f :: (a -> r) -> s -> rRewrite the function
length :: String -> Intin continuation-passing style as
lengthCont :: (Int -> r) -> String -> rand test that it works by passing in the callback
(*2)
So, for this exercise, we have to define length, but
with a callback function as its first parameter, and then we have to
call that callback once we get the string’s length.
lengthCont callback str =
callback $ length strWe can now test that
lengthCont (*2) "hello"evaluates to 10.
Let’s also do the same kind of transformation to our
SimpleGetter to write a Getter (it’s no longer
very simple). Instead of it being a newtype wrapper around a plain
function, we’ll change it to use continuation-passing style, so that
it’ll better compose with other optics we add later.
The type signature might be a little confusing, so bear with me. All
we’re really going to do is replace r with a contravariant
functor over s and a.
Contravariant is like a normal functor, but the order
feels “backwards”. Check out its typeclass
class Contravariant f where
contramap :: (a -> b) -> f b -> f aComparing this to the type signature of fmap, we can
pretty quickly see where the backwardness comes from. The last two
arguments are flipped.
fmap :: (a -> b) -> f a -> f bIt amuses me that the usual operator for contramap is
>$<, as opposed to fmap’s
<$>.
For a little bit of practice with contramap, write a
Contravariant instance for this MakeString
newtype.
newtype MakeString a =
MakeString { mkString :: a -> String }
instance Contravariant MakeString where
contramap = _While you’re playing around with this, note that usual functors with
fmap are what is called “covariant”. In contravariance,
lifted functions go the opposite direction (what we’ve been calling
“backwards”) as plain functions. Covariance just means functions at both
levels go in the same direction.
contramap for MakeString might look a
little something like this.
contramap f (MakeString mkStr) =
MakeString (mkStr . f)All of this machinery has been leading up to defining our first real
Getter. It combines ideas from continuation-passing style,
contravariance, Const functors, and of course just plain
function composition, so don’t worry if it’s a little tricky to figure
out what’s going on at first. Here’s the type signature of
Getter, where f is our contravariant functor
since we need it to work in both directions. You’ll also need
RankNTypes enabled for most of the code from here on
out.
{-# LANGUAGE RankNTypes #-}
type Getter s a =
forall f. (Contravariant f, Functor f)
=> (a -> f a) -> s -> f sWrite the function view (or equivalently,
^.) for a Getter (a, b) a. Remember, it should
act similarly to the function fst :: (a, b) -> a, but
will compose in the opposite order.
This exercise is tough. You’ll probably want Const in
your toolkit.
newtype Const a b = Const { getConst :: a }
instance Functor (Const m)
where fmap _ (Const a) = Const a
instance Contravariant (Const m)
where contramap _ (Const b) = Const bGive this exercise a try, and if you’re still lost, then feel free to
keep reading. One good thing to remember is that if you put
_ instead of a real value, GHC will find the “type hole”
and give you some information about what could possibly go in it. Good
luck!
Just for fun, we’ll implement the operator version first here.
(^.) :: s -> Getter s a -> a
s ^. g = getConst (g Const s)
view :: Getter s a -> s -> a
view g s = s ^. gWhat is going on here? Let’s take it piece by piece. First, we name
our Getter “g” and our structure of type
s “s”. g Const s is applying two
arguments to our Getter type. We can think of those two
arguments as Const :: a -> f a and s :: s.
Finally, of course, our return value will be something of type
f s. This value gets passed to getConst, which
extracts the final value out.
Congratulations! You’ve written your first Haskell optic.
The Getter type above is the same as in
Control.Lens, which means it has the full general power of
those Getters. To simplify our understanding a bit, we can
specialize f to Const r and use this
Getter type:
type Getter s a =
forall r. (a -> Const r a) -> s -> Const r sI recommend trying out this Const r version of
Getter for the next exercise, unless you happen to
know/find the generalization here early!
Remember that list of things we said a SimpleGetter
could get? Write Getters to get them.
Hopefully this exercise is more tedious than difficult, once you
figure out how to write one of the Getters
headGetter :: Getter [a] a
headGetter f = Const . getConst . f . head
nestedGetter :: Getter (a, ((b, (c, d)), e)) d
nestedGetter f = Const . getConst . f . snd . snd . fst . snd
everyThirdGetter :: Getter [a] [a]
everyThirdGetter f = Const . getConst . f . everyThird
where everyThird (_:_:x:xs) = x : everyThird xs
everyThird _ = []
succGetter :: Getter Integer Integer
succGetter f = Const . getConst . f . succ
idGetter :: Getter a a
idGetter = id -- bit of a special caseSome of those Getters are deeply useful in practice,
while others don’t come up that much, but should be good training for
writing Getters.
You’ve probably noticed a pattern here (if not, then I applaud your
clever solution) of using Const . getConst which has type
Const r a -> Const r s. There’s actually a more-general
way to do this operation, called phantom. Just like our
general Getter, phantom operates on
contravariant functors, and is useful to go from an f a to
a f b. It uses <$, which is just
fmap . const, but also the likely-unfamiliar
$<, which is a flipped version of
contramap . const.
phantom :: (Contravariant f, Functor f) => f a -> f b
phantom x = () <$ x $< ()Write toGetter :: (s -> a) -> Getter s a that
turns a function into a Getter. Remember this is possible
because Getters are isomorphic to plain old functions. Use
phantom to unlock the fully general power of
Getters.
If you did the exercise above, you should be able to spot the generalization available here
toGetter :: (s -> a) -> Getter s a
toGetter get f =
phantom . f . getJust like how a Getter is analogous to a plain function,
a Setter is analogous to a plain Functor.
Using a Setter is like fmapping over a
structure.
Let’s get right into the thick of things. Similar to how our
Getter implementation used the Const functor,
Setter is going to use Identity. The
definition for Identity looks like
newtype Identity a =
Identity { runIdentity :: a }
instance Functor Identity
where fmap = coerceBy the way, if you’d like more information on how to use
Identity or coercions (especially the
Coercible composition operator (#.)) I might
recommend reading Composing Coercions
before moving on. Be warned that it gives away the implementation for
set (which is an exercise below), but if you get stuck when
implementing set it could be a good first resource to look
at.
Anyways, just like with Getter, let’s start with a
SimpleSetter. Don’t worry, we’ll be getting rid of this one
rather quickly. Full-blown setters are way more powerful and fun to play
with.
The type of fmap is
(a -> b) -> f a -> f b. Come up with a type for a
SimpleSetter s a that wraps transformed values in the
Identity functor, and replaces the functor f
from the definition of fmap with the arbitrary structure
s (which we can think of as having an a
inside).
Immediately, here’s another exercise, but using the answer to the previous exercise
The type of a SimpleSetter looks like
type SimpleSetter s a =
(a -> Identity a) -> s -> Identity sGeneralize this to make a LessSimpleSetter s t a b.
s is the “source” structure and t is the
“target” structure. a is the type of the initial value we
put in, and b is the type of the transformed value.
Here’s what you should have now:
type LessSimpleSetter s t a b =
(a -> Identity b) -> s -> Identity tOnce again, we’ll quickly jump into another exercise. It’ll help to
know that the definition of Settable is
class ( Applicative f
, Distributive f
, Traversable f
) => Settable fMake one more generalization, this time from Identity
functors to any Settable. That is, change the constraints
on the type of f from Identity to any
Settable.
What we have now is the same Setter type as defined in
Control.Lens.
type Setter s t a b =
forall f. Settable f =>
(a -> f b) -> s -> f tLike view for Getter, Setter’s
main action—changing values inside structures—is called
set, which works like this
set mySetter newValue structureWe’re “setting” a pure functional value using a setter! Of course,
what we’re really doing is more like “replacing”. The operator
equivalent of set is .~, so if we see
mySetter .~ newValue myStructureWe can read it as “set newValue in
myStructure using mySetter”.
Using the above example call as a guide (pay attention to the order
the values come in!), write the type signature for set.
The type signature for set looks like this. Note that we
never have to pass in a value of type a—since it’s being
overwritten with a new value of type b, it doesn’t really
matter what was there before.
set :: Setter s t a b -> b -> s -> tImplement set. If you’re struggling with finding the
right machinery, use type holes and perhaps think about some of the
useful functors we’ve seen along the way.
I recommend looking up the #. operator, as it makes the
implementation cleaner.
One implementation of set looks like
set s b = runIdentity #. s (\_ -> Identity b)Say I give you
setter :: Setter (Int, String) (String, String) Int StringHow would you change (1, "world") into
("hello", "world")?
This we can figure out by following the types. It also feels quite a bit like a function call in some imperative language.
setter .~ "Hello" (1, "world")One easy generalization for set is to make it take a
function instead of a constant value. The usual name for such a function
is over. We can always recover set from
over with a simple
set setter x = over setter (const x).
Implement
over :: Setter s t a b -> (a -> b) -> s -> tover hits a sweet spot. It’s general enough to be really
powerful, but not so general that figuring out how to write it is
trivial.
over setter f =
runIdentity #. setter (Identity #. f)Something surprising and magical has just happened. We’ve unlocked
the front gate to the operator zoo for Haskell lenses. Using
over, or its operator version (%~), we can get
all kinds of helpful setters by passing useful functions to
over.
For example, in programming languages with mutable data, you often
see a += operator to add to a number. The
Setter version of this looks like +~, as is
implemented by…well, you tell me.
Implement +~ which uses a Setter to add to
a Num.
Hopefully that one wasn’t too bad, at least compared to implementing
over!
(+~) :: Num a => Setter s t a a -> a -> s -> t
setter +~ a = over setter (+a)Tons of useful operators have Setter forms. Along with
+~, there are operators like -~,
*~, /~, &&~,
<>~, etc. The key thing to remember here is that the
squiggle means Setter.
There are also Setters specifically for handling
Maybe and State values, which come in
handy.
Just like how .~ means set, and
%~ means over, .= means “set
state” and %= means “modify state”. Implement both. It
might help to know the signature of (.=) as a starting
point.
(.=) :: MonadState s m => Setter s s a b -> b -> m ()This exercise shows some of the similarities between operating within a stateful monad, and using a setter. Both are ways to imagine doing something like imperative programming, but in a purely functional way.
(.=) :: MonadState s m => Setter s s a b -> b -> m ()
setter .= b = modify $ set setter b
(%=) :: MonadState s m => Setter s s a b -> (a -> b) -> m ()
setter %= f = modify $ over setter fWe’re getting really close to imperative programming now, what with all this setting and manipulation of state. Let’s take advantage of that for a simple version of a stateful environment: a game.
Use your newfound Setter skills to implement a game of
Higher/Lower. In this game, one player picks a number and the other
player has to guess it in as few guesses as possible. For each guess,
the first player responds with either “higher” or “lower”. Use
MonadState to maintain the state of previous guesses, and
Setter to update those bounds.
Lenses are among the most useful, and certainly among the
most-talked-about kinds of optics. You can think of a Lens
as combining a Setter and a Getter to provide
a purely functional reference to some piece of data.
They’re especially useful when working with deeply nested data structures, since they save the programmer from having to unpack and repack the structure every time they want to manipulate one of its inner elements.
The type of a Lens is
type Lens s t a b =
forall f. Functor f =>
(a -> f b) -> s -> f tJust like we had SimpleSetter and
SimpleGetter, we can also have a SimpleLens by
reducing generalization and making the source and target types the
same.
Write the type for a SimpleLens, using the more-general
type for Lens
This exercise isn’t too bad. We just make the source and target types the same for both the structure and the value within it.
type SimpleLens s a = Lens s s a aLenses really are just the combination of a getting
function and a setting function. Here, why don’t you prove that?
Write this function which takes a getter function and a setter
function and makes a Lens
makeLens :: (s -> a) -> (s -> b -> t) -> Lens s t a bThis exercise is a bit tricky, so I’ve broken it down into a few
parts and tried to name them appropriately.
get :: s -> a and set :: s -> b -> t
should both be pretty straightforward to understand.
transform :: a -> f b transforms our a into
a b and also wraps it in a Functor called
f. structure :: s should also be clear.
Reading from right to left, we first get a value from
our structure. This value has type a. We then
transform that value, to get an f b. We then
fmap a set structure on this f b,
to get out an f t (set structure has type
b -> t, and so the lifted version is
f b -> f t).
makeLens get set transform structure =
set structure <$> transform (get structure)This actually works in a fairly intuitive way. To do something to a
value, first we have to get it from our structure, then we
can transform it in some way, and then we have to
set that newly-transformed value in the structure.
Here’s another crazy operator. We write %%~ to indicate
that the left side has a lens, and the right side has a transform
function and some structure of data that our lens can operate on.
Write
(%%~) ::
Functor f =>
Lens s t a b -> (a -> f b) -> s -> f twhich takes a Lens, a transformation function, and a
structure and gives back a value of f t.
Alright, so that last exercise is a little cheesy. The answer is
(%%~) = idTo double-check this, look at the types of Lens and
%%~ and groan.
Congratulations! If you’ve completed all twenty exercises, you’ve probably got a decent understanding of how basic lenses work under the hood, but there’s definitely plenty more left to learn about the wild and wonderful world of Haskell optics. Like with anything else, the best way to solidify your knowledge is with practice, which is why I tried to focus so heavily on the exercises here. I hope this post was at least somewhat helpful.
Haskell isn’t the only language with lenses, of course. I’ve also
seen them in PureScript, and have even used these concepts in Elm
(though it was called a Focus). You could also write them
in your favorite non-purely-functional language, though those languages
usually already have idiomatic mutable ways to affect some piece of a
large data structure. (Unfortunately those languages don’t often provide
strong guarantees like the type safety you maintain by using
lenses.)
One more fantastic thing about Lenses is that they
compose! Programmers love things that compose nicely. This composition
is especially nice for lenses because it lets us combine them over very
complicated data structures in straightforward ways, maintaining pure
functional style the whole way.
Again, code accompanying this post can be found in this github repo