| Portability | Rank2Types |
|---|---|
| Stability | provisional |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Safe Haskell | None |
Control.Lens.Setter
Contents
Description
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
typeSettera b c d = (c ->Identityd) -> a ->Identityb
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
- sets :: ((c -> d) -> a -> b) -> Setter a b c d
- mapped :: Functor f => Setter (f a) (f b) a b
- over :: 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
- (<.~) :: Setting a b c d -> d -> a -> (d, b)
- assign :: MonadState a m => Setting a a c d -> d -> m ()
- (.=) :: 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 => Setting a a c d -> d -> m d
- (<~) :: MonadState a m => Setting a a c d -> m d -> m ()
- newtype ReifiedSetter a b c d = ReifySetter {
- reflectSetter :: Setter a b c d
- type Setting a b c d = (c -> Mutator d) -> a -> Mutator b
- type SimpleSetting a b = Setting a a b b
- type SimpleSetter a b = Setter a a b b
- type SimpleReifiedSetter a b = ReifiedSetter 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
setl c (setl b a) ≡setl 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:
overlid≡idoverl f.overl g ≡overl (f.g)
These an be stated more directly:
lpure≡purel 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
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≡overmappedfmapDefault≡overtraverse(<$) ≡setmapped
>>>import Control.Lens>>>over mapped (+1) [1,2,3][2,3,4]
>>>set mapped () [1,2,3][(),(),()]
>>>mapped.mapped %~ (+1) $ [[1,2],[3]][[2,3],[4]]
>>>over (mapped._2) length [("hello","world"),("leaders","!!!")][("hello",5),("leaders",3)]
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≡overmappedfmapDefault≡overtraversesets.over≡idover.sets≡id
>>>import Control.Lens>>>over mapped (*10) [1,2,3][10,20,30]
>>>over _1 show (10,20)("10",20)
Another way to view over is to say that it transformers a Setter into a
"semantic editor combinator".
over::Settera 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≡overfmap≡mapOfmappedfmapDefault≡mapOftraversesets.mapOf≡idmapOf.sets≡id
>>>import Control.Lens>>>mapOf mapped (+1) [1,2,3,4][2,3,4,5]
>>>mapOf _1 (+1) (1,2)(2,2)
>>>mapOf both (+1) (1,2)(2,3)
mapOf::Settera b c d -> (c -> d) -> a -> bmapOf::Isoa b c d -> (c -> d) -> a -> bmapOf::Lensa b c d -> (c -> d) -> a -> bmapOf::Traversala 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.
(<$) ≡setmapped
>>>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::Settera b c d -> d -> a -> bset::Isoa b c d -> d -> a -> bset::Lensa b c d -> d -> a -> bset::Traversala 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")
(.~) ::Settera b c d -> d -> a -> b (.~) ::Isoa b c d -> d -> a -> b (.~) ::Lensa b c d -> d -> a -> b (.~) ::Traversala 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
fmapf ≡mapped%~ffmapDefaultf ≡traverse%~f
>>>import Control.Lens>>>_2 %~ length $ (1,"hello")(1,5)
>>>traverse %~ (+1) $ [1,2,3][2,3,4]
>>>_2 %~ (+1) $ (3,4)(3,5)
>>>traverse.traverse %~ length $ [["hello","world"],["!!!"]][[5,5],[3]]
(%~) ::Settera b c d -> (c -> d) -> a -> b (%~) ::Isoa b c d -> (c -> d) -> a -> b (%~) ::Lensa b c d -> (c -> d) -> a -> b (%~) ::Traversala 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)
>>>both +~ 2 $ (5,6)(7,8)
(+~) :: Num b =>SimpleSettera b -> b -> a -> a (+~) :: Num b =>SimpleIsoa b -> b -> a -> a (+~) :: Num b =>SimpleLensa b -> b -> a -> a (+~) :: Num b =>SimpleTraversala b -> b -> a -> a
(-~) :: 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)
>>>mapped.mapped -~ 1 $ [[4,5],[6,7]][[3,4],[5,6]]
(-~) ::Numb =>SimpleSettera b -> b -> a -> a (-~) ::Numb =>SimpleIsoa b -> b -> a -> a (-~) ::Numb =>SimpleLensa b -> b -> a -> a (-~) ::Numb =>SimpleTraversala b -> b -> a -> a
(*~) :: 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)
>>>mapped *~ 2 $ Just 24Just 48
(*~) ::Numb =>SimpleSettera b -> b -> a -> a (*~) ::Numb =>SimpleIsoa b -> b -> a -> a (*~) ::Numb =>SimpleLensa b -> b -> a -> a (*~) ::Numb =>SimpleTraversala b -> b -> a -> a
(//~) :: Fractional c => Setting a b c c -> c -> a -> bSource
Divide the target(s) of a numerically valued Lens, Iso, Setter or Traversal
>>>import Control.Lens>>>_2 //~ 2 $ ("Hawaii",10)("Hawaii",5.0)
(//~) ::Fractionalb =>SimpleSettera b -> b -> a -> a (//~) ::Fractionalb =>SimpleIsoa b -> b -> a -> a (//~) ::Fractionalb =>SimpleLensa b -> b -> a -> a (//~) ::Fractionalb =>SimpleTraversala b -> b -> a -> a
(^~) :: (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)
(^~) :: (Numb,Integralc) =>SimpleSettera b -> c -> a -> a (^~) :: (Numb,Integralc) =>SimpleIsoa b -> c -> a -> a (^~) :: (Numb,Integralc) =>SimpleLensa b -> c -> a -> a (^~) :: (Numb,Integralc) =>SimpleTraversala b -> c -> a -> a
(^^~) :: (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)
(^^~) :: (Fractionalb,Integralc) =>SimpleSettera b -> c -> a -> a (^^~) :: (Fractionalb,Integralc) =>SimpleIsoa b -> c -> a -> a (^^~) :: (Fractionalb,Integralc) =>SimpleLensa b -> c -> a -> a (^^~) :: (Fractionalb,Integralc) =>SimpleTraversala b -> c -> a -> a
(**~) :: 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)
(**~) ::Floatingb =>SimpleSettera b -> b -> a -> a (**~) ::Floatingb =>SimpleIsoa b -> b -> a -> a (**~) ::Floatingb =>SimpleLensa b -> b -> a -> a (**~) ::Floatingb =>SimpleTraversala b -> b -> a -> a
(||~) :: Setting a b Bool Bool -> Bool -> a -> bSource
Logically || the target(s) of a Bool-valued Lens or Setter
>>>import Control.Lens>>>both ||~ True $ (False,True)(True,True)
>>>both ||~ False $ (False,True)(False,True)
(||~) ::SimpleSetteraBool->Bool-> a -> a (||~) ::SimpleIsoaBool->Bool-> a -> a (||~) ::SimpleLensaBool->Bool-> a -> a (||~) ::SimpleTraversalaBool->Bool-> a -> a
(&&~) :: Setting a b Bool Bool -> Bool -> a -> bSource
Logically && the target(s) of a Bool-valued Lens or Setter
>>>import Control.Lens>>>both &&~ True $ (False, True)(False,True)
>>>both &&~ False $ (False, True)(False,False)
(&&~) ::SimpleSetteraBool->Bool-> a -> a (&&~) ::SimpleIsoaBool->Bool-> a -> a (&&~) ::SimpleLensaBool->Bool-> a -> a (&&~) ::SimpleTraversalaBool->Bool-> a -> a
(<.~) :: 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 directly is a good idea.
.~ d
>>>import Control.Lens>>>_3 <.~ "world" $ ("good","morning","vietnam")("world",("good","morning","world"))
>>>import Data.Map as Map>>>_2.at "hello" <.~ Just "world" $ (42,Map.fromList [("goodnight","gracie")])(Just "world",(42,fromList [("goodnight","gracie"),("hello","world")]))
(<.~) ::Settera b c d -> d -> a -> (d, b) (<.~) ::Isoa b c d -> d -> a -> (d, b) (<.~) ::Lensa b c d -> d -> a -> (d, b) (<.~) ::Traversala b c d -> d -> a -> (d, b)
State Combinators
assign :: 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.
This is an alias for (.=).
assign::MonadStatea m =>SimpleIsoa b -> b -> m ()assign::MonadStatea m =>SimpleLensa b -> b -> m ()assign::MonadStatea m =>SimpleTraversala b -> b -> m ()assign::MonadStatea m =>SimpleSettera b -> b -> m ()
(.=) :: 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.
This is an infix version of assign.
(.=) ::MonadStatea m =>SimpleIsoa b -> b -> m () (.=) ::MonadStatea m =>SimpleLensa b -> b -> m () (.=) ::MonadStatea m =>SimpleTraversala b -> b -> m () (.=) ::MonadStatea m =>SimpleSettera b -> b -> 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.
(%=) ::MonadStatea m =>SimpleIsoa b -> (b -> b) -> m () (%=) ::MonadStatea m =>SimpleLensa b -> (b -> b) -> m () (%=) ::MonadStatea m =>SimpleTraversala b -> (b -> b) -> m () (%=) ::MonadStatea m =>SimpleSettera b -> (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 adding a value
Example:
fresh :: MonadState Int m => m Int fresh = doid+=1useid
(+=) :: (MonadStatea m,Numb) =>SimpleSettera b -> b -> m () (+=) :: (MonadStatea m,Numb) =>SimpleIsoa b -> b -> m () (+=) :: (MonadStatea m,Numb) =>SimpleLensa b -> b -> m () (+=) :: (MonadStatea m,Numb) =>SimpleTraversala 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
(-=) :: (MonadStatea m,Numb) =>SimpleSettera b -> b -> m () (-=) :: (MonadStatea m,Numb) =>SimpleIsoa b -> b -> m () (-=) :: (MonadStatea m,Numb) =>SimpleLensa b -> b -> m () (-=) :: (MonadStatea m,Numb) =>SimpleTraversala 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.
(*=) :: (MonadStatea m,Numb) =>SimpleSettera b -> b -> m () (*=) :: (MonadStatea m,Numb) =>SimpleIsoa b -> b -> m () (*=) :: (MonadStatea m,Numb) =>SimpleLensa b -> b -> m () (*=) :: (MonadStatea m,Numb) =>SimpleTraversala 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.
(//=) :: (MonadStatea m,Fractionalb) =>SimpleSettera b -> b -> m () (//=) :: (MonadStatea m,Fractionalb) =>SimpleIsoa b -> b -> m () (//=) :: (MonadStatea m,Fractionalb) =>SimpleLensa b -> b -> m () (//=) :: (MonadStatea m,Fractionalb) =>SimpleTraversala 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.
(^=) :: (MonadStatea m,Fractionalb,Integralc) =>SimpleSettera b -> c -> m () (^=) :: (MonadStatea m,Fractionalb,Integralc) =>SimpleIsoa b -> c -> m () (^=) :: (MonadStatea m,Fractionalb,Integralc) =>SimpleLensa b -> c -> m () (^=) :: (MonadStatea m,Fractionalb,Integralc) =>SimpleTraversala 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.
(^^=) :: (MonadStatea m,Fractionalb,Integralc) =>SimpleSettera b -> c -> m () (^^=) :: (MonadStatea m,Fractionalb,Integralc) =>SimpleIsoa b -> c -> m () (^^=) :: (MonadStatea m,Fractionalb,Integralc) =>SimpleLensa b -> c -> m () (^^=) :: (MonadStatea m,Fractionalb,Integralc) =>SimpleTraversala 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
(**=) :: (MonadStatea m,Floatingb) =>SimpleSettera b -> b -> m () (**=) :: (MonadStatea m,Floatingb) =>SimpleIsoa b -> b -> m () (**=) :: (MonadStatea m,Floatingb) =>SimpleLensa b -> b -> m () (**=) :: (MonadStatea m,Floatingb) =>SimpleTraversala 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
(||=) ::MonadStatea m =>SimpleSetteraBool->Bool-> m () (||=) ::MonadStatea m =>SimpleIsoaBool->Bool-> m () (||=) ::MonadStatea m =>SimpleLensaBool->Bool-> m () (||=) ::MonadStatea m =>SimpleTraversalaBool->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
(&&=) ::MonadStatea m =>SimpleSetteraBool->Bool-> m () (&&=) ::MonadStatea m =>SimpleIsoaBool->Bool-> m () (&&=) ::MonadStatea m =>SimpleLensaBool->Bool-> m () (&&=) ::MonadStatea m =>SimpleTraversalaBool->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_wallIf you do not need a copy of the intermediate result, then using l .= d will avoid unused binding warnings
(<.=) ::MonadStatea m =>Settera a c d -> d -> m d (<.=) ::MonadStatea m =>Isoa a c d -> d -> m d (<.=) ::MonadStatea m =>Lensa a c d -> d -> m d (<.=) ::MonadStatea m =>Traversala 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.
(<~) ::MonadStatea m =>Isoa a c d -> m d -> m () (<~) ::MonadStatea m =>Lensa a c d -> m d -> m () (<~) ::MonadStatea m =>Traversala a c d -> m d -> m () (<~) ::MonadStatea m =>Settera 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
...
Storing Setters
newtype ReifiedSetter a b c d Source
Reify a setter so it can be stored safely in a container.
Constructors
| ReifySetter | |
Fields
| |
Setter Internals
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.
typeSimpleSettingm =SimpleSetting
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.
setsData.Text.map ::SimpleSetterTextChar
typeSimpleSetter=SimpleSetter
type SimpleReifiedSetter a b = ReifiedSetter a a b bSource