Case study: migrating from lens to optics

Posted on 2020-01-25 by Oleg Grenrus lens, optics

As you are reading this post, you probably know that there is

  • the lens library by Edward Kmett et al. which is de facto optics library for Haskell. It's famous also for its type errors.
  • the optics library by Adam Gundry, Andres Löh, Andrzej Rybczak and myself uses different representation for optics (note: slanted optics is a concept, monospace optics is a library name). I recommend reading through the introduction in the official documentation, especially Comparison with lens section

Some time ago I commented on Reddit, that there are no real experience reports about migrating "real world Haskell codebases" from lens to optics. So I decided to do an experiment. The repository is a public Futurice Haskell code monorepository, which I worked on during my time at the Futurice. The whole codebase is a bit over 70000 lines in 800 files.

One disclaimer is that I do this for fun and out of curiosity, in other words Futurice didn't ask me to do this (fun is subjective). Another disclaimer is that my experiences shouldn't not be extrapolated into how easy or hard this kind of migration is, only that it's possible. I'm way too familiar with the codebase under "migration", as well as with lens and optics libraries. On the other hand, it turned relatively easy for me, and I share my experiences, so it would be easier for others.

#Why move from lens to optics

Before discussing how, let me talk a little about why.

There may be different reasons why a team would like to migrate from lens (or no lens at all) to optics

One bad reason is trying to reduce dependency footprint. It won't. Libraries use lens, and that cannot be easily changed. The HMR consists of dozens of small web services, which use

All these libraries depend on lens. But we can use them with optics too, as I'll show later. And even we wouldn't have libraries with lens interface, the lens is there somewhere in codebases of this scale. The HMR build plan consists of over 500 components, from which about 400 are dependencies from Hackage. In fact, from this "industrial" point of view, it would be better if microlens didn't exist. It's just more duplicate code somewhere there. In the dependency closure there are e.g.

microlens-th-0.4.3.2
microlens-mtl-0.2.0.1
microlens-0.4.11.2
lens-4.17.1

There are also multiple implementations of other things, so this problem is not unique to van Laarhoven lens libraries.

My current project has about 450 components in the build plan, so this scale is not unique.

On the other hand, one proper reason to use optics could be better type errors. (I'm too experienced to judge that properly but optics at least tries to produces better errors). Another complelling reason is OverloadedLabels which just work with optics. We'll see example of that. Thanks to Andrzej Rybczak PR, swagger2 package has optics interface via OverloadedLabels (since version 2.5), and it's neat.

#futurice-prelude

HMR has own prelude. The futurice-prelude package is at the bottom of the package graph, in other words everything else there uses the package and imports Futurice.Prelude module. It's a very fat prelude, re-exporting a lot of stuff. It also has a bit of auxiliary modules, which most of the downstream would need.

Having a module imported by everything else is nice, especially as this module currently re-exports the following lens definitions:

import Control.Lens
       (At (..), Getter, Iso, Iso', Ixed (..), Lens, Lens', LensLike,
       LensLike', Prism, Prism', Traversal, Traversal', folded, from, ifoldMap,
       ifolded, ifor, ifor_, isn't, iso, itoList, itraverse, itraverse_, lazy,
       lens, makeLenses, makePrisms, makeWrapped, over, preview, prism, prism',
       strict, view, (%=), (%~), (&), (.~), (<&>), (?=), (?~), (^.), (^..),
       (^?), _1, _2, _3, _Empty, _Just, _Left, _Nothing, _Right)

That's not much, but enough for basic optics usage. We'll change the exports to use optics:

import Data.Function          ((&))
import Data.Functor           ((<&>))
import Optics
       (AffineTraversal, AffineTraversal', At (..), Getter, Iso, Iso',
       Ixed (..), Lens, Lens', Optic, Optic', Prism, Prism', Traversal,
       Traversal', castOptic, coerced, folded, ifoldMap, ifolded, ifor, ifor_,
       isn't, iso, itraverse, itraverse_, lens, lensVL, makeLenses, makePrisms,
       over, preview, prism, prism', re, simple, traversalVL, traverseOf,
       traversed, (%), _1, _2, _3, _Empty, _Just, _Left, _Nothing, _Right)
import Optics.Operators       ((%~), (.~), (?~), (^.), (^..), (^?))
import Optics.State.Operators ((%=), (?=))

and then continue fixing type errors, as usually with refactoring in Haskell.

Careful reader may notice that operators are not exported from the main Optics module. If you don't like them, it's easier to not import them. The & and <&> operators are available directly from modules in base, so we import them from there.

There are few missing or different bits in the optics imports:

  • The from is just re.

  • There are no LensLike; we won't need it. Instead we'll need Optic and Optic', as well as new kind AffineTraversal and AffineTraversal' (I have written about them).

  • There aren't Wrapped type-class in optics. We'll replace it with coerced. coerced is a bit too polymorphic, so we'll need to add type-annotations. This is a small drawback. Or we could use named Isos. It depends.

  • The itoList and lazy and strict are missing, likely they are easy to implement in the futurice-prelude, so the downstream modules won't even notice. itoList is simple application of ifoldr

    itoList :: Optics.FoldableWithIndex i f => f a -> [(i, a)]
    itoList = Optics.ifoldr (\i x xs -> (i,x) : xs) []

    The story about FunctorWithIndex, FoldableWithIndex and TraversableWithIndex is long, but ultimately it would be nice if both optics and lens could use the same type-classes; however it's not that straight forward. So now, lens and optics define their own variants.

  • strict and lazy allow to convert between strict and lazy Texts or ByteStrings. We'll do the simple thing, and make isos using lens type-class. This should be good enough for now. Recall, lens is still around.

    strict :: L.Strict l s => Iso' l s
    strict = iso (L.view L.strict) (L.view L.lazy)
    
    lazy :: L.Strict l s => Iso' s l
    lazy = iso  (L.view L.lazy) (L.view L.strict)

Similarly to lazy and strict there is packed and unpacked, but migrating those is very trivial:

-import Data.Text.Lens              (packed, unpacked)
+import Data.Text.Optics            (packed, unpacked)

Very important is to remember to re-export %, the optics composition operator.

In addition we also export

  • simple and castOptic combinators, we'll need them soon. See optics#286 issue. In optics the identity optic is not id.

  • lensVL and traversalVL which help convert van Laarhoven lenses (from external libraries) to Optics representation.

  • traverseOf: sometimes we use van Laarhoven lenses directly as traversals, that trick doesn't play with optics. For the similar reason we export traversed: traverse is not an Optic.

One thing, which I would liked to be able to do is to re-export lens module qualified, something like:

module Futurice.Prelude (
   ...
   module qualified L
   ) where

It would helped with this migration, but also help to re-export Data.Map and Data.ByteString etc. that would be bery nice for fat preludes.

This is it, about the prelude. Next I'll list various issues I run into when trying to make a single service in HMR to compile. I picked a particular one, which I remember uses lens a lot for business domain stuff.

To conduct this experiment I:

  1. Added optimization: False to cabal.project.local to make compilation faster
  2. cabal build checklist-app:libs
  3. On error ghcid -c 'cabal repl failing-lib', fix errors in that package
  4. go to step 2.

#Individual issues

#Couldn't match type ‘optics-core-0.2:Optics.Internal.Optic.Optic

This is by far the most common type of errors:

Couldn't match type
    ‘optics-core-0.2:Optics.Internal.Optic.Optic
      optics-core-0.2:Optics.Internal.Optic.Types.A_Lens
      optics-core-0.2:Optics.Internal.Optic.TypeLevel.NoIx
      s0
      t0
      a1
      b1’
    with ‘a0 -> b0’
  Expected type: a0 -> b0
    Actual type: Lens s0 t0 a1 b1

The important bit is

Expected type: a0 -> b0
  Actual type: Lens s0 t0 a1 b1

That means that we need to replace dot operator . with the optics composition combinator %. Another variation on the same is

Precedence parsing error
    cannot mix ‘.’ [infixr 9] and%’ [infixl 9] in the same
    infix expression

which happens when you forgot to change few dots.

#swagger2

As already mentioned, swagger2 has optics interface; the needed instances are defined in Data.Swagger.Optics module. I imported it into Orphans module of futurice-prelude, to make the instances available everywhere.

The most changes are then of following flavor:

-   & Swagger.type_ ?~ Swagger.SwaggerObject
-   & Swagger.properties .~ InsOrdHashMap.fromList ...
+   & #type ?~ Swagger.SwaggerObject
+   & #properties .~ InsOrdHashMap.fromList ...

I honestly just used regexps: s/& Swagger./\& #/, and s/type_/type/.

In one place I had to add a type annotation, as the type become ambiguous. This is not necessarily a bad thing.

+  schema :: Swagger.Referenced Swagger.Schema -> Swagger.Schema
   schema s = mempty

That was very straight-forward, as there is optics support in the swagger2 library now. Thanks Andrzej!

#gogol and amazonka and Chart

Unfortunately gogol and amazonka don't have optics support, as far as I know. Both libraries use lens to provide getters and setters to Google Cloud and AWS domain types.

For the code which operates with the libraries directly (which is relatively few modules, API is encapsulated), I import qualified Control.Lens as L and prefix operators with L..

The resulting code is a slight mess, as you could have both ^. from optics, and L.^. from lens. That's not nice even it works.

A solution would be to invest a day and define a bunch of LabelOptic instances for gogol, amazonka and Chart types. One could drop prefixes at the same time. I'd probably write some Template Haskell to automate that task (TH would be more fun than typing all the definitions by hand). Something like:

$(convertToLabelOptics (drop 3)
  [ ''cleSummary
  , ''cleConferenceProperties
  , ...
  ]

or maybe even reify module contents, look for lenses and do even more magical thing. It would be more uniform, than doing it by hand. AWS and GoogleCloud APIs are huge, and it's hard to know what part you will need next.

amazonka and gogol libraries are code generated, so one other option is to hack the generator to produce an optics packages too.

Chart is not much different API lens-wise, though smaller. There the manual creation of Chart-optics might be viable.

#percent operator

In one place the HMR actually used Rational, and the Rational smart constructor %. In that module the optics weren't used, so I went with hiding ((%)). Maybe I'd defined rational named constructor if I needed it more.

#lens-aeson

In one library integrating with peculiar JSON API, Futurice uses lens-aeson, luckily there's also aeson-optics so the that issue is fixed by changing the import.

In that same spot we run into other difference between optics and lens: ^. in optics really wants a getter. You cannot give it a Prism like _String. lens behavior was (ab)used to return mempty i.e. empty Text on non-match. I think using foldOf is better, though a combinator requiring AffineFold would been even better (i.e. fold resulting at most one value, the non-match could be still mempty, or def from Default).

Similarly in some places ^? were used with folds to get the first value. There headOf is semantically more correct.

By the way, we debated whether we should renamed more stuff for optics, but settled to keep the names mostly the same. It really shows in the migration overall. Many things just work out of the box, after changing the imports.

#Representable

futurice-prelude defines a following type-class:

class Ixed m => Pick m where
    --   ::              Index m -> Lens' m (IxValue m)
    pick :: Functor f => Index m -> LensLike' f m (IxValue m)

instance Eq e => Pick (e -> a) where
    pick e p f = p (f e) <&> \a e' -> if e == e' then a else f e'
    {-# INLINE pick #-}

It's useful when working with Representable containers, where Rep f, i.e. index is some enumerable type. For example:

data PerDayOfWeek a = PWD a a a a a a a

which can be indexable (representble?) by DayOfWeek. One can use PerDayOfWeek to aggregate data per day of the week. I find that quite common need.

One could directly convert that class to use optics, but that is unnecessary. optics' ix combinator could be stronger than default AffineTraversal, for example a Lens for Representable containers. In my opinion this simplifies code, as one uses the same combinator -- ix -- to index Maps and the types like PerDayOfWeek.

instance Ixed (PerDayOfWeek a) where
    type IxKind (PerDayOfWeek a) = A_Lens
    ix = lensVL gix

where gix derives the Lens generically.

#Classy lenses

HMR has also plenty classy lens type-classes, defined manually. There the identity instance needs to be implemnted as castOptic simple:

 class HasUUID a where
     uuid :: Lens' a UUID

 instance HasUUID UUID where
-    uuid = id
+    uuid = castOptic simple

Another alternative would be to the scratch whole class, and rather define

type HasUuid a = LabelOptic "uuid" A_Lens a a UUID UUID

and use OverloadedLabels.

#Small usage of lensVL

In few places HMR uses lens interface to libraries, which don't have an optics counterpart yet. That's where one could selectively sprinkle lensVL:

-name = datatypeInfo (Proxy :: Proxy a) ^. datatypeName . packed
+name = datatypeInfo (Proxy :: Proxy a) ^. lensVL datatypeName % packed

(The library in question is generics-sop-lens, and in fact there is an unreleased optics variant: optics-sop)

Another use-case for lensVL is when some lenses are defined manually, directly using their van Laarhoven encoding:

-worldTasks f (World es ts ls is arc _ _) = f ts <&> ...
+worldTasks = lensVL $ \f (World es ts ls is arc _ _) -> f ts <&> ...

Here we move things a bit and insert lensVL in one place, thus avoiding rewriting the actual code of the lens.

#Custom combinators consuming optics

One may notice that optics doesn't have types like Getting, ALens or ATraversal. That is because optics types aren't RankNTypes, so Lens works as well as ALens. Almost.

You may need to do rewrites similar to the following one:

-toIdMapOf :: HasKey a => Getting (Endo [a]) s a -> s -> IdMap a
+toIdMapOf :: (HasKey a, Optics.Is k A_Getter)
+                      => Optic' k is s a -> s -> IdMap a

This is not nice, but that's what we have in optics. (Not that Endo [a] is nice either).

One could write also

toIdMapOf :: HasKey a => Getter s a -> s -> IdMap a

but that would accept only a Getter (same for lens IIRC), thus we need to jump through a hoop to make more usable definitions.

#No IndexedFold

This a thing which is renamed in optics, indexed variants are named more shortly, in this case you are looking for IxFold. The indexed optics are well supported in optics, and though they are slightly different in their interface, I didn't run into show stopper problems.

#withIndex

There are no withIndex in optics. In HMR it was used in a following snippet:

toMapOf (ifolded % withIndex % alongside (to EnumValue) id % ifolded) im

Let's try to understand what happens there. We fold with index, drop down the index into value, map over the index, and as we have (newIndex, value) we make an indexed fold with the new index.

Why not just remap index directly using reindexed:

toMapOf (ifolded %& reindexed EnumValue) im

Turns out we don't need withIndex here. One could use migration to optics as an opportunity to make a code review scan of their codebase.

Note the composition-like combinator, %&, it allows to post-process optics with "optics transformers", which aren't optics themselves, like reindexed. % and %& are left associative (. is right associative), so the above ifolded &% reindexed EnumValue would work as a part of a bigger optic too.

#ALens

In one module the ALens type was used, with its special operators #~, ^# etc. You sometimes need to take a whole ALens in, if you both view and set. With optics one can use Lens with .~ and ^..

And that's the last noteworthy issue. After a while, everything compiles and even tests pass on the first run.

#Conclusion

I hope that this (almost) "real case study" illustrates some issues which one could run into when moving to use optics, in old or new codebase.

It's worth mentioning that the most tricky issues were inside the auxiliary libraries. The core domain logic, with types which had optics build with makeLenses require mostly only changing . to %.

The biggest obstacle are libraries which have lens i.e. van Laarhoven encoding interfaces. Yet, creating optics interface for them in advance is not insurmountable task.

Whether optics is better for your team is to your team to decide, optics are suitable for "real world haskell".


Site proudly generated by Hakyll