Portability | Rank2Types |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Safe-Infered |
A
is a generalization of Setter
a b c dfmap
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 ::
we monomorphize the type to obtain Functor
f => (c -> d) -> f c -> f d(c -> d) -> a -> b
and then decorate it with Identity
to obtain
typeSetter
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 (<$
).
- type Setter a b c d = forall f. Settable f => (c -> f d) -> a -> f b
- class Applicative f => Settable f where
- untainted :: f a -> a
- sets :: ((c -> d) -> a -> b) -> Setter a b c d
- mapped :: Functor f => Setter (f a) (f b) a b
- adjust :: Setting a b c d -> (c -> d) -> a -> b
- mapOf :: Setting a b c d -> (c -> d) -> a -> b
- set :: Setting a b c d -> d -> a -> b
- (.~) :: Setting a b c d -> d -> a -> b
- (%~) :: Setting a b c d -> (c -> d) -> a -> b
- (+~) :: Num c => Setting a b c c -> c -> a -> b
- (-~) :: Num c => Setting a b c c -> c -> a -> b
- (*~) :: Num c => Setting a b c c -> c -> a -> b
- (//~) :: Fractional c => Setting a b c c -> c -> a -> b
- (^~) :: (Num c, Integral e) => Setting a b c c -> e -> a -> b
- (^^~) :: (Fractional c, Integral e) => Setting a b c c -> e -> a -> b
- (**~) :: Floating c => Setting a b c c -> c -> a -> b
- (||~) :: Setting a b Bool Bool -> Bool -> a -> b
- (&&~) :: Setting a b Bool Bool -> Bool -> a -> b
- (<>~) :: Monoid c => Setting a b c c -> c -> a -> b
- (<.~) :: Setting a b c d -> d -> a -> (d, b)
- (.=) :: MonadState a m => Setting a a c d -> d -> m ()
- (%=) :: MonadState a m => Setting a a c d -> (c -> d) -> m ()
- (+=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m ()
- (-=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m ()
- (*=) :: (MonadState a m, Num b) => SimpleSetting a b -> b -> m ()
- (//=) :: (MonadState a m, Fractional b) => SimpleSetting a b -> b -> m ()
- (^=) :: (MonadState a m, Fractional b, Integral c) => SimpleSetting a b -> c -> m ()
- (^^=) :: (MonadState a m, Fractional b, Integral c) => SimpleSetting a b -> c -> m ()
- (**=) :: (MonadState a m, Floating b) => SimpleSetting a b -> b -> m ()
- (||=) :: MonadState a m => SimpleSetting a Bool -> Bool -> m ()
- (&&=) :: MonadState a m => SimpleSetting a Bool -> Bool -> m ()
- (<>=) :: (MonadState a m, Monoid b) => SimpleSetting a b -> b -> m ()
- (<.=) :: MonadState a m => Setting a a c d -> d -> m d
- (<~) :: MonadState a m => Setting a a c d -> m d -> m ()
- type Setting a b c d = (c -> Mutator d) -> a -> Mutator b
- newtype Mutator a = Mutator {
- runMutator :: a
- type SimpleSetting a b = Setting a a b b
- type SimpleSetter a b = Setter a a b b
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
:
adjust
l id = idadjust
l f .adjust
l g =adjust
l (f . g)
These an be stated more directly:
lpure
=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.
class Applicative f => Settable f whereSource
Building Setters
Common Setters
Functional Combinators
adjust :: 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
=adjust
mapped
fmapDefault
=adjust
traverse
sets
.adjust
=id
adjust
.sets
=id
Another way to view adjust
is to say that it transformers a Setter
into a
"semantic editor combinator".
adjust
::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 adjust that is provided for consistency.
mapOf
=adjust
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 adjust
fmap
f =mapped
%~
ffmapDefault
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
(^^~) :: (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 Data.Pair.Lens
>>>
both ||~ True $ (False,True)
(True,True)
>>>
both ||~ False $ (False,True)
(False,True)
(||~)::Setter
a bBool
Bool
->Bool
-> a -> b (||~)::Iso
a bBool
Bool
->Bool
-> a -> b (||~)::Lens
a bBool
Bool
->Bool
-> a -> b (||~)::Traversal
a bBool
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 Data.Pair.Lens
>>>
both &&~ True $ (False, True)
(False,True)
>>>
both &&~ False $ (False, True)
(False,False)
(&&~)::Setter
a bBool
Bool
->Bool
-> a -> b (&&~)::Iso
a bBool
Bool
->Bool
-> a -> b (&&~)::Lens
a bBool
Bool
->Bool
-> a -> b (&&~)::Traversal
a bBool
Bool
->Bool
-> a -> b
(<>~) :: Monoid c => Setting a b c c -> c -> a -> bSource
Modify the target of a monoidally valued by mappend
ing another value.
>>>
:m + Control.Lens Data.Pair.Lens
>>>
both <>~ "!!!" $ ("hello","world")
("hello!!!","world!!!")
(~) ::Monoid
c =>Setter
a b c c -> c -> a -> b (~) ::Monoid
c =>Iso
a b c c -> c -> a -> b (~) ::Monoid
c =>Lens
a b c c -> c -> a -> b (~) ::Monoid
c =>Traversal
a b c c -> c -> 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 ()
(%=) :: 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 = doid
+=
1use
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
aBool
->Bool
-> m () (||=)::MonadState
a m =>Simple
Iso
aBool
->Bool
-> m () (||=)::MonadState
a m =>Simple
Lens
aBool
->Bool
-> m () (||=)::MonadState
a m =>Simple
Traversal
aBool
->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
aBool
->Bool
-> m () (&&=)::MonadState
a m =>Simple
Iso
aBool
->Bool
-> m () (&&=)::MonadState
a m =>Simple
Lens
aBool
->Bool
-> m () (&&=)::MonadState
a m =>Simple
Traversal
aBool
->Bool
-> m ()
(<>=) :: (MonadState a m, Monoid b) => SimpleSetting a b -> b -> m ()Source
Modify the target(s) of a Simple
Lens
, Iso
, Setter
or Traversal
by mappend
ing a value.
(=) :: (MonadState
a m,Monoid
b) =>Simple
Setter
a b -> b -> m () (=) :: (MonadState
a m,Monoid
b) =>Simple
Iso
a b -> b -> m () (=) :: (MonadState
a m,Monoid
b) =>Simple
Lens
a b -> b -> m () (=) :: (MonadState
a m,Monoid
b) =>Simple
Traversal
a b -> b -> 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 ...
Setter Internals
Mutator
is just a renamed Identity
functor to give better error
messages when someone attempts to use a getter as a setter.
Most user code will never need to see this type.
Mutator | |
|
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.
typeSimpleSetting
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
typeSimpleSetter
=Simple
Setter