Usually explanation of val Laarhoven lens is started from lens. But for me such
construction feels completely artificial. Nothing motivates writing function
with such weird type. Why would anyone wants to write functions with weird type
signature? How could anyone come up with such idea? Traversable is much
better starting point. It's part of base and it's likely that reader is
familiar with this type class and appreciates its usefulness.
So here is pared down definition of Traversable type class. It contains only
traverse since we won't need any other methods:
class Foldable t => Traversable t where
traverse :: forall f. Applicative f => (a -> f b) -> t a -> f (t b)Its meaning is simple: visit every occurrence of a in value of type t a,
replace it with result of function parameter while collecting effects f. Here
are few instances:
instance Traversable [] where
traverse _ [] = pure []
traverse f (x:xs) = (:) <$> f x <*> traverse f xs
instance Traversable (Either a) where
traverse _ (Left a) = pure (Left a)
traverse f (Right b) = Right <$> f b
instance Traversable ((,) a) where
traverse f (a,b) = (,) a <$> f bDoes traverse have any interesting properties? It does. It composes using
ordinary function composition and allows to traverse nested data types:
>>> :t traverse . traverse
:: (Applicative f, Traversable t1, Traversable t2) =>
(a -> f b) -> t1 (t2 a) -> f (t1 (t2 b))
>>> (traverse . traverse) print [Left "ABC", Right 1, Right 12, Left "X"]
1
12
[Left "ABC",Right (),Right (),Left "X"]That's very nice property. Could we generalize it for types that couldn't be
instance of Traversable: bytestrings, unboxed/storable vectors, etc. What if
we want to traverse Left instead of Right as Traversable requires. As
example let look at following data type:
data Foo = Foo Int Int
deriving ShowWe want to write traversal that visits each field. First we need to figure out
its type, and to do that we need to look at the type of traversable :: ∀ f. Applicative f => (a → f b) → (t a → f (t b)) again. a is type of element
we visit, and b is type being produced. Both have to be Int in our case.
t a is type being traversed, t b is result of traversal. Again both are Foo
traverseFoo :: Applicative f => (Int -> f Int) -> Foo -> f Foo
traverseFoo f (Foo n k) = Foo <$> f n <*> f kWriting traversals for both constructors of Either is similarly simple:
_Left :: Applicative f => (a -> f b) -> Either a c -> f (Either b c)
_Left f (Left a) = Left <$> f a
_Left _ (Right b) = pure $ Right b
_Right :: Applicative f => (b -> f c) -> Either a b -> f (Either a c)
_Right = traverseThose signatures are rather cumbersome. They could be replaced by type synonyms
that are familiar to all users of lens:
type Traversal s t a b = forall f. Applicative f => (a -> f b) -> (s -> f t)
type Traversal' s a = Traversal s s a a
traverseFoo :: Traversal' Foo Int
_Left :: Traversal (Either a c) (Either b c) a b
_Right :: Traversal (Either a b) (Either a c) b cTraversals give us free choice of applicative functor f. Are there any
particularly useful choices aside of IO that was used in example? One is
Identity which allows to simply apply function to each traversed element:
over
:: ((a -> Identity b) -> (s -> Identity b))
-> (a -> b)
-> (s -> b)
over = coerceWhen it's written like that function seems to be almost trivial. Yet it works:
>>> over (traverse . _Left . traverseFoo) (+100) [Right "a", Left (Foo 1 20) ]
[Right "a",Left (Foo 101 120)Lens arise naturally once we consider fields that occur exactly once. Tuples are examples of such type and traversals for them are below:
_1 :: Traversal (a,b) (c,b) a c
_1 f (a,b) = (\c -> (c,b)) <$> f a
_2 :: Traversal (a,b) (a,c) b c
_2 f (a,b) = (\c -> (a,c)) <$> f bThis definitions don't Applicative we only use fmap! So we could rewrite
type signatures as:
_1 :: Functor f => (a -> f c) -> ((a,b) -> f (c,b))
_2 :: Functor f => (b -> f c) -> ((a,b) -> f (a,c))To find operations that are specific to lenses but not traversals we need to
find interesting choices of f that aren't applicatives. One such choice is
Const.
view :: ((a -> Const a b) -> (s -> Const a t)) -> s -> a
view l s = getConst $ l Const sYes. It's getter
>>> view (_1 . _2) ((1,2),3)
2Setter however could be defined both for lens and traversals. One need to have exactly one value to be able get it. Setting all values to given values is however well defined for case when we have 0-1-many values.
set
:: ((a -> Identity b) -> (s -> Identity t))
-> b
-> (s -> t)
set l x = over l (const x)