lens-2.5: Lenses, Folds and Traversals

PortabilityRank2Types
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellSafe-Infered

Control.Lens.Setter

Contents

Description

A Setter a b c d is a generalization of fmap from Functor. It allows you to map into a structure and change out the contents, but it isn't strong enough to allow you to enumerate those contents. Starting with fmap :: Functor f => (c -> d) -> f c -> f d we monomorphize the type to obtain (c -> d) -> a -> b and then decorate it with Identity to obtain

type Setter a b c d = (c -> Identity d) -> a -> Identity b

Every Traversal is a valid Setter, since Identity is Applicative.

Everything you can do with a Functor, you can do with a Setter. There are combinators that generalize fmap and (<$).

Synopsis

Setters

type Setter a b c d = forall f. Settable f => (c -> f d) -> a -> f bSource

The only Lens-like law that can apply to a Setter l is that

set l c (set l b a) = set l c a

You can't view a Setter in general, so the other two laws are irrelevant.

However, two Functor laws apply to a Setter:

 over l id = id
 over l f . over l g = over l (f . g)

These an be stated more directly:

 l pure = pure
 l f . untainted . l g = l (f . untainted . g)

You can compose a Setter with a Lens or a Traversal using (.) from the Prelude and the result is always only a Setter and nothing more.

Building Setters

sets :: ((c -> d) -> a -> b) -> Setter a b c dSource

Build a Setter from a map-like function.

Your supplied function f is required to satisfy:

 f id = id
 f g . f h = f (g . h)

Equational reasoning:

 sets . over = id
 over . sets = id

Another way to view sets is that it takes a "semantic editor combinator" and transforms it into a Setter.

Common Setters

mapped :: Functor f => Setter (f a) (f b) a bSource

This setter can be used to map over all of the values in a Functor.

 fmap = over mapped
 fmapDefault = over traverse
 (<$) = set mapped

Functional Combinators

over :: Setting a b c d -> (c -> d) -> a -> bSource

Modify the target of a Lens or all the targets of a Setter or Traversal with a function.

 fmap = over mapped
 fmapDefault = over traverse
 sets . over = id
 over . sets = id

Another way to view over is to say that it transformers a Setter into a "semantic editor combinator".

over :: Setter a b c d -> (c -> d) -> a -> b

mapOf :: Setting a b c d -> (c -> d) -> a -> bSource

Modify the target of a Lens or all the targets of a Setter or Traversal with a function. This is an alias for over that is provided for consistency.

 mapOf = over
 fmap = mapOf mapped
 fmapDefault = mapOf traverse
 sets . mapOf = id
 mapOf . sets = id
 mapOf :: Setter a b c d      -> (c -> d) -> a -> b
 mapOf :: Iso a b c d         -> (c -> d) -> a -> b
 mapOf :: Lens a b c d        -> (c -> d) -> a -> b
 mapOf :: Traversal a b c d   -> (c -> d) -> a -> b

set :: Setting a b c d -> d -> a -> bSource

Replace the target of a Lens or all of the targets of a Setter or Traversal with a constant value.

(<$) = set mapped
>>> import Control.Lens
>>> set _2 "hello" (1,())
(1,"hello")
>>> set mapped () [1,2,3,4]
[(),(),(),()]

Note: Attempting to set a Fold or Getter will fail at compile time with an relatively nice error message.

 set :: Setter a b c d    -> d -> a -> b
 set :: Iso a b c d       -> d -> a -> b
 set :: Lens a b c d      -> d -> a -> b
 set :: Traversal a b c d -> d -> a -> b

(.~) :: Setting a b c d -> d -> a -> bSource

Replace the target of a Lens or all of the targets of a Setter or Traversal with a constant value.

This is an infix version of set, provided for consistency with (.=)

f <$ a = mapped .~ f $ a
>>> import Control.Lens
>>> _1 .~ "hello" $ (42,"world")
("hello","world")
 (.~) :: Setter a b c d    -> d -> a -> b
 (.~) :: Iso a b c d       -> d -> a -> b
 (.~) :: Lens a b c d      -> d -> a -> b
 (.~) :: Traversal a b c d -> d -> a -> b

(%~) :: Setting a b c d -> (c -> d) -> a -> bSource

Modifies the target of a Lens or all of the targets of a Setter or Traversal with a user supplied function.

This is an infix version of over

 fmap f = mapped %~ f
 fmapDefault f = traverse %~ f
>>> import Control.Lens
>>> _2 %~ length $ (1,"hello")
(1,5)
 (%~) :: Setter a b c d    -> (c -> d) -> a -> b
 (%~) :: Iso a b c d       -> (c -> d) -> a -> b
 (%~) :: Lens a b c d      -> (c -> d) -> a -> b
 (%~) :: Traversal a b c d -> (c -> d) -> a -> b

(+~) :: Num c => Setting a b c c -> c -> a -> bSource

Increment the target(s) of a numerically valued Lens, Setter or Traversal

>>> import Control.Lens
>>> _1 +~ 1 $ (1,2)
(2,2)
 (+~) :: Num c => Setter a b c c -> c -> a -> b
 (+~) :: Num c => Iso a b c c -> c -> a -> b
 (+~) :: Num c => Lens a b c c -> c -> a -> b
 (+~) :: Num c => Traversal a b c c -> c -> a -> b

(-~) :: Num c => Setting a b c c -> c -> a -> bSource

Decrement the target(s) of a numerically valued Lens, Iso, Setter or Traversal

>>> import Control.Lens
>>> _1 -~ 2 $ (1,2)
(-1,2)
 (-~) :: Num c => Setter a b c c -> c -> a -> b
 (-~) :: Num c => Iso a b c c -> c -> a -> b
 (-~) :: Num c => Lens a b c c -> c -> a -> b
 (-~) :: Num c => Traversal a b c c -> c -> a -> b

(*~) :: Num c => Setting a b c c -> c -> a -> bSource

Multiply the target(s) of a numerically valued Lens, Iso, Setter or Traversal

>>> import Control.Lens
>>> _2 *~ 4 $ (1,2)
(1,8)
 (*~) :: Num c => Setter a b c c -> c -> a -> b
 (*~) :: Num c => Iso a b c c -> c -> a -> b
 (*~) :: Num c => Lens a b c c -> c -> a -> b
 (*~) :: Num c => Traversal a b c c -> c -> a -> b

(//~) :: Fractional c => Setting a b c c -> c -> a -> bSource

Divide the target(s) of a numerically valued Lens, Iso, Setter or Traversal

 (\/\/~) :: Fractional c => Setter a b c c -> c -> a -> b
 (\/\/~) :: Fractional c => Iso a b c c -> c -> a -> b
 (\/\/~) :: Fractional c => Lens a b c c -> c -> a -> b
 (\/\/~) :: Fractional c => Traversal a b c c -> c -> a -> b

(^~) :: (Num c, Integral e) => Setting a b c c -> e -> a -> bSource

Raise the target(s) of a numerically valued Lens, Setter or Traversal to a non-negative integral power

>>> import Control.Lens
>>> _2 ^~ 2 $ (1,3)
(1,9)

(^^~) :: (Fractional c, Integral e) => Setting a b c c -> e -> a -> bSource

Raise the target(s) of a fractionally valued Lens, Setter or Traversal to an integral power

>>> import Control.Lens
>>> _2 ^^~ (-1) $ (1,2)
(1,0.5)
 (^^~) :: (Fractional c, Integral e) => Setter a b c c -> e -> a -> b
 (^^~) :: (Fractional c, Integral e) => Iso a b c c -> e -> a -> b
 (^^~) :: (Fractional c, Integral e) => Lens a b c c -> e -> a -> b
 (^^~) :: (Fractional c, Integral e) => Traversal a b c c -> e -> a -> b

(**~) :: Floating c => Setting a b c c -> c -> a -> bSource

Raise the target(s) of a floating-point valued Lens, Setter or Traversal to an arbitrary power.

>>> import Control.Lens
>>> _2 **~ pi $ (1,3)
(1,31.54428070019754)
 (**~) :: Floating c => Setter a b c c -> c -> a -> b
 (**~) :: Floating c => Iso a b c c -> c -> a -> b
 (**~) :: Floating c => Lens a b c c -> c -> a -> b
 (**~) :: Floating c => Traversal a b c c -> c -> a -> b

(||~) :: Setting a b Bool Bool -> Bool -> a -> bSource

Logically || the target(s) of a Bool-valued Lens or Setter

>>> :m + Control.Lens
>>> both ||~ True $ (False,True)
(True,True)
>>> both ||~ False $ (False,True)
(False,True)
 (||~):: Setter a b Bool Bool -> Bool -> a -> b
 (||~):: Iso a b Bool Bool -> Bool -> a -> b
 (||~):: Lens a b Bool Bool -> Bool -> a -> b
 (||~):: Traversal a b Bool Bool -> Bool -> a -> b

(&&~) :: Setting a b Bool Bool -> Bool -> a -> bSource

Logically && the target(s) of a Bool-valued Lens or Setter

>>> :m + Control.Lens
>>> both &&~ True $ (False, True)
(False,True)
>>> both &&~ False $ (False, True)
(False,False)
 (&&~):: Setter a b Bool Bool -> Bool -> a -> b
 (&&~):: Iso a b Bool Bool -> Bool -> a -> b
 (&&~):: Lens a b Bool Bool -> Bool -> a -> b
 (&&~):: Traversal a b Bool Bool -> Bool -> a -> b

(<.~) :: Setting a b c d -> d -> a -> (d, b)Source

Set with pass-through

This is mostly present for consistency, but may be useful for for chaining assignments

If you do not need a copy of the intermediate result, then using l .~ d directly is a good idea.

 (\<.~) :: Setter a b c d    -> d -> a -> (d, b)
 (\<.~) :: Iso a b c d       -> d -> a -> (d, b)
 (\<.~) :: Lens a b c d      -> d -> a -> (d, b)
 (\<.~) :: Traversal a b c d -> d -> a -> (d, b)

State Combinators

(.=) :: MonadState a m => Setting a a c d -> d -> m ()Source

Replace the target of a Lens or all of the targets of a Setter or Traversal in our monadic state with a new value, irrespective of the old.

 (.=) :: MonadState a m => Iso a a c d             -> d -> m ()
 (.=) :: MonadState a m => Lens a a c d            -> d -> m ()
 (.=) :: MonadState a m => Traversal a a c d       -> d -> m ()
 (.=) :: MonadState a m => Setter a a c d          -> d -> m ()

It puts the state in the monad or it gets the hose again.

(%=) :: MonadState a m => Setting a a c d -> (c -> d) -> m ()Source

Map over the target of a Lens or all of the targets of a Setter or Traversal in our monadic state.

 (%=) :: MonadState a m => Iso a a c d             -> (c -> d) -> m ()
 (%=) :: MonadState a m => Lens a a c d            -> (c -> d) -> m ()
 (%=) :: MonadState a m => Traversal a a c d       -> (c -> d) -> m ()
 (%=) :: MonadState a m => Setter a a c d          -> (c -> d) -> m ()

(+=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m ()Source

Modify the target(s) of a Simple Lens, Iso, Setter or Traversal by adding a value

Example:

 fresh :: MonadState Int m => m Int
 fresh = do
   id += 1
   use id
 (+=) :: (MonadState a m, Num b) => Simple Setter a b -> b -> m ()
 (+=) :: (MonadState a m, Num b) => Simple Iso a b -> b -> m ()
 (+=) :: (MonadState a m, Num b) => Simple Lens a b -> b -> m ()
 (+=) :: (MonadState a m, Num b) => Simple Traversal a b -> b -> m ()

(-=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m ()Source

Modify the target(s) of a Simple Lens, Iso, Setter or Traversal by subtracting a value

 (-=) :: (MonadState a m, Num b) => Simple Setter a b -> b -> m ()
 (-=) :: (MonadState a m, Num b) => Simple Iso a b -> b -> m ()
 (-=) :: (MonadState a m, Num b) => Simple Lens a b -> b -> m ()
 (-=) :: (MonadState a m, Num b) => Simple Traversal a b -> b -> m ()

(*=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m ()Source

Modify the target(s) of a Simple Lens, Iso, Setter or Traversal by multiplying by value.

ballSpeed . both *= speedMultiplier
 (*=) :: (MonadState a m, Num b) => Simple Setter a b -> b -> m ()
 (*=) :: (MonadState a m, Num b) => Simple Iso a b -> b -> m ()
 (*=) :: (MonadState a m, Num b) => Simple Lens a b -> b -> m ()
 (*=) :: (MonadState a m, Num b) => Simple Traversal a b -> b -> m ()

(//=) :: (MonadState a m, Fractional b) => SimpleSetting a b -> b -> m ()Source

Modify the target(s) of a Simple Lens, Iso, Setter or Traversal by dividing by a value.

 (//=) :: (MonadState a m, Fractional b) => Simple Setter a b -> b -> m ()
 (//=) :: (MonadState a m, Fractional b) => Simple Iso a b -> b -> m ()
 (//=) :: (MonadState a m, Fractional b) => Simple Lens a b -> b -> m ()
 (//=) :: (MonadState a m, Fractional b) => Simple Traversal a b -> b -> m ()

(^=) :: (MonadState a m, Fractional b, Integral c) => SimpleSetting a b -> c -> m ()Source

Raise the target(s) of a numerically valued Lens, Setter or Traversal to a non-negative integral power.

 (^=) ::  (MonadState a m, Fractional b, Integral c) => Simple Setter a b -> c -> m ()
 (^=) ::  (MonadState a m, Fractional b, Integral c) => Simple Iso a b -> c -> m ()
 (^=) ::  (MonadState a m, Fractional b, Integral c) => Simple Lens a b -> c -> m ()
 (^=) ::  (MonadState a m, Fractional b, Integral c) => Simple Traversal a b -> c -> m ()

(^^=) :: (MonadState a m, Fractional b, Integral c) => SimpleSetting a b -> c -> m ()Source

Raise the target(s) of a numerically valued Lens, Setter or Traversal to an integral power.

 (^^=) ::  (MonadState a m, Fractional b, Integral c) => Simple Setter a b -> c -> m ()
 (^^=) ::  (MonadState a m, Fractional b, Integral c) => Simple Iso a b -> c -> m ()
 (^^=) ::  (MonadState a m, Fractional b, Integral c) => Simple Lens a b -> c -> m ()
 (^^=) ::  (MonadState a m, Fractional b, Integral c) => Simple Traversal a b -> c -> m ()

(**=) :: (MonadState a m, Floating b) => SimpleSetting a b -> b -> m ()Source

Raise the target(s) of a numerically valued Lens, Setter or Traversal to an arbitrary power

 (**=) ::  (MonadState a m, Floating b) => Simple Setter a b -> b -> m ()
 (**=) ::  (MonadState a m, Floating b) => Simple Iso a b -> b -> m ()
 (**=) ::  (MonadState a m, Floating b) => Simple Lens a b -> b -> m ()
 (**=) ::  (MonadState a m, Floating b) => Simple Traversal a b -> b -> m ()

(||=) :: MonadState a m => SimpleSetting a Bool -> Bool -> m ()Source

Modify the target(s) of a Simple Lens, 'Iso, Setter or Traversal by taking their logical || with a value

 (||=):: MonadState a m => Simple Setter a Bool -> Bool -> m ()
 (||=):: MonadState a m => Simple Iso a Bool -> Bool -> m ()
 (||=):: MonadState a m => Simple Lens a Bool -> Bool -> m ()
 (||=):: MonadState a m => Simple Traversal a Bool -> Bool -> m ()

(&&=) :: MonadState a m => SimpleSetting a Bool -> Bool -> m ()Source

Modify the target(s) of a Simple Lens, Iso, Setter or Traversal by taking their logical && with a value

 (&&=):: MonadState a m => Simple Setter a Bool -> Bool -> m ()
 (&&=):: MonadState a m => Simple Iso a Bool -> Bool -> m ()
 (&&=):: MonadState a m => Simple Lens a Bool -> Bool -> m ()
 (&&=):: MonadState a m => Simple Traversal a Bool -> Bool -> m ()

(<.=) :: MonadState a m => Setting a a c d -> d -> m dSource

Set with pass-through

This is useful for chaining assignment without round-tripping through your monad stack.

do x <- _2 <.= ninety_nine_bottles_of_beer_on_the_wall

If you do not need a copy of the intermediate result, then using l .= d will avoid unused binding warnings

 (\<.=) :: MonadState a m => Setter a a c d -> d -> m d
 (\<.=) :: MonadState a m => Iso a a c d -> d -> m d
 (\<.=) :: MonadState a m => Lens a a c d -> d -> m d
 (\<.=) :: MonadState a m => Traversal a a c d -> d -> m d

(<~) :: MonadState a m => Setting a a c d -> m d -> m ()Source

Run a monadic action, and set all of the targets of a Lens, Setter or Traversal to its result.

 (\<~) :: MonadState a m => Iso a a c d       -> m d -> m ()
 (\<~) :: MonadState a m => Lens a a c d      -> m d -> m ()
 (\<~) :: MonadState a m => Traversal a a c d -> m d -> m ()
 (\<~) :: MonadState a m => Setter a a c d    -> m d -> m ()

As a reasonable mnemonic, this lets you store the result of a monadic action in a lens rather than in a local variable.

 do foo <- bar
    ...

will store the result in a variable, while

 do foo <~ bar
    ...

will store the result in a Lens, Setter, or Traversal.

Storing Setters

newtype ReifiedSetter a b c d Source

Reify a setter so it can be stored safely in a container.

Constructors

ReifySetter 

Fields

reflectSetter :: Setter a b c d
 

Setter Internals

type Setting a b c d = (c -> Mutator d) -> a -> Mutator bSource

Running a Setter instantiates it to a concrete type.

When consuming a setter directly to perform a mapping, you can use this type, but most user code will not need to use this type.

By choosing Mutator rather than Identity, we get nicer error messages.

type SimpleSetting a b = Setting a a b bSource

This is a useful alias for use when consuming a SimpleSetter.

Most user code will never have to use this type.

type SimpleSetting m = Simple Setting

Simplicity

type SimpleSetter a b = Setter a a b bSource

A Simple Setter is just a Setter that doesn't change the types.

These are particularly common when talking about monomorphic containers. e.g.

sets Data.Text.map :: SimpleSetter Text Char
type SimpleSetter = Simple Setter