| Copyright | (C) 2012-16 Edward Kmett |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Stability | provisional |
| Portability | Rank2Types |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
Control.Lens.Setter
Contents
Description
A is a generalization of Setter s t a bfmap 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
we monomorphize the type to obtain fmap :: Functor f => (a -> b) -> f a -> f b(a -> b) -> s -> t and then decorate it with Identity to obtain:
typeSetters t a b = (a ->Identityb) -> s ->Identityt
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
- type Setter s t a b = forall f. Settable f => (a -> f b) -> s -> f t
- type Setter' s a = Setter s s a a
- type ASetter s t a b = (a -> Identity b) -> s -> Identity t
- type ASetter' s a = ASetter s s a a
- type Setting p s t a b = p a (Identity b) -> s -> Identity t
- type Setting' p s a = Setting p s s a a
- sets :: (Profunctor p, Profunctor q, Settable f) => (p a b -> q s t) -> Optical p q f s t a b
- cloneSetter :: ASetter s t a b -> Setter s t a b
- mapped :: Functor f => Setter (f a) (f b) a b
- lifted :: Monad m => Setter (m a) (m b) a b
- contramapped :: Functor f => Setter (f b) (f a) a b
- argument :: Profunctor p => Setter (p b r) (p a r) a b
- over :: ASetter s t a b -> (a -> b) -> s -> t
- set :: ASetter s t a b -> b -> s -> t
- (.~) :: ASetter s t a b -> b -> s -> t
- (%~) :: ASetter s t a b -> (a -> b) -> s -> t
- (+~) :: Num a => ASetter s t a a -> a -> s -> t
- (-~) :: Num a => ASetter s t a a -> a -> s -> t
- (*~) :: Num a => ASetter s t a a -> a -> s -> t
- (//~) :: Fractional a => ASetter s t a a -> a -> s -> t
- (^~) :: (Num a, Integral e) => ASetter s t a a -> e -> s -> t
- (^^~) :: (Fractional a, Integral e) => ASetter s t a a -> e -> s -> t
- (**~) :: Floating a => ASetter s t a a -> a -> s -> t
- (||~) :: ASetter s t Bool Bool -> Bool -> s -> t
- (<>~) :: Semigroup a => ASetter s t a a -> a -> s -> t
- (&&~) :: ASetter s t Bool Bool -> Bool -> s -> t
- (<.~) :: ASetter s t a b -> b -> s -> (b, t)
- (?~) :: ASetter s t a (Maybe b) -> b -> s -> t
- (<?~) :: ASetter s t a (Maybe b) -> b -> s -> (b, t)
- assign :: MonadState s m => ASetter s s a b -> b -> m ()
- modifying :: MonadState s m => ASetter s s a b -> (a -> b) -> m ()
- (.=) :: MonadState s m => ASetter s s a b -> b -> m ()
- (%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m ()
- (+=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m ()
- (-=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m ()
- (*=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m ()
- (//=) :: (MonadState s m, Fractional a) => ASetter' s a -> a -> m ()
- (^=) :: (MonadState s m, Num a, Integral e) => ASetter' s a -> e -> m ()
- (^^=) :: (MonadState s m, Fractional a, Integral e) => ASetter' s a -> e -> m ()
- (**=) :: (MonadState s m, Floating a) => ASetter' s a -> a -> m ()
- (||=) :: MonadState s m => ASetter' s Bool -> Bool -> m ()
- (<>=) :: (MonadState s m, Semigroup a) => ASetter' s a -> a -> m ()
- (&&=) :: MonadState s m => ASetter' s Bool -> Bool -> m ()
- (<.=) :: MonadState s m => ASetter s s a b -> b -> m b
- (?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m ()
- (<?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m b
- (<~) :: MonadState s m => ASetter s s a b -> m b -> m ()
- scribe :: (MonadWriter t m, Monoid s) => ASetter s t a b -> b -> m ()
- passing :: MonadWriter w m => Setter w w u v -> m (a, u -> v) -> m a
- censoring :: MonadWriter w m => Setter w w u v -> (u -> v) -> m a -> m a
- locally :: MonadReader s m => ASetter s s a b -> (a -> b) -> m r -> m r
- set' :: ASetter' s a -> a -> s -> s
- assignA :: Arrow p => ASetter s t a b -> p s b -> p s t
- class (Applicative f, Cotraversable f, Traversable f) => Settable f
- newtype Identity a = Identity {
- runIdentity :: a
Setters
type Setter s t a b = forall f. Settable f => (a -> f b) -> s -> f t Source #
The only LensLike law that can apply to a Setter l is that
setl y (setl x a) ≡setl y 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 can 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.
>>>over traverse f [a,b,c,d][f a,f b,f c,f d]
>>>over _1 f (a,b)(f a,b)
>>>over (traverse._1) f [(a,b),(c,d)][(f a,b),(f c,d)]
>>>over both f (a,b)(f a,f b)
>>>over (traverse.both) f [(a,b),(c,d)][(f a,f b),(f c,f d)]
type ASetter s t a b = (a -> Identity b) -> s -> Identity t Source #
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.
type Setting p s t a b = p a (Identity b) -> s -> Identity t Source #
This is a convenient alias when defining highly polymorphic code that takes both
ASetter and AnIndexedSetter as appropriate. If a function takes this it is
expecting one of those two things based on context.
type Setting' p s a = Setting p s s a a Source #
This is a convenient alias when defining highly polymorphic code that takes both
ASetter' and AnIndexedSetter' as appropriate. If a function takes this it is
expecting one of those two things based on context.
Building Setters
sets :: (Profunctor p, Profunctor q, Settable f) => (p a b -> q s t) -> Optical p q f s t a b Source #
Build a Setter, IndexedSetter or IndexPreservingSetter depending on your choice of Profunctor.
sets:: ((a -> b) -> s -> t) ->Setters t a b
Common Setters
mapped :: Functor f => Setter (f a) (f b) a b Source #
This Setter can be used to map over all of the values in a Functor.
fmap≡overmappedfmapDefault≡overtraverse(<$) ≡setmapped
>>>over mapped f [a,b,c][f a,f b,f c]
>>>over mapped (+1) [1,2,3][2,3,4]
>>>set mapped x [a,b,c][x,x,x]
>>>[[a,b],[c]] & mapped.mapped +~ x[[a + x,b + x],[c + x]]
>>>over (mapped._2) length [("hello","world"),("leaders","!!!")][("hello",5),("leaders",3)]
mapped::Functorf =>Setter(f a) (f b) a b
If you want an IndexPreservingSetter use .setting fmap
lifted :: Monad m => Setter (m a) (m b) a b Source #
This setter can be used to modify all of the values in a Monad.
You sometimes have to use this rather than mapped -- due to
temporary insanity Functor was not a superclass of Monad until
GHC 7.10.
liftM≡overlifted
>>>over lifted f [a,b,c][f a,f b,f c]
>>>set lifted b (Just a)Just b
If you want an IndexPreservingSetter use .setting liftM
contramapped :: Functor f => Setter (f b) (f a) a b Source #
This Setter can be used to map over all of the inputs to a Functor.
gmap≡overcontramapped
>>>getPredicate (over contramapped (*2) (Predicate even)) 5True
>>>getOp (over contramapped (*5) (Op show)) 100"500"
>>>Prelude.map ($ 1) $ over (mapped . _Unwrapping' Op . contramapped) (*12) [(*2),(+1),(^3)][24,13,1728]
argument :: Profunctor p => Setter (p b r) (p a r) a b Source #
This Setter can be used to map over the input of a Profunctor.
The most common Profunctor to use this with is (->).
>>>(argument %~ f) g xg (f x)
>>>(argument %~ show) length [1,2,3]7
>>>(argument %~ f) h x yh (f x) y
Map over the argument of the result of a function -- i.e., its second argument:
>>>(mapped.argument %~ f) h x yh x (f y)
argument::Setter(b -> r) (a -> r) a b
Functional Combinators
over :: ASetter s t a b -> (a -> b) -> s -> t Source #
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
Given any valid Setter l, you can also rely on the law:
overl f.overl g =overl (f.g)
e.g.
>>>over mapped f (over mapped g [a,b,c]) == over mapped (f . g) [a,b,c]True
Another way to view over is to say that it transforms a Setter into a
"semantic editor combinator".
>>>over mapped f (Just a)Just (f a)
>>>over mapped (*10) [1,2,3][10,20,30]
>>>over _1 f (a,b)(f a,b)
>>>over _1 show (10,20)("10",20)
over::Setters t a b -> (a -> b) -> s -> tover::ASetters t a b -> (a -> b) -> s -> t
set :: ASetter s t a b -> b -> s -> t Source #
Replace the target of a Lens or all of the targets of a Setter
or Traversal with a constant value.
(<$) ≡setmapped
>>>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::Setters t a b -> b -> s -> tset::Isos t a b -> b -> s -> tset::Lenss t a b -> b -> s -> tset::Traversals t a b -> b -> s -> t
(.~) :: ASetter s t a b -> b -> s -> t infixr 4 Source #
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
>>>(a,b,c,d) & _4 .~ e(a,b,c,e)
>>>(42,"world") & _1 .~ "hello"("hello","world")
>>>(a,b) & both .~ c(c,c)
(.~) ::Setters t a b -> b -> s -> t (.~) ::Isos t a b -> b -> s -> t (.~) ::Lenss t a b -> b -> s -> t (.~) ::Traversals t a b -> b -> s -> t
(%~) :: ASetter s t a b -> (a -> b) -> s -> t infixr 4 Source #
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
>>>(a,b,c) & _3 %~ f(a,b,f c)
>>>(a,b) & both %~ f(f a,f b)
>>>_2 %~ length $ (1,"hello")(1,5)
>>>traverse %~ f $ [a,b,c][f a,f b,f c]
>>>traverse %~ even $ [1,2,3][False,True,False]
>>>traverse.traverse %~ length $ [["hello","world"],["!!!"]][[5,5],[3]]
(%~) ::Setters t a b -> (a -> b) -> s -> t (%~) ::Isos t a b -> (a -> b) -> s -> t (%~) ::Lenss t a b -> (a -> b) -> s -> t (%~) ::Traversals t a b -> (a -> b) -> s -> t
(+~) :: Num a => ASetter s t a a -> a -> s -> t infixr 4 Source #
Increment the target(s) of a numerically valued Lens, Setter or Traversal.
>>>(a,b) & _1 +~ c(a + c,b)
>>>(a,b) & both +~ c(a + c,b + c)
>>>(1,2) & _2 +~ 1(1,3)
>>>[(a,b),(c,d)] & traverse.both +~ e[(a + e,b + e),(c + e,d + e)]
(+~) ::Numa =>Setter's a -> a -> s -> s (+~) ::Numa =>Iso's a -> a -> s -> s (+~) ::Numa =>Lens's a -> a -> s -> s (+~) ::Numa =>Traversal's a -> a -> s -> s
(-~) :: Num a => ASetter s t a a -> a -> s -> t infixr 4 Source #
Decrement the target(s) of a numerically valued Lens, Iso, Setter or Traversal.
>>>(a,b) & _1 -~ c(a - c,b)
>>>(a,b) & both -~ c(a - c,b - c)
>>>_1 -~ 2 $ (1,2)(-1,2)
>>>mapped.mapped -~ 1 $ [[4,5],[6,7]][[3,4],[5,6]]
(-~) ::Numa =>Setter's a -> a -> s -> s (-~) ::Numa =>Iso's a -> a -> s -> s (-~) ::Numa =>Lens's a -> a -> s -> s (-~) ::Numa =>Traversal's a -> a -> s -> s
(*~) :: Num a => ASetter s t a a -> a -> s -> t infixr 4 Source #
Multiply the target(s) of a numerically valued Lens, Iso, Setter or Traversal.
>>>(a,b) & _1 *~ c(a * c,b)
>>>(a,b) & both *~ c(a * c,b * c)
>>>(1,2) & _2 *~ 4(1,8)
>>>Just 24 & mapped *~ 2Just 48
(*~) ::Numa =>Setter's a -> a -> s -> s (*~) ::Numa =>Iso's a -> a -> s -> s (*~) ::Numa =>Lens's a -> a -> s -> s (*~) ::Numa =>Traversal's a -> a -> s -> s
(//~) :: Fractional a => ASetter s t a a -> a -> s -> t infixr 4 Source #
Divide the target(s) of a numerically valued Lens, Iso, Setter or Traversal.
>>>(a,b) & _1 //~ c(a / c,b)
>>>(a,b) & both //~ c(a / c,b / c)
>>>("Hawaii",10) & _2 //~ 2("Hawaii",5.0)
(//~) ::Fractionala =>Setter's a -> a -> s -> s (//~) ::Fractionala =>Iso's a -> a -> s -> s (//~) ::Fractionala =>Lens's a -> a -> s -> s (//~) ::Fractionala =>Traversal's a -> a -> s -> s
(^~) :: (Num a, Integral e) => ASetter s t a a -> e -> s -> t infixr 4 Source #
Raise the target(s) of a numerically valued Lens, Setter or Traversal to a non-negative integral power.
>>>(1,3) & _2 ^~ 2(1,9)
(^~) :: (Numa,Integrale) =>Setter's a -> e -> s -> s (^~) :: (Numa,Integrale) =>Iso's a -> e -> s -> s (^~) :: (Numa,Integrale) =>Lens's a -> e -> s -> s (^~) :: (Numa,Integrale) =>Traversal's a -> e -> s -> s
(^^~) :: (Fractional a, Integral e) => ASetter s t a a -> e -> s -> t infixr 4 Source #
Raise the target(s) of a fractionally valued Lens, Setter or Traversal to an integral power.
>>>(1,2) & _2 ^^~ (-1)(1,0.5)
(^^~) :: (Fractionala,Integrale) =>Setter's a -> e -> s -> s (^^~) :: (Fractionala,Integrale) =>Iso's a -> e -> s -> s (^^~) :: (Fractionala,Integrale) =>Lens's a -> e -> s -> s (^^~) :: (Fractionala,Integrale) =>Traversal's a -> e -> s -> s
(**~) :: Floating a => ASetter s t a a -> a -> s -> t infixr 4 Source #
Raise the target(s) of a floating-point valued Lens, Setter or Traversal to an arbitrary power.
>>>(a,b) & _1 **~ c(a**c,b)
>>>(a,b) & both **~ c(a**c,b**c)
>>>_2 **~ 10 $ (3,2)(3,1024.0)
(**~) ::Floatinga =>Setter's a -> a -> s -> s (**~) ::Floatinga =>Iso's a -> a -> s -> s (**~) ::Floatinga =>Lens's a -> a -> s -> s (**~) ::Floatinga =>Traversal's a -> a -> s -> s
(||~) :: ASetter s t Bool Bool -> Bool -> s -> t infixr 4 Source #
Logically || the target(s) of a Bool-valued Lens or Setter.
>>>both ||~ True $ (False,True)(True,True)
>>>both ||~ False $ (False,True)(False,True)
(||~) ::Setter'sBool->Bool-> s -> s (||~) ::Iso'sBool->Bool-> s -> s (||~) ::Lens'sBool->Bool-> s -> s (||~) ::Traversal'sBool->Bool-> s -> s
(<>~) :: Semigroup a => ASetter s t a a -> a -> s -> t infixr 4 Source #
Modify the target of a Semigroup value by using (.<>)
>>>(Sum a,b) & _1 <>~ Sum c(Sum {getSum = a + c},b)
>>>(Sum a,Sum b) & both <>~ Sum c(Sum {getSum = a + c},Sum {getSum = b + c})
>>>both <>~ "!!!" $ ("hello","world")("hello!!!","world!!!")
(<>~) ::Semigroupa =>Setters t a a -> a -> s -> t (<>~) ::Semigroupa =>Isos t a a -> a -> s -> t (<>~) ::Semigroupa =>Lenss t a a -> a -> s -> t (<>~) ::Semigroupa =>Traversals t a a -> a -> s -> t
(&&~) :: ASetter s t Bool Bool -> Bool -> s -> t infixr 4 Source #
Logically && the target(s) of a Bool-valued Lens or Setter.
>>>both &&~ True $ (False, True)(False,True)
>>>both &&~ False $ (False, True)(False,False)
(&&~) ::Setter'sBool->Bool-> s -> s (&&~) ::Iso'sBool->Bool-> s -> s (&&~) ::Lens'sBool->Bool-> s -> s (&&~) ::Traversal'sBool->Bool-> s -> s
(<.~) :: ASetter s t a b -> b -> s -> (b, t) infixr 4 Source #
Set with pass-through.
This is mostly present for consistency, but may be useful for chaining assignments.
If you do not need a copy of the intermediate result, then using l directly is a good idea..~ t
>>>(a,b) & _1 <.~ c(c,(c,b))
>>>("good","morning","vietnam") & _3 <.~ "world"("world",("good","morning","world"))
>>>(42,Map.fromList [("goodnight","gracie")]) & _2.at "hello" <.~ Just "world"(Just "world",(42,fromList [("goodnight","gracie"),("hello","world")]))
(<.~) ::Setters t a b -> b -> s -> (b, t) (<.~) ::Isos t a b -> b -> s -> (b, t) (<.~) ::Lenss t a b -> b -> s -> (b, t) (<.~) ::Traversals t a b -> b -> s -> (b, t)
(?~) :: ASetter s t a (Maybe b) -> b -> s -> t infixr 4 Source #
Set the target of a Lens, Traversal or Setter to Just a value.
l?~t ≡setl (Justt)
>>>Nothing & id ?~ aJust a
>>>Map.empty & at 3 ?~ xfromList [(3,x)]
?~ can be used type-changily:
>>>('a', ('b', 'c')) & _2.both ?~ 'x'('a',(Just 'x',Just 'x'))
(?~) ::Setters t a (Maybeb) -> b -> s -> t (?~) ::Isos t a (Maybeb) -> b -> s -> t (?~) ::Lenss t a (Maybeb) -> b -> s -> t (?~) ::Traversals t a (Maybeb) -> b -> s -> t
(<?~) :: ASetter s t a (Maybe b) -> b -> s -> (b, t) infixr 4 Source #
Set to Just a value 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 Data.Map as Map>>>_2.at "hello" <?~ "world" $ (42,Map.fromList [("goodnight","gracie")])("world",(42,fromList [("goodnight","gracie"),("hello","world")]))
(<?~) ::Setters t a (Maybeb) -> b -> s -> (b, t) (<?~) ::Isos t a (Maybeb) -> b -> s -> (b, t) (<?~) ::Lenss t a (Maybeb) -> b -> s -> (b, t) (<?~) ::Traversals t a (Maybeb) -> b -> s -> (b, t)
State Combinators
assign :: MonadState s m => ASetter s s a b -> b -> 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 (.=).
>>>execState (do assign _1 c; assign _2 d) (a,b)(c,d)
>>>execState (both .= c) (a,b)(c,c)
assign::MonadStates m =>Iso's a -> a -> m ()assign::MonadStates m =>Lens's a -> a -> m ()assign::MonadStates m =>Traversal's a -> a -> m ()assign::MonadStates m =>Setter's a -> a -> m ()
modifying :: MonadState s m => ASetter s s a b -> (a -> b) -> m () Source #
This is an alias for (%=).
(.=) :: MonadState s m => ASetter s s a b -> b -> m () infix 4 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.
>>>execState (do _1 .= c; _2 .= d) (a,b)(c,d)
>>>execState (both .= c) (a,b)(c,c)
(.=) ::MonadStates m =>Iso's a -> a -> m () (.=) ::MonadStates m =>Lens's a -> a -> m () (.=) ::MonadStates m =>Traversal's a -> a -> m () (.=) ::MonadStates m =>Setter's a -> a -> m ()
It puts the state in the monad or it gets the hose again.
(%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m () infix 4 Source #
Map over the target of a Lens or all of the targets of a Setter or Traversal in our monadic state.
>>>execState (do _1 %= f;_2 %= g) (a,b)(f a,g b)
>>>execState (do both %= f) (a,b)(f a,f b)
(%=) ::MonadStates m =>Iso's a -> (a -> a) -> m () (%=) ::MonadStates m =>Lens's a -> (a -> a) -> m () (%=) ::MonadStates m =>Traversal's a -> (a -> a) -> m () (%=) ::MonadStates m =>Setter's a -> (a -> a) -> m ()
(%=) ::MonadStates m =>ASetters s a b -> (a -> b) -> m ()
(+=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m () infix 4 Source #
Modify the target(s) of a Lens', Iso, Setter or Traversal by adding a value.
Example:
fresh::MonadStateIntm => mIntfresh= doid+=1useid
>>>execState (do _1 += c; _2 += d) (a,b)(a + c,b + d)
>>>execState (do _1.at 1.non 0 += 10) (Map.fromList [(2,100)],"hello")(fromList [(1,10),(2,100)],"hello")
(+=) :: (MonadStates m,Numa) =>Setter's a -> a -> m () (+=) :: (MonadStates m,Numa) =>Iso's a -> a -> m () (+=) :: (MonadStates m,Numa) =>Lens's a -> a -> m () (+=) :: (MonadStates m,Numa) =>Traversal's a -> a -> m ()
(-=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m () infix 4 Source #
Modify the target(s) of a Lens', Iso, Setter or Traversal by subtracting a value.
>>>execState (do _1 -= c; _2 -= d) (a,b)(a - c,b - d)
(-=) :: (MonadStates m,Numa) =>Setter's a -> a -> m () (-=) :: (MonadStates m,Numa) =>Iso's a -> a -> m () (-=) :: (MonadStates m,Numa) =>Lens's a -> a -> m () (-=) :: (MonadStates m,Numa) =>Traversal's a -> a -> m ()
(*=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m () infix 4 Source #
Modify the target(s) of a Lens', Iso, Setter or Traversal by multiplying by value.
>>>execState (do _1 *= c; _2 *= d) (a,b)(a * c,b * d)
(*=) :: (MonadStates m,Numa) =>Setter's a -> a -> m () (*=) :: (MonadStates m,Numa) =>Iso's a -> a -> m () (*=) :: (MonadStates m,Numa) =>Lens's a -> a -> m () (*=) :: (MonadStates m,Numa) =>Traversal's a -> a -> m ()
(//=) :: (MonadState s m, Fractional a) => ASetter' s a -> a -> m () infix 4 Source #
Modify the target(s) of a Lens', Iso, Setter or Traversal by dividing by a value.
>>>execState (do _1 //= c; _2 //= d) (a,b)(a / c,b / d)
(//=) :: (MonadStates m,Fractionala) =>Setter's a -> a -> m () (//=) :: (MonadStates m,Fractionala) =>Iso's a -> a -> m () (//=) :: (MonadStates m,Fractionala) =>Lens's a -> a -> m () (//=) :: (MonadStates m,Fractionala) =>Traversal's a -> a -> m ()
(^=) :: (MonadState s m, Num a, Integral e) => ASetter' s a -> e -> m () infix 4 Source #
Raise the target(s) of a numerically valued Lens, Setter or Traversal to a non-negative integral power.
(^=) :: (MonadStates m,Numa,Integrale) =>Setter's a -> e -> m () (^=) :: (MonadStates m,Numa,Integrale) =>Iso's a -> e -> m () (^=) :: (MonadStates m,Numa,Integrale) =>Lens's a -> e -> m () (^=) :: (MonadStates m,Numa,Integrale) =>Traversal's a -> e -> m ()
(^^=) :: (MonadState s m, Fractional a, Integral e) => ASetter' s a -> e -> m () infix 4 Source #
Raise the target(s) of a numerically valued Lens, Setter or Traversal to an integral power.
(^^=) :: (MonadStates m,Fractionala,Integrale) =>Setter's a -> e -> m () (^^=) :: (MonadStates m,Fractionala,Integrale) =>Iso's a -> e -> m () (^^=) :: (MonadStates m,Fractionala,Integrale) =>Lens's a -> e -> m () (^^=) :: (MonadStates m,Fractionala,Integrale) =>Traversal's a -> e -> m ()
(**=) :: (MonadState s m, Floating a) => ASetter' s a -> a -> m () infix 4 Source #
Raise the target(s) of a numerically valued Lens, Setter or Traversal to an arbitrary power
>>>execState (do _1 **= c; _2 **= d) (a,b)(a**c,b**d)
(**=) :: (MonadStates m,Floatinga) =>Setter's a -> a -> m () (**=) :: (MonadStates m,Floatinga) =>Iso's a -> a -> m () (**=) :: (MonadStates m,Floatinga) =>Lens's a -> a -> m () (**=) :: (MonadStates m,Floatinga) =>Traversal's a -> a -> m ()
(||=) :: MonadState s m => ASetter' s Bool -> Bool -> m () infix 4 Source #
Modify the target(s) of a Lens', 'Iso, Setter or Traversal by taking their logical || with a value.
>>>execState (do _1 ||= True; _2 ||= False; _3 ||= True; _4 ||= False) (True,True,False,False)(True,True,True,False)
(||=) ::MonadStates m =>Setter'sBool->Bool-> m () (||=) ::MonadStates m =>Iso'sBool->Bool-> m () (||=) ::MonadStates m =>Lens'sBool->Bool-> m () (||=) ::MonadStates m =>Traversal'sBool->Bool-> m ()
(<>=) :: (MonadState s m, Semigroup a) => ASetter' s a -> a -> m () infix 4 Source #
Modify the target(s) of a Lens', Iso, Setter or Traversal by using (.<>)
>>>execState (do _1 <>= Sum c; _2 <>= Product d) (Sum a,Product b)(Sum {getSum = a + c},Product {getProduct = b * d})
>>>execState (both <>= "!!!") ("hello","world")("hello!!!","world!!!")
(<>=) :: (MonadStates m,Semigroupa) =>Setter's a -> a -> m () (<>=) :: (MonadStates m,Semigroupa) =>Iso's a -> a -> m () (<>=) :: (MonadStates m,Semigroupa) =>Lens's a -> a -> m () (<>=) :: (MonadStates m,Semigroupa) =>Traversal's a -> a -> m ()
(&&=) :: MonadState s m => ASetter' s Bool -> Bool -> m () infix 4 Source #
Modify the target(s) of a Lens', Iso, Setter or Traversal by taking their logical && with a value.
>>>execState (do _1 &&= True; _2 &&= False; _3 &&= True; _4 &&= False) (True,True,False,False)(True,False,False,False)
(&&=) ::MonadStates m =>Setter'sBool->Bool-> m () (&&=) ::MonadStates m =>Iso'sBool->Bool-> m () (&&=) ::MonadStates m =>Lens'sBool->Bool-> m () (&&=) ::MonadStates m =>Traversal'sBool->Bool-> m ()
(<.=) :: MonadState s m => ASetter s s a b -> b -> m b infix 4 Source #
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 will avoid unused binding warnings..= d
(<.=) ::MonadStates m =>Setters s a b -> b -> m b (<.=) ::MonadStates m =>Isos s a b -> b -> m b (<.=) ::MonadStates m =>Lenss s a b -> b -> m b (<.=) ::MonadStates m =>Traversals s a b -> b -> m b
(?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m () infix 4 Source #
Replace the target of a Lens or all of the targets of a Setter or Traversal in our monadic
state with Just a new value, irrespective of the old.
>>>execState (do at 1 ?= a; at 2 ?= b) Map.emptyfromList [(1,a),(2,b)]
>>>execState (do _1 ?= b; _2 ?= c) (Just a, Nothing)(Just b,Just c)
(?=) ::MonadStates m =>Iso's (Maybea) -> a -> m () (?=) ::MonadStates m =>Lens's (Maybea) -> a -> m () (?=) ::MonadStates m =>Traversal's (Maybea) -> a -> m () (?=) ::MonadStates m =>Setter's (Maybea) -> a -> m ()
(<?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m b infix 4 Source #
Set Just a value with pass-through
This is useful for chaining assignment without round-tripping through your Monad stack.
do x <-at"foo"<?=ninety_nine_bottles_of_beer_on_the_wall
If you do not need a copy of the intermediate result, then using l will avoid unused binding warnings.?= d
(<?=) ::MonadStates m =>Setters s a (Maybeb) -> b -> m b (<?=) ::MonadStates m =>Isos s a (Maybeb) -> b -> m b (<?=) ::MonadStates m =>Lenss s a (Maybeb) -> b -> m b (<?=) ::MonadStates m =>Traversals s a (Maybeb) -> b -> m b
(<~) :: MonadState s m => ASetter s s a b -> m b -> m () infixr 2 Source #
Run a monadic action, and set all of the targets of a Lens, Setter or Traversal to its result.
(<~) ::MonadStates m =>Isos s a b -> m b -> m () (<~) ::MonadStates m =>Lenss s a b -> m b -> m () (<~) ::MonadStates m =>Traversals s a b -> m b -> m () (<~) ::MonadStates m =>Setters s a b -> m b -> 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
...
Writer Combinators
scribe :: (MonadWriter t m, Monoid s) => ASetter s t a b -> b -> m () Source #
Write to a fragment of a larger Writer format.
passing :: MonadWriter w m => Setter w w u v -> m (a, u -> v) -> m a Source #
This is a generalization of pass that allows you to modify just a
portion of the resulting MonadWriter.
censoring :: MonadWriter w m => Setter w w u v -> (u -> v) -> m a -> m a Source #
This is a generalization of censor that allows you to censor just a
portion of the resulting MonadWriter.
Reader Combinators
locally :: MonadReader s m => ASetter s s a b -> (a -> b) -> m r -> m r Source #
Modify the value of the Reader environment associated with the target of a
Setter, Lens, or Traversal.
locallylida ≡ alocallyl f.locally l g ≡locallyl (f.g)
>>>(1,1) & locally _1 (+1) (uncurry (+))3
>>>"," & locally ($) ("Hello" <>) (<> " world!")"Hello, world!"
locally :: MonadReader s m =>Isos s a b -> (a -> b) -> m r -> m r locally :: MonadReader s m =>Lenss s a b -> (a -> b) -> m r -> m r locally :: MonadReader s m =>Traversals s a b -> (a -> b) -> m r -> m r locally :: MonadReader s m =>Setters s a b -> (a -> b) -> m r -> m r
Simplified State Setting
set' :: ASetter' s a -> a -> s -> s Source #
Replace the target of a Lens or all of the targets of a Setter'
or Traversal with a constant value, without changing its type.
This is a type restricted version of set, which retains the type of the original.
>>>set' mapped x [a,b,c,d][x,x,x,x]
>>>set' _2 "hello" (1,"world")(1,"hello")
>>>set' mapped 0 [1,2,3,4][0,0,0,0]
Note: Attempting to adjust set' a Fold or Getter will fail at compile time with an
relatively nice error message.
set'::Setter's a -> a -> s -> sset'::Iso's a -> a -> s -> sset'::Lens's a -> a -> s -> sset'::Traversal's a -> a -> s -> s
Arrow operators
assignA :: Arrow p => ASetter s t a b -> p s b -> p s t Source #
Run an arrow command and use the output to set all the targets of
a Lens, Setter or Traversal to the result.
assignA can be used very similarly to (<~), except that the type of
the object being modified can change; for example:
runKleisli action ((), (), ()) where
action = assignA _1 (Kleisli (const getVal1))
>>> assignA _2 (Kleisli (const getVal2))
>>> assignA _3 (Kleisli (const getVal3))
getVal1 :: Either String Int
getVal1 = ...
getVal2 :: Either String Bool
getVal2 = ...
getVal3 :: Either String Char
getVal3 = ...
has the type Either String (Int, Bool, Char)
assignA::Arrowp =>Isos t a b -> p s b -> p s tassignA::Arrowp =>Lenss t a b -> p s b -> p s tassignA::Arrowp =>Traversals t a b -> p s b -> p s tassignA::Arrowp =>Setters t a b -> p s b -> p s t
Exported for legible error messages
class (Applicative f, Cotraversable f, Traversable f) => Settable f Source #
Minimal complete definition
Instances
| Settable Identity Source # | So you can pass our |
Defined in Control.Lens.Internal.Setter Methods untainted :: Identity a -> a Source # untaintedDot :: Profunctor p => p a (Identity b) -> p a b Source # taintedDot :: Profunctor p => p a b -> p a (Identity b) Source # | |
| Settable f => Settable (Backwards f) Source # | |
Defined in Control.Lens.Internal.Setter Methods untainted :: Backwards f a -> a Source # untaintedDot :: Profunctor p => p a (Backwards f b) -> p a b Source # taintedDot :: Profunctor p => p a b -> p a (Backwards f b) Source # | |
| (Settable f, Settable g) => Settable (Compose f g) Source # | |
Defined in Control.Lens.Internal.Setter Methods untainted :: Compose f g a -> a Source # untaintedDot :: Profunctor p => p a (Compose f g b) -> p a b Source # taintedDot :: Profunctor p => p a b -> p a (Compose f g b) Source # | |
Identity functor and monad. (a non-strict monad)
Since: base-4.8.0.0
Constructors
| Identity | |
Fields
| |