Pointwise Lenses
Lenses are a current hot topic in the Haskell community, with a bunch of packages providing implementations (data-accessor, fclabels, lens, amongst others). Although we will recall definitions, this post is not meant as an introduction to lenses. If you have not worked with lenses before, the talk from Simon Peyton Jones or the blog post by Sebastiaan Visser about fclabels are good starting points.
In this blog post we will propose a generalization to the lens representation
used in fclabels
and in many other packages (with various minor variations);
we will consider the relation to the representation used in lens
in a
separate section.
If you wanted to follow along, this is the header I am using:
{-# LANGUAGE FlexibleInstances, RankNTypes, TupleSections #-}
import Prelude hiding ((.), id, const, curry, uncurry)
import Control.Arrow
import Control.Applicative
import Control.Category
import Control.Monad
import Control.Monad.Free
import Control.Monad.Trans.Class
import Data.Functor.Identity
import Data.Functor.Compose
import Data.Traversable
import qualified Data.Traversable as Traversable
-- We define some Show instances just for the examples
instance Show a => Show (Compose [] Identity a) where
show (Compose a) = show a
instance Show a => Show (Compose [] (Compose [] Identity) a) where
show (Compose a) = show a
instance Show a => Show (Identity a) where
show (Identity a) = show a
Basics
A lens from a to b is a way to get a b from an a, and to modify an a given a modification of b:
data Lens a b = Lens {
lensGet :: a -> b
lensModify :: (b -> b) -> (a -> a)
, }
A simple example is a lens for the first component of a pair:
lensFst :: Lens (a, b) a
= Lens fst first lensFst
Importantly, lenses can be composed—they form a category:
instance Category Lens where
id = Lens id id
Lens g m . Lens g' m' = Lens (g . g') (m' . m)
Motivation
Suppose we have a lens from somewhere to a list of pairs:
lensFromSomewhere :: Lens Somewhere [(Int, Char)]
We would like to be able to somehow compose lensFromSomewhere
with lensFst
to get a lens from Somewhere
to [Int]
. The obvious thing to do is to try
and define
mapLens :: Lens a b -> Lens [a] [b]
Lens g m) = Lens (map g) _ mapLens (
The getter is easy enough: we need to get a [b]
from a [a]
, and we have
a function from b -> a
, so we can just map. We get stuck in the modifier,
however: we need to give something of type
-> [b]) -> [a] -> [a] ([b]
given only a modifier of type (b -> b) -> (a -> a)
, and there is simply no
way to do that.
If you think about it, there is a conceptual problem here too. Suppose that we did somehow manage to define a lens of type
weirdLens :: Lens [(Int, Char)] [Int]
This means we would have a modifier of type
weirdModify :: ([Int] -> [Int]) -> [(Int, Char)] -> [(Int, Char)]
What would happen if we tried
1 :) weirdModify (
to insert one Int
into the list? Which (Int, Char)
pair would we insert
into the original list?
Pointwise lenses
What we wanted, really, is a lens that gave us a [Int]
from a [(Int, Char)]
, and that modified a [(Int, Char)]
given a modifier of type Int -> Int
: we want to apply the modifier pointwise at each element of the list. For
this we need to generalize the lens datatype with a functor f:
data PLens f a b = PLens {
plensGet :: a -> f b
plensModify :: (b -> b) -> (a -> a)
, }
It is easy to see that PLens
is strictly more general than Lens
: every lens
is also a Pointwise lens by choosing Identity
for f. Here’s a lens for the
first component of a pair again:
plensFst :: PLens Identity (a, b) a
= PLens (Identity . fst) first plensFst
Note that the type of the modifier is precisely as it was before. As a simple but more interesting example, here is a lens from a list to its elements:
plensList :: PLens [] [a] a
= PLens id map plensList
You can think of plensList
as shifting the focus from the set as a whole to
the elements of the set, not unlike a zipper.
Composition
How does composition work for pointwise lenses?
compose :: Functor f => PLens g b c -> PLens f a b -> PLens (Compose f g) a c
PLens g m) (PLens g' m') = PLens (Compose . fmap g . g') (m' . m) compose (
The modifier is unchanged. For the getter we have a getter from a -> f b
and
a getter from b -> g c
, and we can compose them to get a getter from a -> f (g c)
.
As a simple example, suppose we have
exampleList :: [[(Int, Char)]]
= [[(1, 'a'), (2, 'b')], [(3, 'c'), (4, 'd')]] exampleList
Then we can define a lens from a list of list of pairs to their first coordinate:
exampleLens :: PLens (Compose [] (Compose [] Identity)) [[(a, b)]] a
= plensFst `compose` plensList `compose` plensList exampleLens
Note that we apply the plensList
lens twice and then compose with plensFst
.
If we get
with this lens we get a list of lists of Int
s, as expected:
> plensGet exampleLens exampleList
1,2],[3,4]] [[
and we modify pointwise:
> plensModify exampleLens (+1) exampleList
2,'a'),(3,'b')],[(4,'c'),(5,'d')]] [[(
Category Instance
As we saw in the previous section, in general the type of the lens changes as we compose. We can see from the type of a lens where the focus is: shifting our focus from a list of list, to the inner lists, to the elements of the inner lists:
PLens Identity [[a]] [[a]]
PLens (Compose [] Identity) [[a]] [a]
PLens (Compose [] (Compose [] Identity)) [[a]] a
However, if we want to give a Category
instance then we need to be able to
keep f constant. This means that we need to be able to define a getter of
type a -> f c
from two getters of type a -> f b
and b -> f c
; in other
words, we need f to be a monad:
instance Monad f => Category (PLens f) where
id = PLens return id
PLens g m . PLens g' m' = PLens (g <=< g') (m' . m)
This is however less of a restriction that it might at first sight seem. For
our examples, we can pick the free monad on the list functor (using
Control.Monad.Free
from the free
package):
plensFst' :: PLens (Free []) (a, b) a
= PLens (Pure . fst) first
plensFst'
plensList' :: PLens (Free []) [a] a
= PLens lift map plensList'
We can use these as before:
> plensGet id exampleList :: Free [] [[(Int, Char)]]
Pure [[(1,'a'),(2,'b')],[(3,'c'),(4,'d')]]
> plensGet plensList' exampleList
Free [Pure [(1,'a'),(2,'b')],Pure [(3,'c'),(4,'d')]]
> plensGet (plensList' . plensList') exampleList
Free [Free [Pure (1,'a'),Pure (2,'b')],Free [Pure (3,'c'),Pure (4,'d')]]
> plensGet (plensFst' . plensList' . plensList') exampleList
Free [Free [Pure 1,Pure 2],Free [Pure 3,Pure 4]]
Note that the structure of the original list is still visible, as is the focus of the lens. (If we had chosen [] for f instead of Free [], the original list of lists would have been flattened.) Of course we can still modify the list, too:
> plensModify (plensFst' . plensList' . plensList') (+1) exampleList
2,'a'),(3,'b')],[(4,'c'),(5,'d')]] [[(
Comparison to Traversal
An alternative representation of a lens is the so-called van Laarhoven lens, made popular by the lens package:
type LaarLens a b = forall f. Functor f => (b -> f b) -> (a -> f a)
(this is the representation Simon Peyton-Jones mentions in his talk).
Lens
and LaarLens
are isomorphic: we can translate from Lens
to
LaarLens
and back. This isomorphism is a neat result, and not at all obvious.
If you haven’t seen it before, you should do the proof. It is illuminating.
A Traversal
is like a van Laarhoven lens, but using Applicative
instead of
Functor
:
type Traversal a b = forall f. Applicative f => (b -> f b) -> (a -> f a)
Traversals have a similar purpose to pointwise lenses. In particular, we can define
tget :: Traversal a b -> a -> [b]
= getConst . t (Const . (:[]))
tget t
tmodify :: Traversal a b -> (b -> b) -> (a -> a)
= runIdentity . t (Identity . f) tmodify t f
Note that the types of tget
and tmodify
are similar to types of the getter
and modifier of a pointwise lens, and we can use them in a similar fashion:
travFst :: LaarLens (a, b) a
= (, b) <$> f a
travFst f (a, b)
travList :: Traversal [a] a
= traverse
travList
exampleTrav :: Traversal [[(Int, Char)]] Int
= travList . travList . travFst exampleTrav
As before, we can use this traversal to modify a list of list of pairs:
> tmodify exampleTrav (+1) exampleList
2,'a'),(3,'b')],[(4,'c'),(5,'d')]] [[(
However, Traversals and pointwise lenses are not the same thing. It is tempting to compare the f parameter of the pointwise lens to the universally quantified f in the type of the Traversal, but they don’t play the same role at all. With pointwise lenses it is possible to define a lens from a list of list of pairs to a list of list of ints, as we saw; similarly, it would be possible to define a lens from a tree of pairs to a tree of ints, etc. However, the getter from a traversal only ever returns a single, flat, list:
> tget exampleTrav exampleList
1,2,3,4] [
Note that we have lost the structure of the original list. This behaviour is
inherent in how Traversals work: every element of the structure is wrapped in a
Const
constructor and are then combined in the Applicative
instance for
Const
.
On the other hand, the Traversal
type is much more general than a pointwise
lens. For instance, we can easily define
mapM :: Applicative m => (a -> m a) -> [a] -> m [a]
mapM = travList
and it is not hard to see that we will never be able to define mapM
using a
pointwise lens. Traversals and pointwise lenses are thus incomparable: neither
is more general than the other.
In a sense the generality of the Traversal
type is somewhat accidental,
however: it’s purpose is similar to a pointwise lens, but it’s type also allows
to introduce effectful modifiers. For pointwise lenses (or “normal” lenses)
this ability is entirely orthogonal, as we shall see in the next section.
(PS: Yes, traverse
, travList
and mapM
are all just synonyms, with
specialized types. This is typical of using the lens
package: it defines 14
synonyms for id
alone! What you take away from that is up to you :)
Generalizing further
So far we have only considered pure getters and modifiers; what about effectful ones? For instance, we might want to define lenses into a database, so that our getter and modifier live in the IO monad.
If you look at the actual definition of a lens in fclabels
you will see that
it generalises Lens
to use arrows:
data GLens cat a b = GLens {
glensGet :: cat a b
glensModify :: cat (cat b b, a) a
, }
(Actually, the type is slightly more general still, and allows for polymorphic
lenses. Polymorphism is orthogonal to what we are discussing here and we will
ignore it for the sake of simplicity.) GLens
too forms a category, provided
that cat
satisfies ArrowApply
:
instance ArrowApply cat => Category (GLens cat) where
id = GLens id app
GLens g m) . (GLens g' m') = GLens (g . g') (uncurry (curry m' . curry m))
(
const :: Arrow arr => c -> arr b c
const a = arr (\_ -> a)
curry :: Arrow cat => cat (a, b) c -> (a -> cat b c)
curry m i = m . (const i &&& id)
uncurry :: ArrowApply cat => (a -> cat b c) -> cat (a, b) c
uncurry a = app . arr (first a)
The ArrowApply
constraint effectively means we have only two choices: we can
instantiate cat
with ->
, to get back to Lens
, or we can instantiate it
with Kleisli m
, for some monad m, to get “monadic” functions; i.e. the
getter would have type (isomorphic to) a -> m b
and the modifier would have
type (isomorphic to) (b -> m b) -> (a -> m a)
.
Can we make a similar generalization to pointwise lenses? Defining the datatype is easy:
data GPLens cat f a b = GPLens {
gplensGet :: cat a (f b)
gplensModify :: cat (cat b b, a) a
, }
The question is if we can still define composition.
Interlude: Working with ArrowApply
I personally find working with arrows horribly confusing. However, if we are
working with ArrowApply
arrows then we are effectively working with a monad,
or so Control.Arrow tells us. It doesn’t however quite tell
us how. I find it very convenient to define the following two auxiliary
functions:
toMonad :: ArrowApply arr => arr a b -> (a -> ArrowMonad arr b)
= ArrowMonad $ app . (const (f, a))
toMonad f a
toArrow :: ArrowApply arr => (a -> ArrowMonad arr b) -> arr a b
= app . arr (\a -> (unArrowMonad (act a), ()))
toArrow act where
ArrowMonad a) = a unArrowMonad (
Now I can translate from an arrow to a monadic function and back, and I just write monadic code. Right, now we can continue :)
Category instance for GPLens
Since the type of the modifier has not changed at all from GLens
we can
concentrate on the getters. For the identity we need an arrow of type cat a (f a)
, but this is simply arr return
, so that is easy.
Composition is trickier. For the getter we have two getters of type cat a (f b)
and cat b (f c)
, and we need a getter of type cat a (f c)
. As before,
it looks like we need some kind of monadic (Kleisli) composition, but now in an
arbitrary category cat. If you’re like me at this stage you will search
Hoogle for
ArrowApply cat, Monad f) => cat a (f b) -> cat b (f c) -> cat a (f c) (
… and find nothing. So you try Hayoo and again, find nothing. Fine, we’ll have to try it ourselves. Let’s concentrate on the monadic case:
compM :: (Monad m, Monad f)
=> (a -> m (f b)) -> (b -> m (f c)) -> a -> m (f c)
= do fb <- f a
compM f g a _
so far as good; fb
has type f b
. But now what? We can fmap g
over fb
to
get something of type f (m (f c))
, but that’s no use; we want that m
on the
outside. In general we cannot commute monads like this, but if you are a (very)
seasoned Haskell programmer you will realize that if f
happens to be a
traversable functor then we can flip f
and m
around to get something of
type m (f (f c))
. In fact, instead of fmap
and then commute we can use
mapM
from Data.Traversable
to do both in one go:
compM :: (Monad m, Monad f, Traversable f)
=> (a -> m (f b)) -> (b -> m (f c)) -> a -> m (f c)
= do fb <- f a
compM f g a <- Traversable.mapM g fb
ffc _
Now we’re almost there: ffc
has type f (f c)
, we need somthing of type f c
; since f
is a monad, we can just use join
:
compM :: (Monad m, Monad f, Traversable f)
=> (a -> m (f b)) -> (b -> m (f c)) -> a -> m (f c)
= do fb <- f a
compM f g a <- Traversable.mapM g fb
ffc return (join ffc)
We can use the two auxiliary functions from the previous section to define Kleisli composition on arrows:
compA :: (ArrowApply cat, Monad f, Traversable f)
=> cat a (f b) -> cat b (f c) -> cat a (f c)
= toArrow (compM (toMonad f) (toMonad g)) compA f g
And now we can define our category instance:
instance (ArrowApply cat, Monad f, Traversable f)
=> Category (GPLens cat f) where
id = GPLens (arr return) app
GPLens g m . GPLens g' m' = GPLens (g' `compA` g)
uncurry (curry m' . curry m)) (
Note that the Traversable
constraint comes up now because we need to commute
the “effects” of two monads: the monad f from the structure that we are
returning (be it a list or a tree or..) and the monad m implicit in the
arrow. In a Traversal these two are somehow more closely coupled. In
particular, if we lift a (pure) pointwise lens PLens
to the more general
GPLens
, by picking Identity
for f, the Traversable
constraint is
trivially satisfied.