| Portability | Rank2Types | 
|---|---|
| Stability | provisional | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Safe Haskell | Trustworthy | 
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 (<$).
- 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 IndexedSetter i s t a b = forall f p. (Indexable i p, Settable f) => p a (f b) -> s -> f t
 - type IndexedSetter' i s a = IndexedSetter i s s a a
 - type ASetter s t a b = (a -> Mutator b) -> s -> Mutator t
 - type ASetter' s a = ASetter s s a a
 - type AnIndexedSetter i s t a b = Indexed i a (Mutator b) -> s -> Mutator t
 - type AnIndexedSetter' i s a = AnIndexedSetter i s s a a
 - type Setting p s t a b = p a (Mutator b) -> s -> Mutator 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) -> Overloading p q f s t a b
 - setting :: ((a -> b) -> s -> t) -> IndexPreservingSetter s t a b
 - cloneSetter :: ASetter s t a b -> Setter s t a b
 - cloneIndexPreservingSetter :: ASetter s t a b -> IndexPreservingSetter s t a b
 - cloneIndexedSetter :: AnIndexedSetter i s t a b -> IndexedSetter i 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 :: Contravariant f => Setter (f b) (f a) a b
 - argument :: Profunctor p => Setter (p b r) (p a r) a b
 - over :: Profunctor p => Setting p s t a b -> p a b -> s -> t
 - set :: ASetter s t a b -> b -> s -> t
 - (.~) :: ASetter s t a b -> b -> s -> t
 - (%~) :: Profunctor p => Setting p s t a b -> p 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
 - (<>~) :: Monoid 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 ()
 - (.=) :: MonadState s m => ASetter s s a b -> b -> m ()
 - (%=) :: (Profunctor p, MonadState s m) => Setting p s s a b -> p 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, Monoid 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
 - ipassing :: MonadWriter w m => IndexedSetter i w w u v -> m (a, i -> u -> v) -> m a
 - censoring :: MonadWriter w m => Setter w w u v -> (u -> v) -> m a -> m a
 - icensoring :: MonadWriter w m => IndexedSetter i w w u v -> (i -> u -> v) -> m a -> m a
 - set' :: ASetter' s a -> a -> s -> s
 - imapOf :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t
 - iover :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t
 - isets :: ((i -> a -> b) -> s -> t) -> IndexedSetter i s t a b
 - (%@~) :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t
 - (%@=) :: MonadState s m => AnIndexedSetter i s s a b -> (i -> a -> b) -> m ()
 - class (Applicative f, Distributive f, Traversable f) => Settable f
 - data Mutator a
 - mapOf :: Profunctor p => Setting p s t a b -> p a b -> s -> t
 
Setters
type Setter s t a b = forall f. Settable f => (a -> f b) -> s -> f tSource
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 IndexedSetter i s t a b = forall f p. (Indexable i p, Settable f) => p a (f b) -> s -> f tSource
Every IndexedSetter is a valid Setter.
The Setter laws are still required to hold.
type IndexedSetter' i s a = IndexedSetter i s s a aSource
typeIndexedSetter'i =Simple(IndexedSetteri)
type AnIndexedSetter i s t a b = Indexed i a (Mutator b) -> s -> Mutator tSource
Running an IndexedSetter 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 AnIndexedSetter' i s a = AnIndexedSetter i s s a aSource
typeAnIndexedSetter'i =Simple(AnIndexedSetteri)
type Setting p s t a b = p a (Mutator b) -> s -> Mutator tSource
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 aSource
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) -> Overloading p q f s t a bSource
Build a Setter, IndexedSetter or IndexPreservingSetter depending on your choice of Profunctor.
sets:: ((a -> b) -> s -> t) ->Setters t a b
setting :: ((a -> b) -> s -> t) -> IndexPreservingSetter s t a bSource
Build an index-preserving Setter from a map-like function.
Your supplied function f is required to satisfy:
fid≡idf g.f h ≡ f (g.h)
Equational reasoning:
setting.over≡idover.setting≡id
Another way to view sets is that it takes a "semantic editor combinator"
 and transforms it into a Setter.
setting:: ((a -> b) -> s -> t) ->Setters t a b
cloneIndexPreservingSetter :: ASetter s t a b -> IndexPreservingSetter s t a bSource
Build an IndexPreservingSetter from any Setter.
cloneIndexedSetter :: AnIndexedSetter i s t a b -> IndexedSetter i s t a bSource
Clone an IndexedSetter.
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
>>>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 bSource
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 is not a superclass of Monad.
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 :: Contravariant f => Setter (f b) (f a) a bSource
This Setter can be used to map over all of the inputs to a Contravariant.
contramap≡overcontramapped
>>>getPredicate (over contramapped (*2) (Predicate even)) 5True
>>>getOp (over contramapped (*5) (Op show)) 100"500"
>>>Prelude.map ($ 1) $ over (mapped . wrapping Op . contramapped) (*12) [(*2),(+1),(^3)][24,13,1728]
argument :: Profunctor p => Setter (p b r) (p a r) a bSource
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 :: Profunctor p => Setting p s t a b -> p a b -> s -> tSource
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 -> tSource
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 -> tSource
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
(%~) :: Profunctor p => Setting p s t a b -> p a b -> s -> tSource
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 -> tSource
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 -> tSource
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 -> tSource
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 -> tSource
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 -> tSource
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 -> tSource
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 -> tSource
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 **~ pi $ (1,3)(1,31.54428070019754)
(**~) ::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 -> tSource
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
(<>~) :: Monoid a => ASetter s t a a -> a -> s -> tSource
Modify the target of a monoidally valued by mappending another value.
>>>(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!!!")
(<>~) ::Monoida =>Setters t a a -> a -> s -> t (<>~) ::Monoida =>Isos t a a -> a -> s -> t (<>~) ::Monoida =>Lenss t a a -> a -> s -> t (<>~) ::Monoida =>Traversals t a a -> a -> s -> t
(&&~) :: ASetter s t Bool Bool -> Bool -> s -> tSource
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)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.
.~ 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 -> tSource
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)]
(?~) ::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)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 ()
(.=) :: 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 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 ()
(%=) :: (Profunctor p, MonadState s m) => Setting p s s a b -> p a b -> m ()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 ()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 ()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 ()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 ()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 ()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 ()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 ()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 ()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, Monoid a) => ASetter' s a -> a -> m ()Source
Modify the target(s) of a Lens', Iso, Setter or Traversal by mappending a value.
>>>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,Monoida) =>Setter's a -> a -> m () (<>=) :: (MonadStates m,Monoida) =>Iso's a -> a -> m () (<>=) :: (MonadStates m,Monoida) =>Lens's a -> a -> m () (<>=) :: (MonadStates m,Monoida) =>Traversal's a -> a -> m ()
(&&=) :: MonadState s m => ASetter' s Bool -> Bool -> m ()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 bSource
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 ()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 bSource
Set Just a value with pass-through
This is useful for chaining assignment without round-tripping through your Monad stack.
do x <-atfoo<?=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 ()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 aSource
This is a generalization of pass that alows you to modify just a
 portion of the resulting MonadWriter.
ipassing :: MonadWriter w m => IndexedSetter i w w u v -> m (a, i -> u -> v) -> m aSource
This is a generalization of pass that alows you to modify just a
 portion of the resulting MonadWriter with access to the index of an
 IndexedSetter.
censoring :: MonadWriter w m => Setter w w u v -> (u -> v) -> m a -> m aSource
This is a generalization of censor that alows you to censor just a
 portion of the resulting MonadWriter.
icensoring :: MonadWriter w m => IndexedSetter i w w u v -> (i -> u -> v) -> m a -> m aSource
This is a generalization of censor that alows you to censor just a
 portion of the resulting MonadWriter, with access to the index of an
 IndexedSetter.
Simplified State Setting
set' :: ASetter' s a -> a -> s -> sSource
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
Indexed Setters
imapOf :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> tSource
Deprecated: Use iover
Map with index. (Deprecated alias for iover).
When you do not need access to the index, then mapOf is more liberal in what it can accept.
mapOfl ≡imapOfl.const
imapOf::IndexedSetteri s t a b -> (i -> a -> b) -> s -> timapOf::IndexedLensi s t a b -> (i -> a -> b) -> s -> timapOf::IndexedTraversali s t a b -> (i -> a -> b) -> s -> t
iover :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> tSource
Map with index. This is an alias for imapOf.
When you do not need access to the index, then over is more liberal in what it can accept.
overl ≡ioverl.constioverl ≡overl.Indexed
iover::IndexedSetteri s t a b -> (i -> a -> b) -> s -> tiover::IndexedLensi s t a b -> (i -> a -> b) -> s -> tiover::IndexedTraversali s t a b -> (i -> a -> b) -> s -> t
isets :: ((i -> a -> b) -> s -> t) -> IndexedSetter i s t a bSource
(%@~) :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> tSource
Adjust every target of an IndexedSetter, IndexedLens or IndexedTraversal
 with access to the index.
(%@~) ≡imapOf
When you do not need access to the index then (%@~) is more liberal in what it can accept.
l%~f ≡ l%@~constf
(%@~) ::IndexedSetteri s t a b -> (i -> a -> b) -> s -> t (%@~) ::IndexedLensi s t a b -> (i -> a -> b) -> s -> t (%@~) ::IndexedTraversali s t a b -> (i -> a -> b) -> s -> t
(%@=) :: MonadState s m => AnIndexedSetter i s s a b -> (i -> a -> b) -> m ()Source
Adjust every target in the current state of an IndexedSetter, IndexedLens or IndexedTraversal
 with access to the index.
When you do not need access to the index then (%=) is more liberal in what it can accept.
l%=f ≡ l%@=constf
(%@=) ::MonadStates m =>IndexedSetteri s s a b -> (i -> a -> b) -> m () (%@=) ::MonadStates m =>IndexedLensi s s a b -> (i -> a -> b) -> m () (%@=) ::MonadStates m =>IndexedTraversali s t a b -> (i -> a -> b) -> m ()
Exported for legible error messages
class (Applicative f, Distributive f, Traversable f) => Settable f Source