microlens-0.3.1.0: A tiny part of the lens library which you can depend upon

Safe HaskellNone
LanguageHaskell2010

Lens.Micro

Contents

Synopsis

Documentation

(&) :: a -> (a -> b) -> b infixl 1

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

Since: 4.8.0.0

This operator is useful when you want to modify something several times. For instance, if you want to change 1st and 3rd elements of a tuple, you can write this:

(1,2,3) & _1 .~ 0
        & _3 %~ negate

instead of e.g. this:

(_1 .~ 0) . (_3 %~ negate) $ (1,2,3)

or this:

set _1 0 .
over _3 negate
  $ (1,2,3)

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 this package (because then we'd have to depend on distributive). It's completely alright, however, to export functions which take an ASetter as an argument.

type ASetter' s a = ASetter s s a a Source

This is a type alias for monomorphic setters which don't change the type of the container (or of the value inside). It's useful more often than the same type in lens, because we can't provide real setters and so it does the job of both ASetter' and Setter'.

sets :: ((a -> b) -> s -> t) -> ASetter s t a b Source

sets creates an ASetter from an ordinary function. (The only thing it does is wrapping and unwrapping Identity.)

(%~) :: 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. mapped %~ reverse is the same thing as 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 Lefts 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

over is a synonym for (%~).

Getting fmap in a roundabout way:

over mapped :: Functor f => (a -> b) -> f a -> f b
over 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 over _2 as a replacement for second:

>>> over _2 show (10,20)
(10,"20")

(.~) :: ASetter s t a b -> b -> s -> t infixr 4 Source

(.~) assigns a value to the target. These are equivalent:

See set if you want a non-operator synonym.

Here it is used to change 2 fields of a 3-tuple:

>>> (0,0,0) & _1 .~ 1 & _3 .~ 3
(1,0,3)

set :: ASetter s t a b -> b -> s -> t Source

set is a synonym for (.~).

Setting the 1st component of a pair:

set _1 :: x -> (a, b) -> (x, b)
set _1 = \x t -> (x, snd t)

Using it to rewrite (<$):

set mapped :: Functor f => a -> f b -> f a
set mapped = (<$)

(<%~) :: LensLike ((,) b) s t a b -> (a -> b) -> s -> (b, t) Source

This is a version of (%~) which modifies the structure and returns it along with the new value:

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

Simpler type signatures:

(<%~) ::             Lens s t a b      -> (a -> b) -> s -> (b, t)
(<%~) :: Monoid b => Traversal s t a b -> (a -> b) -> s -> (b, t)

(<<%~) :: LensLike ((,) a) s t a b -> (a -> b) -> s -> (a, t) Source

This is a version of (%~) which modifies the structure and returns it along with the old value:

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

Simpler type signatures:

(<<%~) ::             Lens s t a b      -> (a -> b) -> s -> (a, t)
(<<%~) :: Monoid a => Traversal s t a b -> (a -> b) -> s -> (a, t)

(<<.~) :: LensLike ((,) a) s t a b -> b -> s -> (a, t) Source

This is a version of (.~) which modifies the structure and returns it along with the old value:

>>> (1, 2) & _1 <<.~ 0
(1, (0, 2))

Simpler type signatures:

(<<.~) ::             Lens s t a b      -> b -> s -> (a, t)
(<<.~) :: Monoid a => Traversal s t a b -> b -> s -> (a, t)

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 lenses to carry out information from a structure (instead of changing something inside the structure). Any lens or traversal is a getter.

For details, see the documentation for Getting.

Including Getter is impossible, as then this package would have to depend on contravariant and it's a big dependency.

type Getting r s a = (a -> Const r a) -> s -> Const r s Source

If you take a lens or a traversal and choose Const r as your functor, you will get Getting r s a. This can be used to get something out of the structure instead of modifying it:

s ^. l = getConst (l Const s)

Functions that operate on getters – such as (^.), (^..), (^?) – use Getter r s a (with different values of r) to describe what kind of getter they need. For instance, (^.) needs the getter to be able to return a single value, and so it accepts a getter of type Getting a s a. (^..) wants the getter to gather values together, so it uses Getting (Endo [a]) s a (it could've used Getting [a] s a instead, but it's faster with Endo). The choice of r depends on what you want to do with elements you're extracting from s.

(^.) :: 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.

A non-operator version of (^.) is called view, and it's not included in this package because it is a bit more general (it works in MonadReader and thus requires a mtl dependency). You can get it from microlens-mtl.

Folds (getters returning multiple elements)

Folds are getters that can traverse more than one element (or no elements at all). The only fold here which isn't simultaneously a Traversal is folded (traversals are folds that also can modify elements they're traversing).

You can apply folds to values by using operators like (^..), (^?), etc:

>>> (1,2) ^.. both
[1,2]

A nice thing about folds is that you can combine them with (<>) to concatenate their outputs:

>>> (1,2,3) ^.. (_2 <> _1)  -- in reversed order because why not
[2,1]

You can build more complicated getters with it when each would be unhelpful:

>>> ([1,2], 3, [Nothing, Just 4]) ^.. (_1.each <> _2 <> _3.each._Just)
[1,2,3,4]

It plays nicely with (^?), too:

>>> [0..9] ^? (ix 9 <> ix 5)
Just 9
>>> [0..8] ^? (ix 9 <> ix 5)
Just 5
>>> [0..3] ^? (ix 9 <> ix 5)
Nothing

(Unfortunately, this trick won't help you with setting or modifying.)

(^..) :: 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]

(^?) :: s -> Getting (First a) s a -> Maybe a infixl 8 Source

s ^? t returns the 1st element t returns, or Nothing if t doesn't return anything. It's trivially implemented by passing the First monoid to the getter.

Safe head:

>>> [] ^? each
Nothing
>>> [1..3] ^? each
Just 1

Converting Either to Maybe:

>>> Left 1 ^? _Right
Nothing
>>> Right 1 ^? _Right
Just 1

A non-operator version of (^?) is called preview, and – like view – it's not included in this package because it's more general and requires a mtl dependency). As with view, you can get it from microlens-mtl.

(^?!) :: s -> Getting (Endo a) s a -> a infixl 8 Source

(^?!) is an unsafe variant of (^?) – instead of using Nothing to indicate that there were no elements returned, it throws an exception.

folded :: (Foldable f, Applicative (Const r)) => Getting r (f a) a Source

folded is a fold for anything Foldable. In a way, it's an opposite of mapped – the most powerful getter, but can't be used as a setter.

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 (setters and getters at once)

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 structure
  • b is the type of the replaced value
  • s is the type of the whole structure
  • t is the type of the structure after replacing a in it with b

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. For instance, here we define a lens for the 1st element of a list, but instead of a legitimate getter we use undefined. Then we use the resulting lens for setting and it works, which proves that the getter wasn't used:

>>> [1,2,3] & lens undefined (\s b -> b : tail s) .~ 10
[10,2,3]

at :: At m => Index m -> Lens' m (Maybe (IxValue m)) Source

This lens lets you read, write, or delete elements in Map-like structures. It returns Nothing when the value isn't found, just like lookup:

Data.Map.lookup k m = m ^. at k

However, it also lets you insert and delete values by setting the value to Just value or Nothing:

Data.Map.insert k a m = m & at k .~ Just a

Data.Map.delete k m = m & at k .~ Nothing

at doesn't work for arrays, because you can't delete an arbitrary element from an array.

If you want to modify an already existing value, you should use ix instead because then you won't have to deal with Maybe (ix is available for all types that have at).

Note that at isn't strict for Map, even if you're using Data.Map.Strict:

>>> Data.Map.Strict.size (Data.Map.Strict.empty & at 1 .~ Just undefined)
1

The reason for such behavior is that there's actually no “strict Map” type; Data.Map.Strict just provides some strict functions for ordinary Maps.

This package doesn't actually provide any instances for at, but you can import Lens.Micro.GHC from the microlens-ghc package and get instances for Map and IntMap.

_1 :: Field1 s t a b => Lens s t a b Source

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).

_2, _3, _4, and _5 are also available (see below).

_2 :: Field2 s t a b => Lens s t a b Source

_3 :: Field3 s t a b => Lens s t a b Source

_4 :: Field4 s t a b => Lens s t a b Source

_5 :: Field5 s t a b => Lens s t a b Source

Traversals (lenses iterating over several elements)

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 (^..) to get all values, (^?) to get the 1st value, (.~) to set values, (%~) to modify them. (.) composes traversals just as it composes lenses. (^.) can be used with traversals as well, but don't confuse it with (^..).

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 (or Nothing 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).

failing :: Traversal s t a b -> Traversal s t a b -> Traversal s t a b infixl 5 Source

failing lets you chain traversals together; if the 1st traversal fails, the 2nd traversal will be used.

>>> ([1,2],[3]) & failing (_1.each) (_2.each) .~ 0
([0,0],[3])
>>> ([],[3]) & failing (_1.each) (_2.each) .~ 0
([],[0])

Note that the resulting traversal won't be valid unless either both traversals don't touch each others' elements, or both traversals return exactly the same results. To see an example of how failing can generate invalid traversals, see this Stackoverflow question.

both :: Traversal (a, a) (b, b) a b Source

both traverses both fields of a tuple. Unlike both from lens, it only works for pairs – not for triples or Either.

>>> ("str","ing") ^. both
"string"
>>> ("str","ing") & both %~ reverse
("rts","gni")

traversed :: Traversable f => Traversal (f a) (f b) a b Source

traversed traverses any Traversable container (list, vector, Map, Maybe, you name it):

>>> Just 1 ^.. traversed
[1]

traversed is the same as traverse, but can be faster thanks to magic rewrite rules.

each :: Each s t a b => Traversal s t a b Source

each tries to be a universal Traversal – it behaves like traversed in most situations, but also adds support for e.g. tuples with same-typed values:

>>> (1,2) & each %~ succ
(2,3)
>>> ["x", "y", "z"] ^. each
"xyz"

However, note that each doesn't work on every instance of Traversable. If you have a Traversable which isn't supported by each, you can use traversed instead. Personally, I like using each instead of traversed whenever possible – it's shorter and more descriptive.

You can use each with these things:

each :: Traversal [a] [b] a b

each :: Traversal (Maybe a) (Maybe b) a b

each :: Traversal (a,a) (b,b) a b
each :: Traversal (a,a,a) (b,b,b) a b
each :: Traversal (a,a,a,a) (b,b,b,b) a b
each :: Traversal (a,a,a,a,a) (b,b,b,b,b) a b

each :: (RealFloat a, RealFloat b) => Traversal (Complex a) (Complex b) a b

Additionally, you can use each with types from array, bytestring, and containers by importing Lens.Micro.GHC from the microlens-ghc package.

ix :: Ixed m => Index m -> Traversal' m (IxValue m) Source

This traversal lets you access (and update) an arbitrary element in a list, array, Map, etc. (If you want to insert or delete elements as well, look at at.)

An example for lists:

>>> [0..5] & ix 3 .~ 10
[0,1,2,10,4,5]

You can use it for getting, too:

>>> [0..5] ^? ix 3
Just 3

Of course, the element may not be present (which means that you can use ix as a safe variant of (!!)):

>>> [0..5] ^? ix 10
Nothing

Another useful instance is the one for functions – it lets you modify their outputs for specific inputs. For instance, here's maximum that returns 0 when the list is empty (instead of throwing an exception):

maximum0 = maximum & ix [] .~ 0

The following instances are provided in this package:

ix :: Int -> Traversal' [a] a

ix :: (Eq e) => e -> Traversal' (e -> a) a

Additionally, you can use ix with types from array, bytestring, and containers by importing Lens.Micro.GHC from the microlens-ghc package.

_head :: Cons s s a a => Traversal' s a Source

_head traverses the 1st element of something (usually a list, but can also be a Seq, etc):

>>> [1..5] ^? _head
Just 1

It can be used to modify too, as in this example where the 1st letter of a sentence is capitalised:

>>> "mary had a little lamb." & _head %~ toTitle
"Mary had a little lamb."

The reason it's a traversal and not a lens is that there's nothing to traverse when the list is empty:

>>> [] ^? _head
Nothing

This package only lets you use _head on lists, but you can import Lens.Micro.GHC from the microlens-ghc package and get instances for ByteString and Seq.

_tail :: Cons s s a a => Traversal' s s Source

_tail gives you access to the tail of a list (or Seq, etc):

>>> [1..5] ^? _tail
Just [2,3,4,5]

You can modify the tail as well:

>>> [4,1,2,3] & _tail %~ reverse
[4,3,2,1]

Since lists are monoids, you can use _tail with plain (^.) (and then it'll return an empty list if you give it an empty list):

>>> [1..5] ^. _tail
[2,3,4,5]
>>> [] ^. _tail
[]

If you want to traverse each element of the tail, use _tail with each:

>>> "I HATE CAPS." & _tail.each %~ toLower
"I hate caps."

This package only lets you use _tail on lists, but you can import Lens.Micro.GHC from the microlens-ghc package and get instances for ByteString and Seq.

_init :: Snoc s s a a => Traversal' s s Source

_init gives you access to all-but-the-last elements of the list:

>>> "Hello." ^. _init
"Hello"

See documentation for _tail, as _init and _tail are pretty similar.

_last :: Snoc s s a a => Traversal' s a Source

_last gives you access to the last element of the list:

>>> "Hello." ^? _last
'.'

See documentation for _head, as _last and _head are pretty similar.

Prisms (traversals iterating over at most 1 element)

Prisms are traversals that 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 Lefts in a structure (like the lefts function, but not necessarily just for lists):

>>> [Left 1, Right 'c', Left 3] ^.. each._Just
[1,3]

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 Lefts:

>>> (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)

_Right :: Traversal (Either a b) (Either a b') b b' Source

_Right targets the value contained in an Either, provided it's a Right.

See documentation for _Left.

_Just :: Traversal (Maybe a) (Maybe a') a a' Source

_Just targets the value contained in a Maybe, provided it's a Just.

See documentation for _Left (as these 2 are pretty similar). In particular, it can be used to write these:

_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 has _Nothing as a replacement for isNothing), and provided mainly for consistency.

Implementation:

_Nothing f Nothing = const Nothing <$> f ()
_Nothing _ j       = pure j

Other types

type LensLike f s t a b = (a -> f b) -> s -> f t Source

LensLike is a type that is often used to make combinators as general as possible. For instance, take (<<%~), which only requires the passed lens to be able to work with the (,) a functor (lenses and traversals can do that). The fully expanded type is as follows:

(<<%~) :: ((a -> (a, b)) -> s -> (a, t)) -> (a -> b) -> s -> (a, t)

With LensLike, the intent to use the (,) a functor can be made a bit clearer:

(<<%~) :: LensLike ((,) a) s t a b -> (a -> b) -> s -> (a, t)

type LensLike' f s a = LensLike f s s a a Source

A type alias for monomorphic LensLikes.