Haskell sessions

Lenses 1

We'll need the RankNTypes extension to enable explicit forall syntax (to write the Lens and Traversal types).

We'll need TemplateHaskell to use library-provided generation of lenses for our datatypes (Template Haskell is required because this process requires reflecting on the data type definition.)


{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
module Lib where
import Data.Functor.Identity
import Data.Functor
import Control.Lens.TH
0.5s
Haskell

Mutation in Haskell

Let's define some nested datatypes. We are prefixing the field names with underscores, leaving the plain names available for the corresponding auto-generated lenses.


data OperatingSystem = OS {
    _distribution :: String,
    _version :: String
  } deriving Show
data Computer = Computer {
    _brand :: String,
    _os :: OperatingSystem
  } deriving Show
data Person = Person {
    _name :: String,
    _age :: Integer,
    _computer :: Computer
  } deriving Show
0.4s
Haskell

Here's some base value. In pure languages, we simulate mutation by creating an updated copy of the value, modifying only the fields we need.

We can either use record syntax, or use the plain constructors.

max' = Person "Max" 37 (Computer "thinkpad" (OS "qubes" "4.0"))
0.3s
Haskell

The language-generated accessors compose well:


maxOsVersion = (_version . _os . _computer) max'
0.4s
Haskell

However, updates are more challenging. One way to implement updates is with pattern matching. For instance:

max'' = let Person name  age    computer = max'
        in  Person name (age+1) computer
0.3s
Haskell

This becomes awkward when updating deeply nested fields:

max''' = let Person name age (Computer brand (OS distro _version)) = max''
          in Person name age (Computer brand (OS distro "5.0"   ))
0.4s
Haskell

Thankfully, Haskell provides a convenient syntax for updating records. However, it doesn't scale incredibly well when deeply nesting, as it doesn't compose at all.

max2'' = max' { _age = 38 }
max2''' = max' { _computer = (_computer max') { _os = (_os (_computer max')) { _version = "5.0" } } }
0.5s
Haskell

Composing accessors

In imperative language tradition, we can abstract away a structure field by wrapping it in two methods, a getter and a setter.

For a structure of type s containing some field a, we have:

data Field s a = Field {
    getter :: s -> a,
    setter :: a -> (s -> s)
    }
0.3s
Haskell

We can then wrap the native fields of our data structures:

versionF :: Field OperatingSystem String
versionF = Field {
    getter = _version,
    setter = \a s -> s { _version = a }
 }
osF :: Field Computer OperatingSystem
osF = Field {
    getter = _os, 
    setter = \a s -> s { _os = a }
 }
computerF :: Field Person Computer 
computerF = Field {
    getter = _computer, 
    setter = \a s -> s { _computer = a }
 }
0.3s
Haskell

We can then define a composition operator, to provide access to a deeply nested field.


(./) :: Field a b -> Field b c -> Field a c
ab ./ bc = let Field getBfromA setBinA = ab
               Field getCfromB setCinB = bc
               getCfromA = getCfromB . getBfromA    
               setCinA c a = setBinA (setCinB c (getBfromA a)) a
           in Field getCfromA setCinA
osVersionF = computerF ./ osF ./ versionF
max3''' = setter osVersionF "5.0" max'
0.3s
Haskell

Comonadic Accessors

We can reorder the arguments of the setter, then factor out the s -> to turn a field definition into a single function:

-- data Field s a = Field {
--   getter :: s -> a
--   setter :: s -> (a -> s)
-- }
type Field2 s a = s -> (a, a -> s)
0.3s
Haskell

Peek hard enough at the type (a, a -> s) and you might recognize the Store comonad, the dual of the State monad (but with the type arguments flipped:)

type State s a = (s -> (a, s))
type Store s a = (s, s -> a)
type Field3 s a = s -> Store a s 
0.3s
Haskell

Something something coalgebra something.

Semantic Editor Combinators

Composition, as defined in our Field, is not very elegant; in particular, the composed setter depends on one of the getters.

We can eliminate the problem by changing the API of setters; instead of taking a new value for the field, they take a modification function, and lift it into a function that operates on the entire structure. It is trivial to recover the old behaviour with const. Conveniently, they can compose with the standard function composition operator.

These setters are also called semantic editor combinators

type SEC s a = (a -> a) -> (s -> s)
versionS :: SEC OperatingSystem String
versionS f s = s { _version = f (_version s) }
osS :: SEC Computer OperatingSystem
osS f s = s { _os = f (_os s)}
computerS :: SEC Person Computer
computerS f s = s { _computer = f (_computer s)}
osVersionS :: SEC Person String
osVersionS = computerS . osS . versionS
0.7s
Haskell

Traversals

The type of SECs is disturbingly similar to the one of traversals. We can recover a SEC from a traversal by choosing the Identity functor for the traversal.

We can rewrite our SECs as traversals. In a SEC, we extract the value of a field, apply the provided function to that field, and reassemble the structure around the updated field. With a traversal, the provided functions hands us back a functorial value, and we have to use fmap to lift the reassembly into the functor.

type Traversal' s a = forall f. Applicative f => (a -> f a) -> (s -> f s)
versionL :: Traversal' OperatingSystem String
versionL f s = fmap (\a -> s { _version = a }) (f (_version s))
osL :: Traversal' Computer OperatingSystem
osL f s = fmap (\a -> s { _os = a }) (f (_os s))
computerL :: Traversal' Person Computer
computerL f s = fmap (\a -> s { _computer = a }) (f (_computer s))
0.4s
Haskell

Changing The Types

If the structure type is parameterized by the field type, it becomes possible to map and change this type. For instance, consider the type of traverse for lists (from the Traversable class):

--traverse :: forall f. Applicative f => (a -> f b) -> ([a] -> f [b])
0.3s
Haskell

A more generic type for traversals is thus:

type Traversal s t a b = forall f. Applicative f => (a -> f b) -> (s -> f t)
0.3s
Haskell

Where the types s and t represent the type of the entire structure, before and after applying the lens, and a and b the type of the field.

Let's define an operator for recovering the setter of a traversal:

import Data.Functor.Identity
infixr 8 %~ 
(%~) :: Traversal s t a b -> (a -> b) -> (s -> t)
l %~ f = runIdentity . l (Identity . f)
0.2s
Haskell

Lenses

Observe that, in our definitions, we didn't use the Applicative methods, we only use fmap. The Applicative constraint is too strong; a Functor constraint would have sufficed.

This works because we call the function (a -> f b) exactly once, then use fmap to transform the f b into an f t. If we called this function 0 times, the only way to produce a f t for an arbitrary functor f is to use pure. If we called it several times, we need <*> to combine the results.

We can thus view lenses are a special case of traversals that always visit exactly one element, by relaxing the constraint:

type Lens s t a b = forall f. Functor f => (a -> f b) -> (s -> f t)
0.3s
Haskell

As Applicative requires Functor, all lenses are valid traversals. They can still be combined with the (.) operator, and Haskell's treatment of constraints gives us a kind of emulated subtyping: composing two lenses give a lens, composing a lens with a traversal gives a traversal.

Getters

It turns out that we can not only recover a setter from a lens, but a getter as well, by choosing this time the constant functor.

Intuitively, this works because of the way lenses operate: by first extracting the value from the structure field, then allowing the user to lift this value into a functor, and perform structure reassembly inside the functor, by using fmap to lift the reassembly inside the functor. Using the constant functor signals that we are not interested in the reassembly (fmap for Const just discards its argument), and we want instead to keep the constant value we introduced when the field was processed.

We can also define a convenience operator to recover the getter of a lens.

newtype Const c a = Const { runConst :: c }
instance Functor (Const c) where
    fmap _ (Const c) = Const c
(^.) :: s -> Lens s t a b -> a
s ^. l = runConst (l Const s)
-- max'^.computerL.osL.versionL == "4.0"
0.3s
Haskell

TH-Generated Lenses

For simple structures (product types), lenses are automatically derivable. This requires reflecting on the datatype and introducing new names into the namespace, so it requires Template Haskell:

makeLenses ''OperatingSystem
makeLenses ''Computer
makeLenses ''Person
0.5s
Haskell

For every field name starting with an underscore, we now have a corresponding lens (without underscore).

Folds

It is not possible to write an Applicative instance for the type Const c. This is because the implementation of pure would require us to provide a value of type c when we have none available.

However, if we add a constraint (Monoid c) =>, we can write the instance, using mempty to provide the default value in pure, and <> to write ap in a way that respects the Applicative laws.

instance (Monoid c) => Applicative (Const c) where
    pure a = Const mempty
    Const c1 <*> Const c2 = Const (c1 <> c2) 
0.3s
Haskell

This way, traversals naturally decay to folds, if we use them as getters to some kind of monoid. For instance, we can use this convenience operator to recover a list of all values traversed:

(^..) :: Traversal' s a -> s -> [a]
t ^.. s = runConst (t (Const . (:[])) s)
0.3s
Haskell
Runtimes (1)