category feedLensesMiscellaneouseditdelete







Lenses are a universal solution to data manipulation in Haskell. They make working with nested data (tuples, records, lists of vectors of tuples of records) easy.

You can use fst to get the first element of a pair, and you can write \(_, b) -> (a, b) to change the first element of a pair – wouldn't it be nice if you could do both with the same function? Well, lenses do exactly that. Additionally, you can combine lenses into chains – for instance, if you want to modify the n-th element of a list buried inside a tuple that is a record field, with lens you can do it as set (someField . _1 . ix n) someValue. Look at this post to see the power of lenses for yourself.

All libraries here provide a way to automatically generate lenses for a record (since it's one of the most common uses for lenses). Some also provide stock lenses for common types like tuples, lists, Either, and more.

“van Laarhoven” refers to a particular type of lenses that can be defined without depending on any lens library and are generally very clever and very generalisable (but they can be somewhat hard to understand).

Recommendations

  • If you don't mind dependencies, just use lens. It's the most used package and the most featureful one.

  • If you mind dependencies, use microlens, which lets you choose exactly what dependencies you want/don't want and follows lens closely.

  • If you're only starting with lenses, probably use microlens/microlens-platform as it's got nice docs and lots of examples, but be prepared to look into lens-simple's source.

edit description
or press Ctrl+Enter to savemarkdown supported
#
lens-simple (Hackage)
van Laarhoven
move item up move item down edit item info delete item
Summary edit summary

Another small lens-compatible library. Has a simpler implementation, which is good for learning. Doesn't have good docs, which is bad for learning.

Summary quit editing summary
Prosedit prosquit editing pros
  • Rather small, has few dependencies.
    move trait up move trait down edit trait delete trait
  • Unlike microlens, has *Of functions and many operators from lens (<>~, &&=, etc).
    move trait up move trait down edit trait delete trait
  • The implementation is simpler than that of either lens or microlens (so it could be good for studying how lenses work).
    move trait up move trait down edit trait delete trait

press Ctrl+Enter or Enter to addmarkdown supportededit off
Consedit consquit editing cons
  • Doesn't use overloading, so _1 and _2 only work on pairs, ix doesn't work with lists, and at only works with Map. If you try to use it for a big project, you might end up annoyed with missing functionality.
    move trait up move trait down edit trait delete trait
  • Doesn't provide lens's more advanced features (like prisms or indexed traversals).
    move trait up move trait down edit trait delete trait
  • Its Fold can't be used by functions from lens that take a Fold from lens, which potentially hurts compatibility a bit.
    move trait up move trait down edit trait delete trait
  • Could be slower than lens (due to the absence of INLINE pragmas – but I haven't benchmarked).
    move trait up move trait down edit trait delete trait

press Ctrl+Enter or Enter to addmarkdown supportededit off
Ecosystemedit ecosystem
Ecosystemquit editing ecosystemor press Ctrl+Enter to savemarkdown supported
#
van Laarhoven
move item up move item down edit item info delete item
Summary edit summary

A fork of lens that explicitly tries to be as small as possible while still being useful (e.g. all extra features are split into separate packages). Provides a somewhat different set of functions than lens-simple, but generally is closer to lens than lens-simple is. Like lens, uses ad-hoc typeclasses to provide overloaded lenses.

Summary quit editing summary
Prosedit prosquit editing pros
  • Very small (the base package has no dependencies at all).
    move trait up move trait down edit trait delete trait
  • Has better documentation than either lens-simple or lens.
    move trait up move trait down edit trait delete trait
  • It's just a fork of lens, so nothing has been renamed and everything behaves in the same way. (And also it should be just as fast.)
    move trait up move trait down edit trait delete trait
  • Doesn't omit overloaded lenses (so at and _1 work with many things) – and it also provides each, a traversal that can traverse mostly everything.
    move trait up move trait down edit trait delete trait

press Ctrl+Enter or Enter to addmarkdown supportededit off
Consedit consquit editing cons
  • Doesn't provide lens's more advanced features (like prisms or indexed traversals).
    move trait up move trait down edit trait delete trait
  • Doesn't let you write code in fully “lensy” style (since it omits lots of operators and *Of functions from lens).
    move trait up move trait down edit trait delete trait
  • Provides orphan instances in microlens-ghc and microlens-platform.
    move trait up move trait down edit trait delete trait

press Ctrl+Enter or Enter to addmarkdown supportededit off
Ecosystemedit ecosystem

Official:

Unofficial:

Ecosystemquit editing ecosystemor press Ctrl+Enter to savemarkdown supported
Notes
collapse notesedit notes

Imports

If importing everything separately is annoying to you, Lens.Micro.Platform from microlens-platform reexports functions from all other packages (together with instances for HashMap, Vector, etc). Otherwise:

  • Lens.Micro exports most things
  • Lens.Micro.TH from microlens-th exports makeLenses and so on
  • Lens.Micro.Mtl from microlens-mtl exports view/use, .=/%=/etc, and zoom

Usage

See notes for lens.

Gotchas

If you're looking for view: it's not in Lens.Micro. Either do import Lens.Micro.Extras (view) or use microlens-platform. Same goes for preview.

collapse notesedit notes
#
lens (Hackage)
van Laarhoven
move item up move item down edit item info delete item
Summary edit summary

The most widely used and most featureful lens library. Can be overkill in some cases, but is often the best fit for applications. Can also be hard to understand, and hence use (since without understanding what happens inside, you're bound to stumble somewhere sooner or later).

Summary quit editing summary
Prosedit prosquit editing pros
  • The most popular lens library, by a huge margin (and one of most popular overall on Hackage).
    move trait up move trait down edit trait delete trait
  • Contains pretty much everything you could want – in addition to usual lenses (for manipulating lists, maps, tuples, and standard types like Maybe/Either/etc), lens has functions for manipulating filepaths, Template Haskell structures, generics, complex numbers, exceptions, Text, Vector, ByteString, and so on. Other libraries aren't even close.
    move trait up move trait down edit trait delete trait
  • Unlike most other libraries, has prisms – a kind of lenses that can act both as constructors and deconstructors at once. They can be pretty useful when you're dealing with exceptions, Template Haskell, JSON, sum types, etc.
    move trait up move trait down edit trait delete trait
  • Probably the most performant one.
    move trait up move trait down edit trait delete trait

press Ctrl+Enter or Enter to addmarkdown supportededit off
Consedit consquit editing cons
  • Takes a lot of time to compile, and has a lot of dependencies as well.
    move trait up move trait down edit trait delete trait
  • Some of its advanced features are very intimidating, and the whole library may seem overengineered. See this post.
    move trait up move trait down edit trait delete trait
  • Once you start using lenses for everything (which happens often to users of lens), your code may start not looking like Haskell much and people not used to this style will have a hard time understanding it. See this post.
    move trait up move trait down edit trait delete trait
  • Doesn't have (unlawful) monadic lenses (i.e. you can't write something like Lens' (IORef a) a).
    move trait up move trait down edit trait delete trait

press Ctrl+Enter or Enter to addmarkdown supportededit off
Ecosystemedit ecosystem
Ecosystemquit editing ecosystemor press Ctrl+Enter to savemarkdown supported
Notes
collapse notesedit notes

Links

If your question isn't answered here, there's an IRC channel (#haskell-lens) which you can join here.

Imports

Control.Lens reexports most things you might need. However, to get additional lenses, import:

  • Control.Exception.Lens for lenses for things from Control.Exception
  • Data.Bits.Lens for manipulation of bits
  • Data.Complex.Lens for things from Data.Complex
  • Language.Haskell.TH.Lens for things from Language.Haskell.TH
  • ...you get the idea

Basic operations

Extract a value from a bigger value: value ^. lens or view lens value:

> (1,2) ^. _1
1

Set a part of a bigger value: value & lens .~ x or set lens x value (.~ is a synonym for set and & just applies a function to a value):

> (1,2) & _1 .~ 10
(10,2)

Modify a part of a bigger value: value & lens %~ f or over lens f value:

> (1,2) & _1 %~ negate
(-1,2)

(Lens is known for its operators (120 and counting); you can find a table of them here.)

Generate lenses for your record type:

{-# LANGUAGE TemplateHaskell #-}

data FullName = FullName {
  _name       :: String,
  _middleName :: Maybe String,
  _surname    :: Maybe String }

data Person = Person {
  _fullName :: FullName,
  _age      :: Int }

makeLenses ''FullName
makeLenses ''Person

And use them:

> let theName = FullName "Richard" Nothing (Just "Ellys")
> let richard = Person theName 28

> richard ^. fullName . surname
Just "Ellys"

> richard & age %~ succ
Person (FullName "Richard" Nothing (Just "Ellys")) 29

Different types of lenses

Lens provides several types of accessors – they all do different things and they all can be composed with each other:

  • Lens' s a – points at a single part of a structure. The structure has the type s, the part has the type a.

  • Lens s t a b – points at a single part of a structure, but lets you change the type of the part – i.e. if you apply a function of type a -> b, the whole thing will go from s to t. Lens' s a is the same as Lens s s a a. An example: _1 has the type Lens (a, x) (b, x) a b.

  • Traversal' s a – modifies (or extracts) several parts of a structure (Traversal s t a b exists as well). If you use set/over, it will overwrite/apply a function to all parts. If you use view/^., it will concatenate the extracted values using <>. To get a list of extracted values, use ^.. instead of ^.. An example: both has the type Traversal' (a, a) a:

    > (1, 2) ^.. both
    [1, 2]
  • Prism' s a – converts s into a if possible (so it behaves as a Traversal that either points to a single element or doesn't point to anything). Anything you can do with a traversal you can do with a prism. A bonus feature is that it can also convert a into s. An example: _Right :: Prism (Either x a) (Either x b) a b:

    > Left 0 ^.. _Right
    []
    
    > Right 0 ^.. _Right
    [0]
    
    > _Right # 0
    Right 0

    By composing prisms you can build bigger prisms and they still would work both as accessors and as constructors.

  • Iso' s a – can always convert s into a and a into s. So, something like a Lens' s a that you can turn into Lens' a s using from. For instance, if you've got a lazy Text and you have a function that works on strict Text, you can apply it to your lazy Text like this:

    > someLazyText & strict %~ f

    Or you can do the opposite if f works on lazy Text:

    > someStrictText & from strict %~ f

There are also some other, less powerful variants: Getter is like Lens that can't modify the value, Setter is like Traversal that can't extract parts of the value, Fold is like Getter but can extract many elements.

Lenses as functions

Lenses are just functions under the hood, and so they can be composed with .. For instance, _1._2 is a lens that accesses the 2nd element of the 1st element of a tuple. When you compose a lens and a traversal, you get a traversal; a lens and a getter – a getter; a traversal and a setter – a setter; a getter and a setter can't be composed; etc.

Here is how Lens is defined:

type Lens s t a b = Functor f => (a -> f b) -> (s -> f t)

It's quite similar to map and traverse:

map :: (a -> b) -> ([a] -> [b])
traverse :: (Applicative f, Traversable t) => (a -> f b) -> t a -> f (t b)

If you compose map.map, you will get something of type (a -> b) -> ([[a]] -> [[b]]). It's almost the same with lenses, except that with lenses there's also f in the mix. f is what lets lenses be used as getters (unlike map) with a clever trick involving Const.

Since lenses are functions, you can apply them directly. For instance, _1 print (1, 2) is an IO action that would print “1” when executed. Generally, you can use lenses and traversals the same way you can use traverse or mapM (and moreover, traverse is a Traversal). This all also means that you can define lenses and traversals in your code without depending on lens-the-package.

Standard lenses (and traversals and prisms)

  • _1, _2, _3, ... – the 1st/2nd/3rd/etc element of a tuple (any tuple, since they're overloaded – e.g. you can use _1 both with (a,b) and (a,b,c)).

  • each – a traversal for mostly anything (elements of a list, vector, tuple, Map, characters in a Text, bytes in a ByteString, etc).

  • at − a lens for Map-like things; at "foo" points at the element with the key "foo". An interesting feature of it is that you can use it to insert and delete elements by setting Nothing or Just v:

    > Map.fromList [(1,"world")] ^. at 1
    Just "world"
    
    > Map.fromList [(1,"world"]) & at 1 .~ Nothing
    fromList []
    
    > Map.fromList [(1,"world"]) & at 2 .~ Just "hi"
    fromList [(1,"world"), (2,"hi")]
  • ix – a traversal for “element-at-index”; similar to at, but can't be used for inserting/deleting elements and works with more things (e.g. lists and vectors).

  • _head, _tail, _init, _last – traversals for first/last element (and init/tail) of various structures (like ix, they are overloaded)

  • folded – a getter for anything Foldable; mapped – a setter for any Functor; traversed – a traversal for any Traversable (but in many cases each is going to work as well).

  • filtered – a traversal that traverses an element only if it satisfies a predicate:

    > (1,2,4,0,3) ^.. each . filtered even
    [2,4,0]

    You can use it for setting/modifying too, but if you're going to use it to define other traversals, read this first because you might get bitten otherwise.

  • _Left, _Right, _Just, _Nothing – prisms for accessing branches of Either and Maybe.

  • worded and lined – traversals for words/lines in a string.

  • strict, lazyIsos for converting Text/ByteString from lazy to strict or vice-versa.

Writing your own lenses

You can use lens, prism, iso, setting folding, or to (for getters) to create a lens/prism/etc out of a getter and a setter. You can also easily write lenses and traversals manually:

  • Lens:

    _1 :: Lens (a, x) (b, x) a b
    _1 f = \(a, x) -> (,x) <$> f b
  • Traversal:

    both :: Traversal' (a, a) a
    both f = \(a1, a2) -> (,) <$> f a1 <*> f a2
    
    _head :: Traversal' [a] a
    _head f   []   = pure []
    _head f (x:xs) = (:xs) <$> f x

*Of functions

Many functions from base have their *Of counterparts in lens. When a function traverses something, its *Of counterpart traverses something using the traversal you give to it.

Are there any even elements in a tuple?

> anyOf each even (1,2)
True

How many elements are in a list of lists?

> lengthOf (each.each) [[1,2],[3,4],[5,6]]
6

How many elements are equal to their index?

> length . filter (\(i, x) -> i == x) . zip [0..] $ [0,-1,2,-3]
2

> lengthOf (traversed.ifiltered (==)) [0,-1,2,-3]
2

Indexed traversals

An indexed traversal is a traversal that gives the index of the traversed element to the function. Indexed traversals can be used like ordinary traversals too, thanks to some horrible magic.

Most of the time you can make an indexed operator of an ordinary one by adding @ to it, or an indexed function out of ordinary one by sticking i in front of it. A lot of standard traversals are already indexed (e.g. traversed). For instance, here we multiply each element in the list by its index:

> [1,4,2,3,1] & traversed %@~ (\i x -> (i+1) * x)
[1,8,6,12,5]

(each isn't an indexed traversal, but you can use e.g. Data.Text.Lens.text and Data.ByteString.Lens.bytes for Text and ByteString respectively.)

A lot of functions from base have their indexed counterparts in lens. For instance, you can use iany to check whether any element in the list is equal to its index, and ifind to actually find that element:

> iany (==) [4,2,3,3]
True

> ifind (==) [4,2,3,3]
Just (3,3)

You can combine indices with another traversal to only traverse elements with index satisfying some condition:

> over (traversed.indices (>0)) reverse ["He","was","stressed","o_O"]
["He","saw","desserts","O_o"]

When you compose indexed traversals, by default the index from the right traversal is retained:

> ["abcd","efgh"] ^@.. traversed.traversed
[(0,'a'),(1,'b'),(2,'c'),(3,'d'),
 (0,'e'),(1,'f'),(2,'g'),(3,'h')]

You can use <. to retain the index from the left traversal:

> ["abcd","efgh"] ^@.. traversed<.traversed
[(0,'a'),(0,'b'),(0,'c'),(0,'d'),
 (1,'e'),(1,'f'),(1,'g'),(1,'h')]

Or you can use <.> to combine both indexes into a tuple:

> ["abcd","efgh"] ^@.. traversed<.>traversed
[((0,0),'a'),((0,1),'b'),((0,2),'c'),((0,3),'d'),
 ((1,0),'e'),((1,1),'f'),((1,2),'g'),((1,3),'h')]

For some types, several variants of indexing are possible – for instance, when you're traversing a Map k v, you could say that the index should be k (i.e. the element's key), or Int (i.e. the order in which it was traversed). itraversed gives you the former, and traversed gives you the latter:

> let m = Map.fromList [("John","Doe"), ("Jane","Roe")]

> m ^@.. traversed
[(0,"Roe"),(1,"Doe")]

> m ^@.. itraversed
[("Jane","Roe"),("John","Doe")]

indexing can turn any traversal into an indexed traversal, and indexed64 does the same but uses Int64 as the index (in case your structure is really big).

Common gotchas

  • weird error messages about Monoid usually appear when you try to use ^. on a traversal

  • can't combine traversals vertically (e.g. can't take _1 and _3 and make a traversal that traverses the 1st and 3rd elements of a tuple)

  • if you want to make a list of lenses or store a lens in a record, you have to use ALens instead of Lens

TODO

  • write about using lenses with state and reader
  • mention pattern synonyms
  • mention ^?, ^?!, singular, has, etc etc etc
  • combining folds with <>x ^.. (a <> b) is the same as (x ^.. a) ++ (x ^.. b)
collapse notesedit notes
#
fclabels (Hackage)
other
move item up move item down edit item info delete item
Summary edit summary

A do-it-yourself lens library that doesn't try to be a universal data manipulation toolkit – if you don't need such a toolkit, and if you want monadic lenses, it could be useful.

Summary quit editing summary
Prosedit prosquit editing pros
  • Few dependencies (compared to lens).
    move trait up move trait down edit trait delete trait
  • Has lenses that can report errors (via Either).
    move trait up move trait down edit trait delete trait
  • Has monadic lenses (e.g. you could make a lens that reads a file, or an IORef, or something from a database).
    move trait up move trait down edit trait delete trait
  • Lets you compose lenses into bigger lenses (a pretty unique feature among lens libraries – all other libraries require you to write lenses manually or provide a getter and a setter).
    move trait up move trait down edit trait delete trait
  • Can make lenses for GADTs (see an example in the notes).
    move trait up move trait down edit trait delete trait

press Ctrl+Enter or Enter to addmarkdown supportededit off
Consedit consquit editing cons
  • Doesn't have traversals at all. (Apart from “partial lenses” like just.)
    move trait up move trait down edit trait delete trait
  • Provides very few lenses.
    move trait up move trait down edit trait delete trait
  • Is designed to be imported qualified (which can be annoying), and you have to import Prelude hiding (id, (.)) as well if you want to use it.
    move trait up move trait down edit trait delete trait

press Ctrl+Enter or Enter to addmarkdown supportededit off
Ecosystemquit editing ecosystemor press Ctrl+Enter to savemarkdown supported
Notes
collapse notesedit notes

Links

Imports

The default is total lenses that can't change the type of the value (they are called :->):

{-# LANGUAGE TypeOperators #-}

import Data.Label ((:->))
import qualified Data.Label as L
-- for predefined lenses
import qualified Data.Label.Base as L

GADTs

This works with fclabels and silently fails with lens:

{-# LANGUAGE GADTs, TemplateHaskell #-}

import qualified Data.Label as L

data X a where
  X :: {_a :: String} -> X Bool

L.mkLabel ''X

Constructing lenses out of smaller lenses

fclabels has operators that let you create “views” into structures, which could be useful if e.g. you have fields that are related, but not related enough to move them out into their own datatype. Here's a (somewhat contrived) example.

First, some prerequisites:

{-# LANGUAGE TypeOperators, TemplateHaskell #-}

import Data.Label ((:->), (>-))
import qualified Data.Label as L
import Prelude hiding (id, (.))
import Control.Category (id, (.))

data Person = Person
  { _name   :: String
  , _age    :: Int
  , _place  :: Place
  } deriving Show

data Place = Place
  { _city
  , _country
  , _continent :: String
  } deriving Show

L.mkLabels [''Person, ''Place]

And the view itself:

ageAndCity :: Person :-> (Int, String)
ageAndCity = L.point $
  (,) <$> L.fst >- age
      <*> L.snd >- city . place

(Of course, instead of (,) you could use any other data constructor.)

Monadic lenses

fclabels lets you define lenses that work in some monad. For instance, partial lenses (here f is the outer type and o is the inner type):

type (:~>) f o = Poly.Lens (Kleisli Maybe) f o

And lenses that work in Either and can report errors (and e.g. validate the value you're trying to set before setting it):

type Lens e f o = Poly.Lens (Kleisli (Either e)) f o

Similarly we could define a type for lenses that have access to IO:

{-# LANGUAGE TupleSections #-}

import qualified Data.Label.Poly as Poly
import qualified Data.Label.Mono as Mono

import Control.Arrow
import Control.Exception (evaluate)
import Control.Category ((.), id)
import Prelude hiding ((.), id)
-- The type
type IOLens f o = Mono.Lens (Kleisli IO) f o
-- Functions for getting/setting/modifying (for some reason you have to
-- define them manually – I stole the definitions from Data.Label.Failing
-- and changed the types)

get :: IOLens s a -> s -> IO a
get l = runKleisli (Poly.get l)

set :: IOLens s a -> a -> s -> IO s
set l v = runKleisli (Poly.set l . arr (v,))

modify :: IOLens s a -> (a -> a) -> s -> IO s
modify l m = runKleisli (Poly.modify l . arr (arr m,))
-- A function to create a lens from a getter and a setter
lens :: (f -> IO o)
     -> ((o -> IO o) -> f -> IO f)
     -> IOLens f o
lens g s = Poly.lens (Kleisli g) (Kleisli (\(m, f) -> s (runKleisli m) f))
-- And, finally, the lens itself
file :: IOLens FilePath String
file = lens readFile setter
  where
    -- f :: String -> IO String
    setter f path = do
      x <- readFile path
      evaluate (length x)    -- force the file to be read fully
      writeFile path =<< f x
      return path
collapse notesedit notes
#
data-lens-light (Hackage)
other
move item up move item down edit item info delete item
Summary edit summary

A really really basic lenses library that only seems to be useful for record manipulation.

Summary quit editing summary
Prosedit prosquit editing pros
  • Has the most obvious implementation – Lens a b = a -> (b -> a, b) – without any tricks or weird typeclasses or anything.
    move trait up move trait down edit trait delete trait

press Ctrl+Enter or Enter to addmarkdown supportededit off
Consedit consquit editing cons
  • Lets you make and use lenses, but doesn't actually give any lenses, so you have to define them by yourself (or use Template Haskell generation).
    move trait up move trait down edit trait delete trait
  • No traversals, no prisms, nothing.
    move trait up move trait down edit trait delete trait
  • Doesn't allow lenses that change the type.
    move trait up move trait down edit trait delete trait

press Ctrl+Enter or Enter to addmarkdown supportededit off
Ecosystemedit ecosystem
Ecosystemquit editing ecosystemor press Ctrl+Enter to savemarkdown supported
Notes
collapse notesedit notes

Imports

import Data.Lens.Light

Usage

First let's define some lenses for tuples (to use them as examples):

fstL :: Lens (a, b) a
fstL = lens fst (\(a, _) b -> (a, b))

swapL :: Lens (a, b) (b, a)
swapL = iso swap swap
  where swap (x, y) = (y, x)

Getting/setting/modifying:

> getL fstL (1,2)
1

> setL fstL 10 (1,2)
(10,2)

> modL fstL negate (1,2)
(-1,2)

Generating lenses with TH:

{-# LANGUAGE TemplateHaskell #-}

data Score = Score {
  _p1Score :: Int,
  _p2Score :: Int,
  rounds :: Int }

makeLenses ''Score
collapse notesedit notes