Haskell/Lens
本章中我们将讨论函数式引用. "引用"指的是能够对值的一部分进行访问和修改的能力; "函数式"指我们不会因此失去 Haskell 中函数所具有的灵活性和可复合性. 我们将讨论强大的 lens
库所实现的函数式引用. lens
库的名字来源于 lenses(透镜), 我们将会介绍的一种臭名昭著的函数式引用. 除了作为一些非常有趣的概念外, lens 和其它函数式引用为我们带来了一些方便而且越来越普遍的语言用法, 而且被许多实用的库所采用.
初尝 lens
[编辑]作为热身, 我们将演示 lens 最简单的使用案例: 替代传统的 Haskell 的具有命名的数据类型 (record syntax). 我们先不给出详细的解释; 随着本章的进展, 我们会逐渐覆盖所需的知识的.
我们来看看下面两个数据类型, 或许我们会在一些2D绘图库中看见它们:
-- 平面上一点.
data Point = Point
{ positionX :: Double
, positionY :: Double
} deriving (Show)
-- 两点间的一条线段.
data Segment = Segment
{ segmentStart :: Point
, segmentEnd :: Point
} deriving (Show)
-- 构造线和点的函数.
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 自动为我们定义了访问这两个数据类型中的域的函数. 有了这些函数, 从一条线段中读取它的两个端点并不困难:
GHCi> let testSeg = makeSegment (0, 1) (2, 4)
GHCi> positionY . segmentEnd $ testSeg
GHCi> 4.0
但修改就略嫌麻烦了...
GHCi> testSeg { segmentEnd = makePoint (2, 3) }
Segment {segmentStart = Point {positionX = 0.0, positionY = 1.0}
, segmentEnd = Point {positionX = 2.0, positionY = 3.0}}
...而当我们需要修改嵌套在深处的域时, 代码变得非常丑陋. 例如, 修改线段终点的 y 轴坐标:
GHCi> :set +m -- 开启 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}}
lens 允许我们绕开这些讨厌的嵌套, 观察下面的代码:
-- 本章中的一些例子需要开启一些 GHC 扩展:
-- makeLenses 需要 TemplateHaskell 扩展;
-- 之后的一些类型声明需要 RankNTypes 扩展.
{-# 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)
这里唯一的改变就是 makeLenses
, 其自动生成了 Point
和 Segment
的 lens (域名前的下划线是 makeLenses
的特殊要求). 我们将会看到, 手写 lens 定义并不复杂; 然而, 如果有许多域都需要使用 lense, 这个过程就会变得很枯燥, 因此我们使用方便的自动生成.
使用了 makeLenses
后, 每一个域都有各自的 lens 了. 这些 lens 的名字和域名一一对应, 区别之处在于头部的下划线被删除了:
GHCi> :info positionY
positionY :: Lens' Point Double
-- 定义于 WikibookLenses.hs:9:1
GHCi> :info segmentEnd
segmentEnd :: Lens' Segment Point
-- 定义于 WikibookLenses.hs:15:1
类型签名 positionY :: Lens' Point Double
告诉我们, positionY
是一个 Point
中 Double
的引用. 我们使用 lens
库提供的组合函数来操作这些引用. 其中一个函数是 view
, 其返回一个 lens 所指向的值, 如同 record 所自动生成的那些访问函数一样:
GHCi> let testSeg = makeSegment (0, 1) (2, 4)
GHCi> view segmentEnd testSeg
Point {_positionX = 2.0, _positionY = 4.0}
另一个是 set
, 它能够修改其指向的值:
GHCi> set segmentEnd (makePoint (2, 3)) testSeg
Segment {_segmentStart = Point {_positionX = 0.0, _positionY = 1.0}
, _segmentEnd = Point {_positionX = 2.0, _positionY = 3.0}}
lens 的一大优点是它们能够互相组合:
GHCi> view (segmentEnd . positionY) testSeg
4.0
注意到, 在组合 lens, 例如 segmentEnd . positionY
时, 顺序是由总到分. 本例中, 指向线段的终点的 lens 写在指向点的坐标的 lens 前面. 或许这和 record 所提供的函数的工作方式不尽相同 (和本节开头不使用 lens 的等价写法比较), 但这里的 (.)
确实是我们所熟悉的函数组合.
lens 的组合为修改嵌套 record 内部的值提供了一个解决方案. 我们将之前给出的将坐标翻倍的例子改写成使用 lens 和 over
函数的写法, 后者将一个函数应用到被 lens 指向的值上 (并返回整个 record 修改后的值):
GHCi> over (segmentEnd . positionY) (2 *) testSeg
Segment {_segmentStart = Point {_positionX = 0.0, _positionY = 1.0}
, _segmentEnd = Point {_positionX = 2.0, _positionY = 8.0}}
这些例子或许看起来有些不可思议. 为什么用同一个 lens 我们不仅能访问, 还能够修改一个值呢? 为什么 lens 能够用 (.)
组合呢? 不使用 makeLenses
而是改为手写 lens 真的并不困难吗? 为了回答这些问题, 我们将介绍 lens 的工作原理.
lens 前方800m
[编辑]我们能从许多角度解读 lens. 我们将遵循一条蜿蜒曲折而平缓的道路, 避免跳跃过大. 一路上, 我们将介绍好几个种类的函数式引用. 我们将使用 lens 的命名趣味, 使用"光学元件(optic)"[1]来统称函数式引用. 正如我们将看到的, lens
中的 optic 互相关联, 形成了有序的上下关系. 我们即将介绍这种关系.
traversal
[编辑]我们选择不从 lens, 而是从一个紧密相关的 optic -- traversal
-- 入手. 我们知道, traverse
能够遍历一个结构并产生一个最终结果.
traverse
:: (Applicative f, Traversable t) => (a -> f b) -> t a -> f (t b)
有了 traverse
, 你能够使用任何你想要的 Applicative
来产生这个最终结果. 特别的, 我们知道 fmap
能够用 traverse
定义: 只要选择 Identity
作为其中的 Applicative
就好了. foldMap
和 Const m
也存在类似的关系:
fmap f = runIdentity . traverse (Identity . f)
foldMap f = getConst . traverse (Const . f)
lens
是在这个基础上一次漂亮的延伸.
操作 Traversable
结构内部的数据, 也就是 traverse
的功能, 恰恰就是一个操作整体数据内部特定部分的例子. 然而 traverse
的灵活性仅仅允许我们处理有限范围内的类型. 例如, 我们或许会想要操作非 Traversable
的值. 比如说, 我们或许会想要这样一个处理 Point
值的函数:
pointCoordinates
:: Applicative f => (Double -> f Double) -> Point -> f Point
pointCoordinates g (Point x y) = Point <$> g x <*> g y
pointCoordinates
是对 Point
类型值的一种 traversal (遍历). 它和 traverse
具有相似的实现和使用方法. 这是来自之前章节[2]的 rejectWithNegatives
的使用样例:
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
这种 pointCoordinates
的例子中出现的一般意义上的遍历被 lens
库的核心类型之一 -- Traversal
所表示:
type Traversal s t a b =
forall f. Applicative f => (a -> f b) -> s -> f t
注解
|
有了 Traversal
类型别名的定义, pointCoordinates
的类型能够被表示为:
Traversal Point Point Double Double
让我们看看 Traversal s t a b
中每个类型变量的值:
s
=Point
:pointCoordinates
是一个Point
上的遍历.t
=Point
:pointCoordinates
将产生一个Point
(某种Applicative
的意义上).a
=Double
:pointCoordinates
指向一个Point
内的Double
值 (点的 X 和 Y 坐标).b
=Double
: 指向的Double
将被修改为一个Double
(有时不一定相同).
在 pointCoordinates
的例子中, s
和 t
相同, a
也和 b 相同. pointCoordinates
并不改变被遍历结构和它的"内部目标"的类型, 但这并不对所有 lens 成立. 例如我们熟悉的 traverse
, 其类型可以被表示为:
Traversable t => Traversal (t a) (t b) a b
traverse
能够改变 Traversable
结构内部值的类型, 因此也能够改变整个结构的类型.
Control.Lens.Traversal 模块中包含了 Data.Traversable 模块中函数的推广, 以及一些额外的操作 traversal 的函数.
练习 |
---|
|
设置器
[编辑]接下来我们的程序中将推广 Traversable
, Functor
和 Foldable
之间的联系. 我们将从 Functor
开始.
为了从 traverse
中恢复 fmap
, 我们选择 Identity
作为相应的应用函子. 这使得我们能够修改目标值而不产生别的影响. 我们可以通过选择一个 Traversal
的定义实现相似的功能...
forall f. Applicative f => (a -> f b) -> s -> f t
... 并设定 f
为 Identity
:
(a -> Identity b) -> s -> Identity t
用 lens
相关的说法, 这样做使你得到了一个 Setter
. 由于一些专门的原因, 在 Template:Haskell lib 中 Setter
的定义有点不同...
type Setter s t a b =
forall f. Settable f => (a -> f b) -> s -> f t
...但如果你从文档中深入发掘你会发现一个 Settable
函子不过就是一个 Identity
或者差不多的东西, 因此不必在意这里面的差异.
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}
练习 |
---|
|
Folds
[编辑]Having 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
, Template:Haskell lib 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
注解
contramap :: Contravariant f => (a -> b) -> f b -> f a
... which looks a lot like newtype Predicate a = Predicate { getPredicate :: a -> Bool }
GHCi> :m +Data.Functor.Contravariant
GHCi> let largerThanFour = Predicate (> 4)
GHCi> getPredicate largerThanFour 6
True
GHCi> getPredicate (contramap length largerThanFour) "orange"
True
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 Template:Haskell lib. 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 Template:Haskell lib.
GHCi> preview traverse [1..10]
Just 1
Getters
[编辑]So 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 Template:Haskell lib 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
注解
Given what we have just said about 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 type Getting r s a = (a -> Const r a) -> s -> Const r s
view :: MonadReader s m => Getting a s a -> m a
Many combinators in both 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
|
Lenses at last
[编辑]If 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.
注解
On close reading, our claim that every 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 |
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
练习 |
---|
|
Composition
[编辑]The 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
|
注解
The type Lens' s a = Lens s s a a
There are analogous |
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
[编辑]Several 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
[编辑]Thus 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
[编辑]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)
).- Template:Haskell lib 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
[编辑]In 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 Template:Haskell lib.
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. Template:Haskell lib 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
[编辑]With 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
Traversable
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 Template:Haskell lib. 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, Template:Haskell lib 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 Template:Haskell lib module.
练习 |
---|
|
Laws
[编辑]There 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) = 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
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
[编辑]When 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 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
[编辑]As 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
and 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 make it possible to have multiple optic frameworks (i.e. lens
and similar libraries) that can be used interchangeably.
Further reading
[编辑]- 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 inlens
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 courselens
' 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 minimalisticlens
-compatible libraries such asmicrolens
andlens-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 useslens
extensively to deal with properties of graphic elements.wreq
, a web client library with alens
-based interface.xml-lens
, which provides optics for manipulating XML.formattable
, a library for date, time and number formattting. Template:Haskell lib is an example of a module that provideslens
-compatible lenses without depending on thelens
package.
Lens |
习题解答 |
Advanced Haskell |
Haskell |
Haskell基础
>> 初级Haskell
>> Haskell进阶
>> Monads
|