LensBeginnersCheatsheet
Edward Kmett’s lens
package. “JQuery for Haskell values”.
import Control.Lens
If you want to import the lens functions qualified, but the lens operators unqualified, then
import qualified Control.Lens
import Control.Lens.Operators
Using Lenses[edit]
Control.Lens.Setter | over setter f s |
setter %~ f $ s |
modify pure value |
set setter b s |
setter .~ b $ s |
set pure value | |
setter %= f |
modify MonadState | ||
setter .= b |
set MonadState | ||
Control.Lens.Getter | s ^. getter |
get pure value | |
view getter |
get MonadReader | ||
use getter |
get MonadState |
where
setter :: Setter s t a b
getter :: Getter s a
s :: s
b :: b
f :: a -> b
Many other similar functions and operators are available.
Composing Lenses[edit]
Use .
and pretend you're using a more mainstream language: outerLens . innerLens
.
s = [Data.Map.singleton "bob" 7,
Data.Map.fromList [("alice", 5), ("kerry", 8)],
Data.Map.singleton "harry" 6]
t = element 1 . at "kerry" .~ Just 42 $ s
-- t = [Data.Map.singleton "bob" 7,
-- Data.Map.fromList [("alice", 5), ("kerry", 42)],
-- Data.Map.singleton "harry" 6]
Types (stab stab stabbity stab stab stab)[edit]
Mostly of the form
type Something s t a b = forall f. {- some constraint on f -} => (a -> f b) -> (s -> f t)
with a simple "primed" form
type Something' s a = Something s s a a
These allow us to
- focus on an inner value of type
a
... within an outer value of types
; and perhaps - provide (a) new inner value(s) of type
b
... to produce a new outer value of typet
The simple types therefore describe lenses that produce new values without changing the types.
Setter s t a b |
set or modify value |
Getter s a |
get value |
Traversal s t a b |
focus on one, none or many values; can be used as a Setter;can be used as a Getter if a is a Monoid |
Lens s t a b |
can be used as a Getter/Setter/Traversal/etc |
Many other lens types are available. You can use a value of a more general type where a value of a more specific type is required. Some values are presented in this document with a more specific and less esoteric type than the more general and less common type they really have.
Predefined Lenses[edit]
Control.Lens.At | at :: Ord k => k -> Lens' (Map k v) (Maybe v)
|
Just v -> value is present; Nothing -> value is absent
|
at :: (Eq k, Hashable k) => k -> Lens' (HashMap k v) (Maybe v)
| ||
at :: Int -> Lens' (IntMap v) (Maybe v)
| ||
Control.Lens.Traversal | element :: Int -> Traversable f => Traversal' (f v) v
|
get/set/modify nth element of a container; no effect if no nth element |
Many other predefined lenses are available.
Generating Lenses For Your Own Record Types[edit]
Using the Lens Function[edit]
Create Lenses for a record using module helper functions.
import Control.Lens (lens, Lens')
data Foo a = Foo {_bar :: Int,
_baz :: a,
quux :: String}
foo_barL :: Lens' (Foo a) Int
foo_barL = lens _bar (\x y -> x { _bar = y })
foo_bazL :: Lens' (Foo a) a
foo_bazL = lens _baz (\x y -> x { _baz = y })
Using Templates[edit]
The aforementioned boiler plate can be auto-generated by template Haskell.
{-# LANGUAGE TemplateHaskell #-}
import Control.Lens.TH
data Foo a = Foo {_bar :: Int,
_baz :: a,
quux :: String}
$(makeLenses ''Foo) -- creates `bar :: Lens' (Foo a) Int` and `baz :: Lens (Foo a) (Foo b) a b
$(makeLensesFor [("_bar", "bar"), ("_baz", "baz")] ''Foo) -- the same
Many other TH lens functions are available providing varying amounts of control.