status
failed

Overloading record fields with lens

After seeing this comment on reddit asking if lens solves the “overloading issue” with Haskell’s record systems, I thought I’d write up what I found here. By the way, The answer is yes, it can solve the problem with makeFields. The code for this blog post is available as a github gist.

Often, when making lenses I’ll use makeLenses. This is one of the simplest Template Haskell lens functions, and tries to make a named lens for each field in your record. If you try to avoid the clashing field names by doing something like this:

data Foo = Foo { _oneFoo :: Double, _twoFoo :: Double }
data Bar = Bar { _oneBar :: Double, _twoBar :: Double }

makeLenses ''Foo
makeLenses ''Bar

… you’ll end up with many different (and long) names for everything. That’s not nice.

Instead you can use makeFields. This will give you a typeclass for each field called (for example) HasOne.

If we’d used makeFields in our example above, both Foo and Bar would be instances of HasOne, we could refer to the fields using the name one, and everything would be just rosy. A more complete example is below. I’ve used 2D and 3D vectors (Vec2 and Vec3) to demonstrate how we can create lenses named x, y, and z super-simply just using makeFields.

{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}

module Fields where

import Control.Lens
import Control.Lens.TH

data Vec2 = Vec2
  { _vec2X :: Double
  , _vec2Y :: Double
  } deriving (Eq, Read, Show)

data Vec3 = Vec3
  { _vec3X :: Double
  , _vec3Y :: Double
  , _vec3Z :: Double
  } deriving (Eq, Read, Show)

makeFields ''Vec2
makeFields ''Vec3
-- each _vecNC field can now be referred to as 'x', 'y', or 'z'

-- results in: Vec2 2 2
example1 = over x (+1) $ Vec2 1 2
-- results in: Vec3 1 2 300
example2 = over z (*100) $ Vec3 1 2 3

Here, makeFields uses some default rules to strip away the underscore and record type name to transform our field names (_vec3X, vec2X) into the lens name (x). These rules can be customised by using makeFieldsWith.

We can use ghci to examine the created typeclasses (using :t HasX at the GHCI prompt):

class HasX c_a24V e_a24W | c_a24V -> e_a24W where
  x :: Functor f => (e0 -> f e0) -> c0 -> f c0
        -- Defined at Fields.hs:21:1
instance HasX Vec2 Double -- Defined at Fields.hs:21:1
instance HasX Vec3 Double -- Defined at Fields.hs:22:1

Aside from the strange type variable names, this is fairly simple: the HasX class has a single value, x, which is the Lens into our record. The type parameters to HasX are the record type, then the field type. That means we can write a normal Vec2 like this.

v :: (v ~ Vec2, HasX v Double) => v
v = Vec2 10 10

Note that the type could be written simply as v :: Vec21. Our more complicated type signature is just intended to illustrate how the type parameters get ‘filled in’. The tilde (~) in a type signature denotes equality.

A more useful example, in which we want to write a function that zeroes out the x component of any vector, is below:

-- | Take any type of vector with an x component and zero it
zeroX :: HasX t Double => t -> t
zeroX = x .~ 0

-- We get a Vec2 0 10
zeroed2 :: Vec2
zeroed2 = zeroX $ Vec2 100 10

We can also make 2- and 3- tuples instances of HasX and HasY like this:

instance HasX (Double, a) Double where
  x = _1

instance HasY (a, Double) Double where
  y = _2

instance HasX (Double, a, b) Double where
  x = _1

instance HasY (a, Double, b) Double where
  y = _2

instance HasZ (a, b, Double) Double where
  z = _3

The Control.Lens.TH module is full of useful functions like makeFields, so I definitely recommend reading through the documentation to see if there’s anything useful to you in there.


  1. This isn’t strictly true, because we’re also asserting that Vec2 must be an instance of HasX v Double. If we removed the makeFields call, this line would complain that there was no instance, whereas if we’d written the type simply as v :: Vec2, it would compile.↩︎