| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Optic.Setter
Contents
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
- (.~) :: 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
- (&&~) :: ASetter s t Bool Bool -> Bool -> s -> t
- set :: ASetter s t a b -> b -> s -> t
- over :: ASetter s t a b -> (a -> b) -> s -> t
Setter
type Setter s t a b = forall (f :: * -> *). Settable f => (a -> f b) -> s -> f t #
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)]
(.~) :: ASetter s t a b -> b -> s -> t infixr 4 #
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 #
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 #
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 #
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 #
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 #
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 #
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 #
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 #
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 #
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
(&&~) :: ASetter s t Bool Bool -> Bool -> s -> t infixr 4 #
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
set :: ASetter s t a b -> b -> s -> t #
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
over :: ASetter s t a b -> (a -> b) -> s -> t #
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