| Copyright | (C) 2012-15 Edward Kmett | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | Safe | 
| Language | Haskell98 | 
Control.Lens.Operators
Contents
Description
This module exists for users who like to work with qualified imports but want access to the operators from Lens.
import qualified Control.Lens as L import Control.Lens.Operators
- (<|) :: Cons s s a a => a -> s -> s
- (|>) :: Snoc s s a a => s -> a -> s
- (^..) :: s -> Getting (Endo [a]) s a -> [a]
- (^?) :: s -> Getting (First a) s a -> Maybe a
- (^?!) :: s -> Getting (Endo a) s a -> a
- (^@..) :: s -> IndexedGetting i (Endo [(i, a)]) s a -> [(i, a)]
- (^@?) :: s -> IndexedGetting i (Endo (Maybe (i, a))) s a -> Maybe (i, a)
- (^@?!) :: s -> IndexedGetting i (Endo (i, a)) s a -> (i, a)
- (^.) :: s -> Getting a s a -> a
- (^@.) :: s -> IndexedGetting i (i, a) s a -> (i, a)
- (<.) :: Indexable i p => (Indexed i s t -> r) -> ((a -> b) -> s -> t) -> p a b -> r
- (.>) :: (st -> r) -> (kab -> st) -> kab -> r
- (<.>) :: Indexable (i, j) p => (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> p a b -> r
- (%%~) :: Optical p q f s t a b -> p a (f b) -> q s (f t)
- (%%=) :: MonadState s m => Over p ((,) r) s s a b -> p a (r, b) -> m r
- (&) :: a -> (a -> b) -> b
- (&~) :: s -> State s a -> s
- (<&>) :: Functor f => f a -> (a -> b) -> f b
- (??) :: Functor f => f (a -> b) -> a -> f b
- (<%~) :: Profunctor p => Optical p q ((,) b) s t a b -> p a b -> q s (b, t)
- (<+~) :: Num a => Optical (->) q ((,) a) s t a a -> a -> q s (a, t)
- (<-~) :: Num a => Optical (->) q ((,) a) s t a a -> a -> q s (a, t)
- (<*~) :: Num a => Optical (->) q ((,) a) s t a a -> a -> q s (a, t)
- (<//~) :: Fractional a => Optical (->) q ((,) a) s t a a -> a -> q s (a, t)
- (<^~) :: (Num a, Integral e) => Optical (->) q ((,) a) s t a a -> e -> q s (a, t)
- (<^^~) :: (Fractional a, Integral e) => Optical (->) q ((,) a) s t a a -> e -> q s (a, t)
- (<**~) :: Floating a => Optical (->) q ((,) a) s t a a -> a -> q s (a, t)
- (<||~) :: Optical (->) q ((,) Bool) s t Bool Bool -> Bool -> q s (Bool, t)
- (<&&~) :: Optical (->) q ((,) Bool) s t Bool Bool -> Bool -> q s (Bool, t)
- (<<%~) :: Strong p => Optical p q ((,) a) s t a b -> p a b -> q s (a, t)
- (<<.~) :: Optical (->) q ((,) a) s t a b -> b -> q s (a, t)
- (<<+~) :: Num a => Optical' (->) q ((,) a) s a -> a -> q s (a, s)
- (<<-~) :: Num a => Optical' (->) q ((,) a) s a -> a -> q s (a, s)
- (<<*~) :: Num a => Optical' (->) q ((,) a) s a -> a -> q s (a, s)
- (<<//~) :: Fractional a => Optical' (->) q ((,) a) s a -> a -> q s (a, s)
- (<<^~) :: (Num a, Integral e) => Optical' (->) q ((,) a) s a -> e -> q s (a, s)
- (<<^^~) :: (Fractional a, Integral e) => Optical' (->) q ((,) a) s a -> e -> q s (a, s)
- (<<**~) :: Floating a => Optical' (->) q ((,) a) s a -> a -> q s (a, s)
- (<<||~) :: Optical' (->) q ((,) Bool) s Bool -> Bool -> q s (Bool, s)
- (<<&&~) :: Optical' (->) q ((,) Bool) s Bool -> Bool -> q s (Bool, s)
- (<<<>~) :: Monoid r => Optical' (->) q ((,) r) s r -> r -> q s (r, s)
- (<%=) :: (Profunctor p, MonadState s m) => Over p ((,) b) s s a b -> p a b -> m b
- (<+=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<-=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<*=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<//=) :: (MonadState s m, Fractional a) => LensLike' ((,) a) s a -> a -> m a
- (<^=) :: (MonadState s m, Num a, Integral e) => LensLike' ((,) a) s a -> e -> m a
- (<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> m a
- (<**=) :: (MonadState s m, Floating a) => LensLike' ((,) a) s a -> a -> m a
- (<||=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool
- (<&&=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool
- (<<%=) :: (Strong p, MonadState s m) => Over p ((,) a) s s a b -> p a b -> m a
- (<<.=) :: MonadState s m => LensLike ((,) a) s s a b -> b -> m a
- (<<+=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<<-=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<<*=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<<//=) :: (MonadState s m, Fractional a) => LensLike' ((,) a) s a -> a -> m a
- (<<^=) :: (MonadState s m, Num a, Integral e) => LensLike' ((,) a) s a -> e -> m a
- (<<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> m a
- (<<**=) :: (MonadState s m, Floating a) => LensLike' ((,) a) s a -> a -> m a
- (<<||=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool
- (<<&&=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool
- (<<<>=) :: (MonadState s m, Monoid r) => LensLike' ((,) r) s r -> r -> m r
- (<<~) :: MonadState s m => ALens s s a b -> m b -> m b
- (<<>~) :: Monoid m => Optical (->) q ((,) m) s t m m -> m -> q s (m, t)
- (<<>=) :: (MonadState s m, Monoid r) => LensLike' ((,) r) s r -> r -> m r
- (<%@~) :: Optical (Indexed i) q ((,) b) s t a b -> (i -> a -> b) -> q s (b, t)
- (<<%@~) :: Optical (Indexed i) q ((,) a) s t a b -> (i -> a -> b) -> q s (a, t)
- (%%@~) :: IndexedLensLike i f s t a b -> (i -> a -> f b) -> s -> f t
- (%%@=) :: MonadState s m => IndexedLensLike i ((,) r) s s a b -> (i -> a -> (r, b)) -> m r
- (<%@=) :: MonadState s m => IndexedLensLike i ((,) b) s s a b -> (i -> a -> b) -> m b
- (<<%@=) :: MonadState s m => IndexedLensLike i ((,) a) s s a b -> (i -> a -> b) -> m a
- (^#) :: s -> ALens s t a b -> a
- (#~) :: ALens s t a b -> b -> s -> t
- (#%~) :: ALens s t a b -> (a -> b) -> s -> t
- (#%%~) :: Functor f => ALens s t a b -> (a -> f b) -> s -> f t
- (#=) :: MonadState s m => ALens s s a b -> b -> m ()
- (#%=) :: MonadState s m => ALens s s a b -> (a -> b) -> m ()
- (<#%~) :: ALens s t a b -> (a -> b) -> s -> (b, t)
- (<#%=) :: MonadState s m => ALens s s a b -> (a -> b) -> m b
- (#%%=) :: MonadState s m => ALens s s a b -> (a -> (r, b)) -> m r
- (<#~) :: ALens s t a b -> b -> s -> (b, t)
- (<#=) :: MonadState s m => ALens s s a b -> b -> m b
- (...) :: (Applicative f, Plated c) => LensLike f s t c c -> Over p f c c a b -> Over p f s t a b
- (#) :: AReview t b -> b -> t
- (%~) :: Profunctor p => Setting p s t a b -> p a b -> s -> t
- (.~) :: ASetter s t a b -> b -> s -> t
- (?~) :: ASetter s t a (Maybe b) -> b -> s -> t
- (<.~) :: ASetter s t a b -> b -> s -> (b, t)
- (<?~) :: ASetter s t a (Maybe b) -> b -> s -> (b, 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
- (.=) :: 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 => ASetter s s a (Maybe b) -> 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 => ASetter' s Bool -> Bool -> m ()
- (<~) :: MonadState s m => ASetter s s a b -> m b -> m ()
- (<.=) :: MonadState s m => ASetter s s a b -> b -> m b
- (<?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m b
- (<>~) :: Monoid a => ASetter s t a a -> a -> s -> t
- (<>=) :: (MonadState s m, Monoid a) => ASetter' s a -> a -> m ()
- (%@~) :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t
- (%@=) :: MonadState s m => AnIndexedSetter i s s a b -> (i -> a -> b) -> m ()
Control.Lens.Cons
Control.Lens.Fold
(^..) :: s -> Getting (Endo [a]) s a -> [a] infixl 8 Source
A convenient infix (flipped) version of toListOf.
>>>[[1,2],[3]]^..traverse.traverse[1,2,3]
>>>(1,2)^..both[1,2]
toListxs ≡ xs^..folded(^..) ≡fliptoListOf
(^..) :: s ->Getters a -> a :: s ->Folds a -> a :: s ->Lens's a -> a :: s ->Iso's a -> a :: s ->Traversal's a -> a :: s ->Prism's a -> [a]
(^?) :: s -> Getting (First a) s a -> Maybe a infixl 8 Source
Perform a safe head of a Fold or Traversal or retrieve Just the result
 from a Getter or Lens.
When using a Traversal as a partial Lens, or a Fold as a partial Getter this can be a convenient
 way to extract the optional value.
Note: if you get stack overflows due to this, you may want to use firstOf instead, which can deal
 more gracefully with heavily left-biased trees.
>>>Left 4 ^?_LeftJust 4
>>>Right 4 ^?_LeftNothing
>>>"world" ^? ix 3Just 'l'
>>>"world" ^? ix 20Nothing
(^?) ≡flippreview
(^?) :: s ->Getters a ->Maybea (^?) :: s ->Folds a ->Maybea (^?) :: s ->Lens's a ->Maybea (^?) :: s ->Iso's a ->Maybea (^?) :: s ->Traversal's a ->Maybea
(^@..) :: s -> IndexedGetting i (Endo [(i, a)]) s a -> [(i, a)] infixl 8 Source
An infix version of itoListOf.
(^@?) :: s -> IndexedGetting i (Endo (Maybe (i, a))) s a -> Maybe (i, a) infixl 8 Source
Perform a safe head (with index) of an IndexedFold or IndexedTraversal or retrieve Just the index and result
 from an IndexedGetter or IndexedLens.
When using a IndexedTraversal as a partial IndexedLens, or an IndexedFold as a partial IndexedGetter this can be a convenient
 way to extract the optional value.
(^@?) :: s ->IndexedGetteri s a ->Maybe(i, a) (^@?) :: s ->IndexedFoldi s a ->Maybe(i, a) (^@?) :: s ->IndexedLens'i s a ->Maybe(i, a) (^@?) :: s ->IndexedTraversal'i s a ->Maybe(i, a)
(^@?!) :: s -> IndexedGetting i (Endo (i, a)) s a -> (i, a) infixl 8 Source
Perform an *UNSAFE* head (with index) of an IndexedFold or IndexedTraversal assuming that it is there.
(^@?!) :: s ->IndexedGetteri s a -> (i, a) (^@?!) :: s ->IndexedFoldi s a -> (i, a) (^@?!) :: s ->IndexedLens'i s a -> (i, a) (^@?!) :: s ->IndexedTraversal'i s a -> (i, a)
Control.Lens.Getter
(^.) :: s -> Getting a s a -> a infixl 8 Source
View the value pointed to by a Getter or Lens or the
 result of folding over all the results of a Fold or
 Traversal that points at a monoidal values.
This is the same operation as view with the arguments flipped.
The fixity and semantics are such that subsequent field accesses can be
 performed with (.).
>>>(a,b)^._2b
>>>("hello","world")^._2"world"
>>>import Data.Complex>>>((0, 1 :+ 2), 3)^._1._2.to magnitude2.23606797749979
(^.) :: s ->Getters a -> a (^.) ::Monoidm => s ->Folds m -> m (^.) :: s ->Iso's a -> a (^.) :: s ->Lens's a -> a (^.) ::Monoidm => s ->Traversal's m -> m
(^@.) :: s -> IndexedGetting i (i, a) s a -> (i, a) infixl 8 Source
View the index and value of an IndexedGetter or IndexedLens.
This is the same operation as iview with the arguments flipped.
The fixity and semantics are such that subsequent field accesses can be
 performed with (.).
(^@.) :: s ->IndexedGetteri s a -> (i, a) (^@.) :: s ->IndexedLens'i s a -> (i, a)
The result probably doesn't have much meaning when applied to an IndexedFold.
Control.Lens.Indexed
(<.) :: Indexable i p => (Indexed i s t -> r) -> ((a -> b) -> s -> t) -> p a b -> r infixr 9 Source
Compose an Indexed function with a non-indexed function.
Mnemonically, the < points to the indexing we want to preserve.
>>>let nestedMap = (fmap Map.fromList . Map.fromList) [(1, [(10, "one,ten"), (20, "one,twenty")]), (2, [(30, "two,thirty"), (40,"two,forty")])]>>>nestedMap^..(itraversed<.itraversed).withIndex[(1,"one,ten"),(1,"one,twenty"),(2,"two,thirty"),(2,"two,forty")]
(.>) :: (st -> r) -> (kab -> st) -> kab -> r infixr 9 Source
Compose a non-indexed function with an Indexed function.
Mnemonically, the > points to the indexing we want to preserve.
This is the same as (..)
f  (and . gf ) gives you the index of .> gg unless g is index-preserving, like a
 Prism, Iso or Equality, in which case it'll pass through the index of f.
>>>let nestedMap = (fmap Map.fromList . Map.fromList) [(1, [(10, "one,ten"), (20, "one,twenty")]), (2, [(30, "two,thirty"), (40,"two,forty")])]>>>nestedMap^..(itraversed.>itraversed).withIndex[(10,"one,ten"),(20,"one,twenty"),(30,"two,thirty"),(40,"two,forty")]
(<.>) :: Indexable (i, j) p => (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> p a b -> r infixr 9 Source
Composition of Indexed functions.
Mnemonically, the < and > points to the fact that we want to preserve the indices.
>>>let nestedMap = (fmap Map.fromList . Map.fromList) [(1, [(10, "one,ten"), (20, "one,twenty")]), (2, [(30, "two,thirty"), (40,"two,forty")])]>>>nestedMap^..(itraversed<.>itraversed).withIndex[((1,10),"one,ten"),((1,20),"one,twenty"),((2,30),"two,thirty"),((2,40),"two,forty")]
Control.Lens.Lens
(%%~) :: Optical p q f s t a b -> p a (f b) -> q s (f t) infixr 4 Source
(%%~) can be used in one of two scenarios:
When applied to a Lens, it can edit the target of the Lens in a
 structure, extracting a functorial result.
When applied to a Traversal, it can edit the
 targets of the traversals, extracting an applicative summary of its
 actions.
For all that the definition of this combinator is just:
(%%~) ≡id
It may be beneficial to think about it as if it had these even more restricted types, however:
(%%~) ::Functorf =>Isos t a b -> (a -> f b) -> s -> f t (%%~) ::Functorf =>Lenss t a b -> (a -> f b) -> s -> f t (%%~) ::Applicativef =>Traversals t a b -> (a -> f b) -> s -> f t
When applied to a Traversal, it can edit the
 targets of the traversals, extracting a supplemental monoidal summary
 of its actions, by choosing f = ((,) m)
(%%~) ::Isos t a b -> (a -> (r, b)) -> s -> (r, t) (%%~) ::Lenss t a b -> (a -> (r, b)) -> s -> (r, t) (%%~) ::Monoidm =>Traversals t a b -> (a -> (m, b)) -> s -> (m, t)
(%%=) :: MonadState s m => Over p ((,) r) s s a b -> p a (r, b) -> m r infix 4 Source
Modify the target of a Lens in the current state returning some extra
 information of type r or modify all targets of a
 Traversal in the current state, extracting extra
 information of type r and return a monoidal summary of the changes.
>>>runState (_1 %%= \x -> (f x, g x)) (a,b)(f a,(g a,b))
(%%=) ≡ (state.)
It may be useful to think of (%%=), instead, as having either of the
 following more restricted type signatures:
(%%=) ::MonadStates m =>Isos s a b -> (a -> (r, b)) -> m r (%%=) ::MonadStates m =>Lenss s a b -> (a -> (r, b)) -> m r (%%=) :: (MonadStates m,Monoidr) =>Traversals s a b -> (a -> (r, b)) -> m r
(&) :: a -> (a -> b) -> b infixl 1
(&~) :: s -> State s a -> s infixl 1 Source
This can be used to chain lens operations using op= syntax
 rather than op~ syntax for simple non-type-changing cases.
>>>(10,20) & _1 .~ 30 & _2 .~ 40(30,40)
>>>(10,20) &~ do _1 .= 30; _2 .= 40(30,40)
This does not support type-changing assignment, e.g.
>>>(10,20) & _1 .~ "hello"("hello",20)
(??) :: Functor f => f (a -> b) -> a -> f b infixl 1 Source
This is convenient to flip argument order of composite functions.
>>>over _2 ?? ("hello","world") $ length("hello",5)
>>>over ?? length ?? ("hello","world") $ _2("hello",5)
(<%~) :: Profunctor p => Optical p q ((,) b) s t a b -> p a b -> q s (b, t) infixr 4 Source
(<//~) :: Fractional a => Optical (->) q ((,) a) s t a a -> a -> q s (a, t) infixr 4 Source
Divide the target of a fractionally valued Lens and return the result.
When you do not need the result of the division, (//~) is more flexible.
(<//~) ::Fractionala =>Lens's a -> a -> s -> (a, s) (<//~) ::Fractionala =>Iso's a -> a -> s -> (a, s)
(<^^~) :: (Fractional a, Integral e) => Optical (->) q ((,) a) s t a a -> e -> q s (a, t) infixr 4 Source
Raise the target of a fractionally valued Lens to an Integral power
 and return the result.
When you do not need the result of the operation, (^^~) is more flexible.
(<^^~) :: (Fractionala,Integrale) =>Lens's a -> e -> s -> (a, s) (<^^~) :: (Fractionala,Integrale) =>Iso's a -> e -> s -> (a, s)
(<<+~) :: Num a => Optical' (->) q ((,) a) s a -> a -> q s (a, s) infixr 4 Source
Increment the target of a numerically valued Lens and return the old value.
When you do not need the old value, (+~) is more flexible.
>>>(a,b) & _1 <<+~ c(a,(a + c,b))
>>>(a,b) & _2 <<+~ c(b,(a,b + c))
(<<+~) ::Numa =>Lens's a -> a -> s -> (a, s) (<<+~) ::Numa =>Iso's a -> a -> s -> (a, s)
(<<-~) :: Num a => Optical' (->) q ((,) a) s a -> a -> q s (a, s) infixr 4 Source
Decrement the target of a numerically valued Lens and return the old value.
When you do not need the old value, (-~) is more flexible.
>>>(a,b) & _1 <<-~ c(a,(a - c,b))
>>>(a,b) & _2 <<-~ c(b,(a,b - c))
(<<-~) ::Numa =>Lens's a -> a -> s -> (a, s) (<<-~) ::Numa =>Iso's a -> a -> s -> (a, s)
(<<*~) :: Num a => Optical' (->) q ((,) a) s a -> a -> q s (a, s) infixr 4 Source
Multiply the target of a numerically valued Lens and return the old value.
When you do not need the old value, (-~) is more flexible.
>>>(a,b) & _1 <<*~ c(a,(a * c,b))
>>>(a,b) & _2 <<*~ c(b,(a,b * c))
(<<*~) ::Numa =>Lens's a -> a -> s -> (a, s) (<<*~) ::Numa =>Iso's a -> a -> s -> (a, s)
(<<//~) :: Fractional a => Optical' (->) q ((,) a) s a -> a -> q s (a, s) infixr 4 Source
Divide the target of a numerically valued Lens and return the old value.
When you do not need the old value, (//~) is more flexible.
>>>(a,b) & _1 <<//~ c(a,(a / c,b))
>>>("Hawaii",10) & _2 <<//~ 2(10.0,("Hawaii",5.0))
(<<//~) :: Fractional a =>Lens's a -> a -> s -> (a, s) (<<//~) :: Fractional a =>Iso's a -> a -> s -> (a, s)
(<<^^~) :: (Fractional a, Integral e) => Optical' (->) q ((,) a) s a -> e -> q s (a, s) infixr 4 Source
Raise the target of a fractionally valued Lens to an integral power and return the old value.
When you do not need the old value, (^^~) is more flexible.
(<<^^~) :: (Fractionala,Integrale) =>Lens's a -> e -> s -> (a, s) (<<^^~) :: (Fractionala,Integrale) =>Iso's a -> e -> S -> (a, s)
(<<**~) :: Floating a => Optical' (->) q ((,) a) s a -> a -> q s (a, s) infixr 4 Source
Raise the target of a floating-point valued Lens to an arbitrary power and return the old value.
When you do not need the old value, (**~) is more flexible.
>>>(a,b) & _1 <<**~ c(a,(a**c,b))
>>>(a,b) & _2 <<**~ c(b,(a,b**c))
(<<**~) ::Floatinga =>Lens's a -> a -> s -> (a, s) (<<**~) ::Floatinga =>Iso's a -> a -> s -> (a, s)
(<<||~) :: Optical' (->) q ((,) Bool) s Bool -> Bool -> q s (Bool, s) infixr 4 Source
Logically || the target of a Bool-valued Lens and return the old value.
When you do not need the old value, (||~) is more flexible.
>>>(False,6) & _1 <<||~ True(False,(True,6))
>>>("hello",True) & _2 <<||~ False(True,("hello",True))
(<<||~) ::Lens'sBool->Bool-> s -> (Bool, s) (<<||~) ::Iso'sBool->Bool-> s -> (Bool, s)
(<<&&~) :: Optical' (->) q ((,) Bool) s Bool -> Bool -> q s (Bool, s) infixr 4 Source
Logically && the target of a Bool-valued Lens and return the old value.
When you do not need the old value, (&&~) is more flexible.
>>>(False,6) & _1 <<&&~ True(False,(False,6))
>>>("hello",True) & _2 <<&&~ False(True,("hello",False))
(<<&&~) ::Lens's Bool -> Bool -> s -> (Bool, s) (<<&&~) ::Iso's Bool -> Bool -> s -> (Bool, s)
(<<<>~) :: Monoid r => Optical' (->) q ((,) r) s r -> r -> q s (r, s) infixr 4 Source
Modify the target of a monoidally valued Lens by mappending a new value and return the old value.
When you do not need the old value, (<>~) is more flexible.
>>>(Sum a,b) & _1 <<<>~ Sum c(Sum {getSum = a},(Sum {getSum = a + c},b))
>>>_2 <<<>~ ", 007" $ ("James", "Bond")("Bond",("James","Bond, 007"))
(<<<>~) ::Monoidr =>Lens's r -> r -> s -> (r, s) (<<<>~) ::Monoidr =>Iso's r -> r -> s -> (r, s)
(<%=) :: (Profunctor p, MonadState s m) => Over p ((,) b) s s a b -> p a b -> m b infix 4 Source
Modify the target of a Lens into your Monad's state by a user supplied
 function and return the result.
When applied to a Traversal, it this will return a monoidal summary of all of the intermediate
 results.
When you do not need the result of the operation, (%=) is more flexible.
(<%=) ::MonadStates m =>Lens's a -> (a -> a) -> m a (<%=) ::MonadStates m =>Iso's a -> (a -> a) -> m a (<%=) :: (MonadStates m,Monoida) =>Traversal's a -> (a -> a) -> m a
(<+=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a infix 4 Source
Add to the target of a numerically valued Lens into your Monad's state
 and return the result.
When you do not need the result of the addition, (+=) is more
 flexible.
(<+=) :: (MonadStates m,Numa) =>Lens's a -> a -> m a (<+=) :: (MonadStates m,Numa) =>Iso's a -> a -> m a
(<-=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a infix 4 Source
Subtract from the target of a numerically valued Lens into your Monad's
 state and return the result.
When you do not need the result of the subtraction, (-=) is more
 flexible.
(<-=) :: (MonadStates m,Numa) =>Lens's a -> a -> m a (<-=) :: (MonadStates m,Numa) =>Iso's a -> a -> m a
(<*=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a infix 4 Source
Multiply the target of a numerically valued Lens into your Monad's
 state and return the result.
When you do not need the result of the multiplication, (*=) is more
 flexible.
(<*=) :: (MonadStates m,Numa) =>Lens's a -> a -> m a (<*=) :: (MonadStates m,Numa) =>Iso's a -> a -> m a
(<//=) :: (MonadState s m, Fractional a) => LensLike' ((,) a) s a -> a -> m a infix 4 Source
Divide the target of a fractionally valued Lens into your Monad's state
 and return the result.
When you do not need the result of the division, (//=) is more flexible.
(<//=) :: (MonadStates m,Fractionala) =>Lens's a -> a -> m a (<//=) :: (MonadStates m,Fractionala) =>Iso's a -> a -> m a
(<^=) :: (MonadState s m, Num a, Integral e) => LensLike' ((,) a) s a -> e -> m a infix 4 Source
Raise the target of a numerically valued Lens into your Monad's state
 to a non-negative Integral power and return the result.
When you do not need the result of the operation, (^=) is more flexible.
(<^=) :: (MonadStates m,Numa,Integrale) =>Lens's a -> e -> m a (<^=) :: (MonadStates m,Numa,Integrale) =>Iso's a -> e -> m a
(<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> m a infix 4 Source
Raise the target of a fractionally valued Lens into your Monad's state
 to an Integral power and return the result.
When you do not need the result of the operation, (^^=) is more flexible.
(<^^=) :: (MonadStates m,Fractionalb,Integrale) =>Lens's a -> e -> m a (<^^=) :: (MonadStates m,Fractionalb,Integrale) =>Iso's a -> e -> m a
(<**=) :: (MonadState s m, Floating a) => LensLike' ((,) a) s a -> a -> m a infix 4 Source
Raise the target of a floating-point valued Lens into your Monad's
 state to an arbitrary power and return the result.
When you do not need the result of the operation, (**=) is more flexible.
(<**=) :: (MonadStates m,Floatinga) =>Lens's a -> a -> m a (<**=) :: (MonadStates m,Floatinga) =>Iso's a -> a -> m a
(<<%=) :: (Strong p, MonadState s m) => Over p ((,) a) s s a b -> p a b -> m a infix 4 Source
Modify the target of a Lens into your Monad's state by a user supplied
 function and return the old value that was replaced.
When applied to a Traversal, it this will return a monoidal summary of all of the old values
 present.
When you do not need the result of the operation, (%=) is more flexible.
(<<%=) ::MonadStates m =>Lens's a -> (a -> a) -> m a (<<%=) ::MonadStates m =>Iso's a -> (a -> a) -> m a (<<%=) :: (MonadStates m,Monoidb) =>Traversal's a -> (a -> a) -> m a
(<<%=) ::MonadStates m =>LensLike((,)a) s s a b -> (a -> b) -> m a
(<<.=) :: MonadState s m => LensLike ((,) a) s s a b -> b -> m a infix 4 Source
Replace the target of a Lens into your Monad's state with a user supplied
 value and return the old value that was replaced.
When applied to a Traversal, it this will return a monoidal summary of all of the old values
 present.
When you do not need the result of the operation, (.=) is more flexible.
(<<.=) ::MonadStates m =>Lens's a -> a -> m a (<<.=) ::MonadStates m =>Iso's a -> a -> m a (<<.=) :: (MonadStates m,Monoidt) =>Traversal's a -> a -> m a
(<<+=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a infix 4 Source
Modify the target of a Lens into your Monad's state by adding a value
 and return the old value that was replaced.
When you do not need the result of the operation, (+=) is more flexible.
(<<+=) :: (MonadStates m,Numa) =>Lens's a -> a -> m a (<<+=) :: (MonadStates m,Numa) =>Iso's a -> a -> m a
(<<-=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a infix 4 Source
Modify the target of a Lens into your Monad's state by subtracting a value
 and return the old value that was replaced.
When you do not need the result of the operation, (-=) is more flexible.
(<<-=) :: (MonadStates m,Numa) =>Lens's a -> a -> m a (<<-=) :: (MonadStates m,Numa) =>Iso's a -> a -> m a
(<<*=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a infix 4 Source
Modify the target of a Lens into your Monad's state by multipling a value
 and return the old value that was replaced.
When you do not need the result of the operation, (*=) is more flexible.
(<<*=) :: (MonadStates m,Numa) =>Lens's a -> a -> m a (<<*=) :: (MonadStates m,Numa) =>Iso's a -> a -> m a
(<<//=) :: (MonadState s m, Fractional a) => LensLike' ((,) a) s a -> a -> m a infix 4 Source
Modify the target of a Lens into your Monads state by dividing by a value
 and return the old value that was replaced.
When you do not need the result of the operation, (//=) is more flexible.
(<<//=) :: (MonadStates m,Fractionala) =>Lens's a -> a -> m a (<<//=) :: (MonadStates m,Fractionala) =>Iso's a -> a -> m a
(<<^=) :: (MonadState s m, Num a, Integral e) => LensLike' ((,) a) s a -> e -> m a infix 4 Source
Modify the target of a Lens into your Monad's state by raising it by a non-negative power
 and return the old value that was replaced.
When you do not need the result of the operation, (^=) is more flexible.
(<<^=) :: (MonadStates m,Numa,Integrale) =>Lens's a -> e -> m a (<<^=) :: (MonadStates m,Numa,Integrale) =>Iso's a -> a -> m a
(<<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> m a infix 4 Source
Modify the target of a Lens into your Monad's state by raising it by an integral power
 and return the old value that was replaced.
When you do not need the result of the operation, (^^=) is more flexible.
(<<^^=) :: (MonadStates m,Fractionala,Integrale) =>Lens's a -> e -> m a (<<^^=) :: (MonadStates m,Fractionala,Integrale) =>Iso's a -> e -> m a
(<<**=) :: (MonadState s m, Floating a) => LensLike' ((,) a) s a -> a -> m a infix 4 Source
Modify the target of a Lens into your Monad's state by raising it by an arbitrary power
 and return the old value that was replaced.
When you do not need the result of the operation, (**=) is more flexible.
(<<**=) :: (MonadStates m,Floatinga) =>Lens's a -> a -> m a (<<**=) :: (MonadStates m,Floatinga) =>Iso's a -> a -> m a
(<<||=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool infix 4 Source
Modify the target of a Lens into your Monad's state by taking its logical || with a value
 and return the old value that was replaced.
When you do not need the result of the operation, (||=) is more flexible.
(<<||=) ::MonadStates m =>Lens'sBool->Bool-> mBool(<<||=) ::MonadStates m =>Iso'sBool->Bool-> mBool
(<<&&=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool infix 4 Source
Modify the target of a Lens into your Monad's state by taking its logical && with a value
 and return the old value that was replaced.
When you do not need the result of the operation, (&&=) is more flexible.
(<<&&=) ::MonadStates m =>Lens'sBool->Bool-> mBool(<<&&=) ::MonadStates m =>Iso'sBool->Bool-> mBool
(<<<>=) :: (MonadState s m, Monoid r) => LensLike' ((,) r) s r -> r -> m r infix 4 Source
Modify the target of a Lens into your Monad's state by mappending a value
 and return the old value that was replaced.
When you do not need the result of the operation, (<>=) is more flexible.
(<<<>=) :: (MonadStates m,Monoidr) =>Lens's r -> r -> m r (<<<>=) :: (MonadStates m,Monoidr) =>Iso's r -> r -> m r
(<<~) :: MonadState s m => ALens s s a b -> m b -> m b infixr 2 Source
Run a monadic action, and set the target of Lens to its result.
(<<~) ::MonadStates m =>Isos s a b -> m b -> m b (<<~) ::MonadStates m =>Lenss s a b -> m b -> m b
NB: This is limited to taking an actual Lens than admitting a Traversal because
 there are potential loss of state issues otherwise.
(<%@~) :: Optical (Indexed i) q ((,) b) s t a b -> (i -> a -> b) -> q s (b, t) infixr 4 Source
Adjust the target of an IndexedLens returning the intermediate result, or
 adjust all of the targets of an IndexedTraversal and return a monoidal summary
 along with the answer.
l<%~f ≡ l<%@~constf
When you do not need access to the index then (<%~) is more liberal in what it can accept.
If you do not need the intermediate result, you can use (%@~) or even (%~).
(<%@~) ::IndexedLensi s t a b -> (i -> a -> b) -> s -> (b, t) (<%@~) ::Monoidb =>IndexedTraversali s t a b -> (i -> a -> b) -> s -> (b, t)
(<<%@~) :: Optical (Indexed i) q ((,) a) s t a b -> (i -> a -> b) -> q s (a, t) infixr 4 Source
Adjust the target of an IndexedLens returning the old value, or
 adjust all of the targets of an IndexedTraversal and return a monoidal summary
 of the old values along with the answer.
(<<%@~) ::IndexedLensi s t a b -> (i -> a -> b) -> s -> (a, t) (<<%@~) ::Monoida =>IndexedTraversali s t a b -> (i -> a -> b) -> s -> (a, t)
(%%@~) :: IndexedLensLike i f s t a b -> (i -> a -> f b) -> s -> f t infixr 4 Source
Adjust the target of an IndexedLens returning a supplementary result, or
 adjust all of the targets of an IndexedTraversal and return a monoidal summary
 of the supplementary results and the answer.
(%%@~) ≡withIndex
(%%@~) ::Functorf =>IndexedLensi s t a b -> (i -> a -> f b) -> s -> f t (%%@~) ::Applicativef =>IndexedTraversali s t a b -> (i -> a -> f b) -> s -> f t
In particular, it is often useful to think of this function as having one of these even more restricted type signatures:
(%%@~) ::IndexedLensi s t a b -> (i -> a -> (r, b)) -> s -> (r, t) (%%@~) ::Monoidr =>IndexedTraversali s t a b -> (i -> a -> (r, b)) -> s -> (r, t)
(%%@=) :: MonadState s m => IndexedLensLike i ((,) r) s s a b -> (i -> a -> (r, b)) -> m r infix 4 Source
Adjust the target of an IndexedLens returning a supplementary result, or
 adjust all of the targets of an IndexedTraversal within the current state, and
 return a monoidal summary of the supplementary results.
l%%@=f ≡state(l%%@~f)
(%%@=) ::MonadStates m =>IndexedLensi s s a b -> (i -> a -> (r, b)) -> s -> m r (%%@=) :: (MonadStates m,Monoidr) =>IndexedTraversali s s a b -> (i -> a -> (r, b)) -> s -> m r
(<%@=) :: MonadState s m => IndexedLensLike i ((,) b) s s a b -> (i -> a -> b) -> m b infix 4 Source
Adjust the target of an IndexedLens returning the intermediate result, or
 adjust all of the targets of an IndexedTraversal within the current state, and
 return a monoidal summary of the intermediate results.
(<%@=) ::MonadStates m =>IndexedLensi s s a b -> (i -> a -> b) -> m b (<%@=) :: (MonadStates m,Monoidb) =>IndexedTraversali s s a b -> (i -> a -> b) -> m b
(<<%@=) :: MonadState s m => IndexedLensLike i ((,) a) s s a b -> (i -> a -> b) -> m a infix 4 Source
Adjust the target of an IndexedLens returning the old value, or
 adjust all of the targets of an IndexedTraversal within the current state, and
 return a monoidal summary of the old values.
(<<%@=) ::MonadStates m =>IndexedLensi s s a b -> (i -> a -> b) -> m a (<<%@=) :: (MonadStates m,Monoidb) =>IndexedTraversali s s a b -> (i -> a -> b) -> m a
(#=) :: MonadState s m => ALens s s a b -> b -> m () infix 4 Source
(#%=) :: MonadState s m => ALens s s a b -> (a -> b) -> m () infix 4 Source
(<#%=) :: MonadState s m => ALens s s a b -> (a -> b) -> m b infix 4 Source
(#%%=) :: MonadState s m => ALens s s a b -> (a -> (r, b)) -> m r infix 4 Source
(<#=) :: MonadState s m => ALens s s a b -> b -> m b infix 4 Source
Control.Lens.Plated
(...) :: (Applicative f, Plated c) => LensLike f s t c c -> Over p f c c a b -> Over p f s t a b infixr 9 Source
Compose through a plate
Control.Lens.Review
(#) :: AReview t b -> b -> t infixr 8 Source
An infix alias for review.
untof # x ≡ f x l # x ≡ x^.rel
This is commonly used when using a Prism as a smart constructor.
>>>_Left # 4Left 4
But it can be used for any Prism
>>>base 16 # 123"7b"
(#) ::Iso's a -> a -> s (#) ::Prism's a -> a -> s (#) ::Reviews a -> a -> s (#) ::Equality's a -> a -> s
Control.Lens.Setter
(%~) :: Profunctor p => Setting p s t a b -> p 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
(.~) :: 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 (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)]
(?~) ::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 b -> b -> s -> (b, t) infixr 4 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 -> (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)
(+~) :: 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
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
(-~) :: 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
(//~) :: 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
(&&~) :: 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
(.=) :: 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.
(%=) :: (Profunctor p, MonadState s m) => Setting p s s a b -> p 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 => 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, 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,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 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 => 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
   ...
(<.=) :: 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 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
(<>~) :: Monoid a => ASetter s t a a -> a -> s -> t infixr 4 Source
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
(<>=) :: (MonadState s m, Monoid a) => ASetter' s a -> a -> m () infix 4 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 ()
(%@~) :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t infixr 4 Source
Adjust every target of an IndexedSetter, IndexedLens or IndexedTraversal
 with access to the index.
(%@~) ≡iover
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 () infix 4 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 ()