Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Lens.Micro
Contents
- (&) :: a -> (a -> b) -> b
- type ASetter s t a b = (a -> Identity b) -> s -> Identity t
- sets :: ((a -> b) -> s -> t) -> ASetter s t a b
- (%~) :: ASetter s t a b -> (a -> b) -> s -> t
- over :: ASetter s t a b -> (a -> b) -> s -> t
- (.~) :: ASetter s t a b -> b -> s -> t
- set :: ASetter s t a b -> b -> s -> t
- mapped :: Functor f => ASetter (f a) (f b) a b
- type Getting r s a = (a -> Const r a) -> s -> Const r s
- (^.) :: s -> Getting a s a -> a
- (^..) :: s -> Getting (Endo [a]) s a -> [a]
- toListOf :: Getting (Endo [a]) s a -> s -> [a]
- (^?) :: s -> Getting (First a) s a -> Maybe a
- (^?!) :: s -> Getting (Endo a) s a -> a
- folded :: (Foldable f, Applicative (Const r)) => Getting r (f a) a
- has :: Getting Any s a -> s -> Bool
- type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
- type Lens' s a = Lens s s a a
- lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
- type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t
- type Traversal' s a = Traversal s s a a
- both :: Traversal (a, a) (b, b) a b
- _Left :: Traversal (Either a b) (Either a' b) a a'
- _Right :: Traversal (Either a b) (Either a b') b b'
- _Just :: Traversal (Maybe a) (Maybe a') a a'
- _Nothing :: Traversal' (Maybe a) ()
- class Field1 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field2 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field3 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field4 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field5 s t a b | s -> a, t -> b, s b -> t, t a -> s where
Documentation
Setting (applying a function to values)
type ASetter s t a b = (a -> Identity b) -> s -> Identity t Source
ASetter s t a b
is something that turns a function modifying a value
into a function modifying a structure. If you ignore
Identity
(as Identity a
is the same thing as a
),
the type is:
type ASetter s t a b = (a -> b) -> s -> t
This means that examples of setters you might've already seen are:
map
:: (a -> b) -> [a] -> [b](which corresponds to
mapped
)fmap
::Functor
f => (a -> b) -> f a -> f b(which corresponds to
mapped
as well)first
:: (a -> b) -> (a, x) -> (b, x)(which corresponds to
_1
)left
:: (a -> b) -> Either a x -> Either b x(which corresponds to
_Left
)
The reason Identity
is used here is for ASetter
to
be composable with other types, such as Lens
.
Technically, if you're writing a library, you shouldn't use this type for
setters you are exporting from your library; the right type to use is
Setter
, but it is not provided by microlens. It's completely alright,
however, to export functions which take an ASetter
as an argument.
(%~) :: ASetter s t a b -> (a -> b) -> s -> t infixr 4 Source
(%~
) applies a function to the target; an alternative explanation is that
it is an inverse of sets
, which turns a setter into an ordinary
function.
is the same thing as mapped
%~
reverse
.fmap
reverse
See over
if you want a non-operator synonym.
Negating the 1st element of a pair:
>>>
(1,2) & _1 %~ negate
(-1,2)
Turning all Left
s in a list to upper case:
>>>
(mapped._Left.mapped %~ toUpper) [Left "foo", Right "bar"]
[Left "FOO",Right "bar"]
over :: ASetter s t a b -> (a -> b) -> s -> t Source
Getting fmap
in a roundabout way:
over
mapped
::Functor
f => (a -> b) -> f a -> f bover
mapped
=fmap
Applying a function to both components of a pair:
over
both
:: (a -> b) -> (a, a) -> (b, b)over
both
= \f t -> (f (fst t), f (snd t))
Using
as a replacement for over
_2
second
:
>>>
over _2 show (10,20)
(10,"20")
mapped :: Functor f => ASetter (f a) (f b) a b Source
mapped
is a setter for everything contained in a functor. You can use it
to map over lists, Maybe
, or even IO
(which is something you can't do
with traversed
or each
).
Here mapped
is used to turn a value to all non-Nothing
values in a list:
>>>
[Just 3,Nothing,Just 5] & mapped.mapped .~ 0
[Just 0,Nothing,Just 0]
Keep in mind that while mapped
is a more powerful setter than each
, it
can't be used as a getter! This won't work (and will fail with a type error):
[(1,2),(3,4),(5,6)]^..
mapped
.both
Getting (retrieving a value)
Getters are a not-entirely-obvious way to use (supposedly) value-changing
traversals to carry out information from a structure. For details, see the
documentation for Getting
.
Exporting Getter
is impossible, as then microlens would have to depend on
contravariant.
(^.) :: s -> Getting a s a -> a infixl 8 Source
(^.
) applies a getter to a value; in other words, it gets a value out of a
structure using a getter (which can be a lens, traversal, fold, etc.).
Getting 1st field of a tuple:
(^.
_1
) :: (a, b) -> a (^.
_1
) =fst
When (^.
) is used with a traversal, it combines all results using the
Monoid
instance for the resulting type. For instance, for lists it would be
simple concatenation:
>>>
("str","ing") ^. each
"string"
The reason for this is that traversals use Applicative
, and the
Applicative
instance for Const
uses monoid concatenation to combine
“effects” of Const
.
Folds (getters which return multiple elements)
(^..) :: s -> Getting (Endo [a]) s a -> [a] infixl 8 Source
s ^.. t
returns the list of all values that t
gets from s
.
A Maybe
contains either 0 or 1 values:
>>>
Just 3 ^.. _Just
[3]
Gathering all values in a list of tuples:
>>>
[(1,2),(3,4)] ^.. each.each
[1,2,3,4]
has :: Getting Any s a -> s -> Bool Source
has
checks whether a getter (any getter, including lenses, traversals, and
folds) returns at least 1 value.
Checking whether a list is non-empty:
>>>
has each []
False
You can also use it with e.g. _Left
(and other 0-or-1 traversals) as a
replacement for isNothing
, isJust
and other
isConstructorName
functions:
>>>
has _Left (Left 1)
True
Lenses (things which are both setters and getters)
type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t Source
Lenses in a nutshell: use (^.
) to get, (.~
) to set, (%~
) to
modify. (.
) composes lenses (i.e. if a B
is a part of A
, and a C
is
a part of in B
, then b.c
lets you operate on C
inside A
). You can
create lenses with lens
, or you can write them by hand (see below).
Lens s t a b
is the lowest common denominator of a setter and a getter,
something that has the power of both; it has a Functor
constraint, and
since both Const
and Identity
are functors, it can
be used whenever a getter or a setter is needed.
a
is the type of the value inside of structureb
is the type of the replaced values
is the type of the whole structuret
is the type of the structure after replacinga
in it withb
A Lens
can only point at a single value inside a structure (unlike a
Traversal
).
It is easy to write lenses manually. The generic template is:
somelens :: Lens s t a b
-- “f” is the “a -> f b” function, “s” is the structure.
somelens f s =
let
a = ... -- Extract the value from “s”.
rebuildWith b = ... -- Write a function which would
-- combine “s” and modified value
-- to produce new structure.
in
rebuildWith <$>
f a -- Apply the structure-producing
-- function to the modified value.
Here's the _1
lens:
_1 :: Lens (a, x) (b, x) a b
_1 f (a, x) = (\b -> (b, x)) <$>
f a
Here's a more complicated lens, which extracts several values from a structure (in a tuple):
type Age = Int type City = String type Country = String data Person = Person Age City Country -- This lens lets you access all location-related information about a person. location ::Lens'
Person (City, Country) location f (Person age city country) = (\(city', country') -> Person age city' country')<$>
f (city, country)
You even can choose to use a lens to present all information contained in
the structure (in a different way). Such lenses are called Iso
in lens's
terminology. For instance (assuming you don't mind functions that can error
out), here's a lens which lets you act on the string representation of a
value:
string :: (Read a, Show a) =>Lens'
a String string f s = read<$>
f (show s)
Using it to reverse a number:
>>> 123&
string%~
reverse 321
type Lens' s a = Lens s s a a Source
This is a type alias for monomorphic lenses which don't change the type of the container (or of the value inside).
lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b Source
lens
creates a Lens
from a getter and a setter. The resulting lens isn't
the most effective one (because of having to traverse the structure twice
when modifying), but it shouldn't matter much.
A (partial) lens for list indexing:
ix :: Int ->Lens'
[a] a ix i =lens
(!!
i) -- getter (\s b -> take i s ++ b : drop (i+1) s) -- setter
Usage:
>>> [1..9]^.
ix 3 4 >>> [1..9] & ix 3%~
negate [1,2,3,-4,5,6,7,8,9]
When getting, the setter is completely unused. When setting, the getter is unused. Both are used only when the value is being modified.
Here's an example of using a lens targeting the head of a list. The getter is
replaced with undefined
to make sure it's not used:
>>>
[1,2,3] & lens undefined (\s b -> b : tail s) .~ 10
[10,2,3]
Traversals (lenses which have multiple targets)
type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t Source
Traversals in a nutshell: they're like lenses but they can point at multiple
values. Use (^..
) (not ^.
) to get all values, (^?
) to get the 1st
value, (.~
) to set values, (%~
) to modify them. (.
) composes traversals
just as it composes lenses.
Traversal s t a b
is a generalisation of Lens
which allows many targets
(possibly 0). It's achieved by changing the constraint to Applicative
instead of Functor
– indeed, the point of Applicative
is that you can
combine effects, which is just what we need to have many targets.
Traversals don't differ from lenses when it comes to setting – you can use
usual (%~
) and (.~
) to modify and set values. Getting is a bit different,
because you have to decide what to do in the case of multiple values. In
particular, you can use these combinators (as well as everything else in the
“Folds” section):
- (
^..
) gets a list of values - (
^?
) gets the 1st value (orNothing
if there are no values) - (
^?!
) gets the 1st value and throws an exception if there are no values
In addition, (^.
) works for traversals as well – it combines traversed
values using the (<>
) operation (if the values are instances of Monoid
).
Traversing any value twice is a violation of traversal laws. You can, however, traverse values in any order.
Ultimately, traversals should follow 2 laws:
t pure ≡ pure fmap (t f) . t g ≡ getCompose . t (Compose . fmap f . g)
The 1st law states that you can't change the shape of the structure or do anything funny with elements (traverse elements which aren't in the structure, create new elements out of thin air, etc.). The 2nd law states that you should be able to fuse 2 identical traversals into one. For a more detailed explanation of the laws, see this blog post (if you prefer rambling blog posts), or The Essence Of The Iterator Pattern (if you prefer papers).
type Traversal' s a = Traversal s s a a Source
This is a type alias for monomorphic traversals which don't change the type of the container (or of the values inside).
Prisms
Prisms are traversals which always target 0 or 1 values. Moreover, it's possible to reverse a prism, using it to construct a structure instead of peeking into it. Here's an example from the lens library:
>>> over _Left (+1) (Left 2) Left 3 >>> _Left # 5 Left 5
However, it's not possible for microlens to export prisms, because their type
depends on Choice
, which resides in the profunctors library, which is a
somewhat huge dependency. So, all prisms included here are traversals
instead.
_Left :: Traversal (Either a b) (Either a' b) a a' Source
_Left
targets the value contained in an Either
, provided it's a Left
.
Gathering all Left
s in a structure (like the lefts
function):
toListOf
(each
._Left
) :: [Either
a b] -> [a]toListOf
(each
._Left
) =lefts
Checking whether an Either
is a Left
(like isLeft
):
>>>
has _Left (Left 1)
True
>>>
has _Left (Right 1)
False
Extracting a value (if you're sure it's a Left
):
>>>
Left 1 ^?! _Left
1
Mapping over all Left
s:
>>>
(each._Left %~ map toUpper) [Left "foo", Right "bar"]
[Left "FOO",Right "bar"]
Implementation:
_Left
f (Left a) =Left
<$>
f a_Left
_ (Right b) =pure
(Right
b)
_Nothing :: Traversal' (Maybe a) () Source
_Nothing
targets a ()
if the Maybe
is a Nothing
, and doesn't target
anything otherwise:
>>>
Just 1 ^.. _Nothing
[]
>>>
Nothing ^.. _Nothing
[()]
It's not particularly useful (unless you want to use
as a
replacement for has
_Nothing
isNothing
), and provided mainly for consistency.
Implementation:
_Nothing
f Nothing =const
Nothing
<$>
f ()_Nothing
_ j =pure
j
Tuples
class Field1 s t a b | s -> a, t -> b, s b -> t, t a -> s where Source
Minimal complete definition
Nothing
Methods
Gives access to the 1st field of a tuple (up to 5-tuples).
Getting the 1st component:
>>>
(1,2,3,4,5) ^. _1
1
Setting the 1st component:
>>>
(1,2,3) & _1 .~ 10
(10,2,3)
Note that this lens is lazy, and can set fields even of undefined
:
>>>
set _1 10 undefined :: (Int, Int)
(10,*** Exception: Prelude.undefined
This is done to avoid violating a lens law stating that you can get back what you put:
>>>
view _1 . set _1 10 $ (undefined :: (Int, Int))
10
The implementation (for 2-tuples) is:
_1
f t = (,)<$>
f (fst t)<*>
pure
(snd t)
or, alternatively,
_1
f ~(a,b) = (\a' -> (a',b))<$>
f a
(where ~
means a lazy pattern).
class Field2 s t a b | s -> a, t -> b, s b -> t, t a -> s where Source
Minimal complete definition
Nothing
Methods
Gives access to the 2nd field of a tuple (up to 5-tuples).
See documentation for _1
.
class Field3 s t a b | s -> a, t -> b, s b -> t, t a -> s where Source
Minimal complete definition
Nothing
Methods
Gives access to the 3rd field of a tuple (up to 5-tuples).
See documentation for _1
.