Portability | non-portable |
---|---|
Stability | experimental |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | None |
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
- (^!) :: Monad m => s -> Acting m a s a -> m a
- (^!!) :: Monad m => s -> Acting m [a] s a -> m [a]
- (^!?) :: Monad m => s -> Acting m (Leftmost a) s a -> m (Maybe a)
- (^@!) :: Monad m => s -> IndexedActing i m (i, a) s a -> m (i, a)
- (^@!!) :: Monad m => s -> IndexedActing i m [(i, a)] s a -> m [(i, a)]
- (^@!?) :: Monad m => s -> IndexedActing i m (Leftmost (i, a)) s a -> m (Maybe (i, a))
- (<|) :: 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
- (<&>) :: 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 s t a 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.Action
(^!) :: Monad m => s -> Acting m a s a -> m aSource
Perform an Action
.
>>>
["hello","world"]^!folded.act putStrLn
hello world
(^!!) :: Monad m => s -> Acting m [a] s a -> m [a]Source
Perform a MonadicFold
and collect all of the results in a list.
>>>
["ab","cd","ef"]^!!folded.acts
["ace","acf","ade","adf","bce","bcf","bde","bdf"]
(^!?) :: Monad m => s -> Acting m (Leftmost a) s a -> m (Maybe a)Source
Perform a MonadicFold
and collect the leftmost result.
Note: this still causes all effects for all elements.
>>>
[Just 1, Just 2, Just 3]^!?folded.acts
Just (Just 1)>>>
[Just 1, Nothing]^!?folded.acts
Nothing
(^@!) :: Monad m => s -> IndexedActing i m (i, a) s a -> m (i, a)Source
Perform an IndexedAction
.
(^@!!) :: Monad m => s -> IndexedActing i m [(i, a)] s a -> m [(i, a)]Source
Obtain a list of all of the results of an IndexedMonadicFold
.
(^@!?) :: Monad m => s -> IndexedActing i m (Leftmost (i, a)) s a -> m (Maybe (i, a))Source
Perform an IndexedMonadicFold
and collect the Leftmost
result.
Note: this still causes all effects for all elements.
Control.Lens.Cons
Control.Lens.Fold
(^..) :: s -> Getting (Endo [a]) s a -> [a]Source
A convenient infix (flipped) version of toListOf
.
>>>
[[1,2],[3]]^..traverse.traverse
[1,2,3]
>>>
(1,2)^..both
[1,2]
toList
xs ≡ xs^..
folded
(^..
) ≡flip
toListOf
(^..
) :: s ->Getter
s a -> [a] (^..
) :: s ->Fold
s 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 aSource
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 ^?_Left
Just 4
>>>
Right 4 ^?_Left
Nothing
>>>
"world" ^? ix 3
Just 'l'
>>>
"world" ^? ix 20
Nothing
(^?
) ≡flip
preview
(^?
) :: s ->Getter
s a ->Maybe
a (^?
) :: s ->Fold
s a ->Maybe
a (^?
) :: s ->Lens'
s a ->Maybe
a (^?
) :: s ->Iso'
s a ->Maybe
a (^?
) :: s ->Traversal'
s a ->Maybe
a
(^@..) :: s -> IndexedGetting i (Endo [(i, a)]) s a -> [(i, a)]Source
An infix version of itoListOf
.
(^@?) :: s -> IndexedGetting i (Endo (Maybe (i, a))) s a -> Maybe (i, a)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 ->IndexedGetter
i s a ->Maybe
(i, a) (^@?
) :: s ->IndexedFold
i 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)Source
Perform an *UNSAFE* head
(with index) of an IndexedFold
or IndexedTraversal
assuming that it is there.
(^@?!
) :: s ->IndexedGetter
i s a -> (i, a) (^@?!
) :: s ->IndexedFold
i 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 -> aSource
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)^._2
b
>>>
("hello","world")^._2
"world"
>>>
import Data.Complex
>>>
((0, 1 :+ 2), 3)^._1._2.to magnitude
2.23606797749979
(^.
) :: s ->Getter
s a -> a (^.
) ::Monoid
m => s ->Fold
s m -> m (^.
) :: s ->Iso'
s a -> a (^.
) :: s ->Lens'
s a -> a (^.
) ::Monoid
m => s ->Traversal'
s m -> m
(^@.) :: s -> IndexedGetting i (i, a) s a -> (i, a)Source
View the value pointed to by a Getter
or Lens
.
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 ->IndexedGetter
i 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 -> rSource
Compose an Indexed
function with a non-indexed function.
Mnemonically, the <
points to the indexing we want to preserve.
(<.>) :: Indexable (i, j) p => (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> p a b -> rSource
Composition of Indexed
functions.
Mnemonically, the <
and >
points to the fact that we want to preserve the indices.
Control.Lens.Lens
(%%~) :: Optical p q f s t a b -> p a (f b) -> q s (f t)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:
(%%~
) ::Functor
f =>Iso
s t a b -> (a -> f b) -> s -> f t (%%~
) ::Functor
f =>Lens
s t a b -> (a -> f b) -> s -> f t (%%~
) ::Applicative
f =>Traversal
s 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)
(%%~
) ::Iso
s t a b -> (a -> (r, b)) -> s -> (r, t) (%%~
) ::Lens
s t a b -> (a -> (r, b)) -> s -> (r, t) (%%~
) ::Monoid
m =>Traversal
s t a b -> (a -> (m, b)) -> s -> (m, t)
(%%=) :: MonadState s m => Over p ((,) r) s s a b -> p a (r, b) -> m rSource
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:
(%%=
) ::MonadState
s m =>Iso
s s a b -> (a -> (r, b)) -> m r (%%=
) ::MonadState
s m =>Lens
s s a b -> (a -> (r, b)) -> m r (%%=
) :: (MonadState
s m,Monoid
r) =>Traversal
s s a b -> (a -> (r, b)) -> m r
(&) :: a -> (a -> b) -> bSource
Passes the result of the left side to the function on the right side (forward pipe operator).
This is the flipped version of ($
), which is more common in languages like F# as (|>
) where it is needed
for inference. Here it is supplied for notational convenience and given a precedence that allows it
to be nested inside uses of ($
).
>>>
a & f
f a
>>>
"hello" & length & succ
6
This combinator is commonly used when applying multiple Lens
operations in sequence.
>>>
("hello","world") & _1.element 0 .~ 'j' & _1.element 4 .~ 'y'
("jelly","world")
This reads somewhat similar to:
>>>
flip execState ("hello","world") $ do _1.element 0 .= 'j'; _1.element 4 .= 'y'
("jelly","world")
(??) :: Functor f => f (a -> b) -> a -> f bSource
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)Source
(<//~) :: Fractional a => Optical (->) q ((,) a) s t a a -> a -> q s (a, t)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.
(<//~
) ::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 t a a -> e -> q s (a, t)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.
(<^^~
) :: (Fractional
a,Integral
e) =>Lens'
s a -> e -> s -> (a, s) (<^^~
) :: (Fractional
a,Integral
e) =>Iso'
s a -> e -> s -> (a, s)
(<<//~) :: Fractional a => Optical' (->) q ((,) a) s a -> a -> q s (a, s)Source
(<%=) :: (Profunctor p, MonadState s m) => Over p ((,) b) s s a b -> p a b -> m bSource
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.
(<%=
) ::MonadState
s m =>Lens'
s a -> (a -> a) -> m a (<%=
) ::MonadState
s m =>Iso'
s a -> (a -> a) -> m a (<%=
) :: (MonadState
s m,Monoid
a) =>Traversal'
s a -> (a -> a) -> m a
(<+=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m aSource
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.
(<+=
) :: (MonadState
s m,Num
a) =>Lens'
s a -> a -> m a (<+=
) :: (MonadState
s m,Num
a) =>Iso'
s a -> a -> m a
(<-=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m aSource
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.
(<-=
) :: (MonadState
s m,Num
a) =>Lens'
s a -> a -> m a (<-=
) :: (MonadState
s m,Num
a) =>Iso'
s a -> a -> m a
(<*=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m aSource
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.
(<*=
) :: (MonadState
s m,Num
a) =>Lens'
s a -> a -> m a (<*=
) :: (MonadState
s m,Num
a) =>Iso'
s a -> a -> m a
(<//=) :: (MonadState s m, Fractional a) => LensLike' ((,) a) s a -> a -> m aSource
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.
(<//=
) :: (MonadState
s m,Fractional
a) =>Lens'
s a -> a -> m a (<//=
) :: (MonadState
s m,Fractional
a) =>Iso'
s a -> a -> m a
(<^=) :: (MonadState s m, Num a, Integral e) => LensLike' ((,) a) s a -> e -> m aSource
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.
(<^=
) :: (MonadState
s m,Num
a,Integral
e) =>Lens'
s a -> e -> m a (<^=
) :: (MonadState
s m,Num
a,Integral
e) =>Iso'
s a -> e -> m a
(<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> m aSource
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.
(<^^=
) :: (MonadState
s m,Fractional
b,Integral
e) =>Lens'
s a -> e -> m a (<^^=
) :: (MonadState
s m,Fractional
b,Integral
e) =>Iso'
s a -> e -> m a
(<**=) :: (MonadState s m, Floating a) => LensLike' ((,) a) s a -> a -> m aSource
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.
(<**=
) :: (MonadState
s m,Floating
a) =>Lens'
s a -> a -> m a (<**=
) :: (MonadState
s m,Floating
a) =>Iso'
s a -> a -> m a
(<<%=) :: (Strong p, MonadState s m) => Over p ((,) a) s s a b -> p a b -> m aSource
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.
(<<%=
) ::MonadState
s m =>Lens'
s a -> (a -> a) -> m a (<<%=
) ::MonadState
s m =>Iso'
s a -> (a -> a) -> m a (<<%=
) :: (MonadState
s m,Monoid
b) =>Traversal'
s a -> (a -> a) -> m a
(<<%=
) ::MonadState
s m =>LensLike
((,)a) s s a b -> (a -> b) -> m a
(<<.=) :: MonadState s m => LensLike ((,) a) s s a b -> b -> m aSource
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.
(<<.=
) ::MonadState
s m =>Lens'
s a -> a -> m a (<<.=
) ::MonadState
s m =>Iso'
s a -> a -> m a (<<.=
) :: (MonadState
s m,Monoid
t) =>Traversal'
s a -> a -> m a
(<<//=) :: (MonadState s m, Fractional a) => LensLike' ((,) a) s a -> a -> m aSource
(<<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> m aSource
(<<~) :: MonadState s m => ALens s s a b -> m b -> m bSource
Run a monadic action, and set the target of Lens
to its result.
(<<~
) ::MonadState
s m =>Iso
s s a b -> m b -> m b (<<~
) ::MonadState
s m =>Lens
s 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)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<%@~
const
f
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 (%~
).
(<%@~
) ::IndexedLens
i s t a b -> (i -> a -> b) -> s -> (b, t) (<%@~
) ::Monoid
b =>IndexedTraversal
i 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)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.
(<<%@~
) ::IndexedLens
i s t a b -> (i -> a -> b) -> s -> (a, t) (<<%@~
) ::Monoid
a =>IndexedTraversal
i s t a b -> (i -> a -> b) -> s -> (a, t)
(%%@~) :: IndexedLensLike i f s t a b -> (i -> a -> f b) -> s -> f tSource
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
(%%@~
) ::Functor
f =>IndexedLens
i s t a b -> (i -> a -> f b) -> s -> f t (%%@~
) ::Applicative
f =>IndexedTraversal
i 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:
(%%@~
) ::IndexedLens
i s t a b -> (i -> a -> (r, b)) -> s -> (r, t) (%%@~
) ::Monoid
r =>IndexedTraversal
i 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 rSource
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)
(%%@=
) ::MonadState
s m =>IndexedLens
i s s a b -> (i -> a -> (r, b)) -> s -> m r (%%@=
) :: (MonadState
s m,Monoid
r) =>IndexedTraversal
i 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 bSource
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.
(<%@=
) ::MonadState
s m =>IndexedLens
i s s a b -> (i -> a -> b) -> m b (<%@=
) :: (MonadState
s m,Monoid
b) =>IndexedTraversal
i s s a b -> (i -> a -> b) -> m b
(<<%@=) :: MonadState s m => IndexedLensLike i ((,) a) s s a b -> (i -> a -> b) -> m aSource
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.
(<<%@=
) ::MonadState
s m =>IndexedLens
i s s a b -> (i -> a -> b) -> m a (<<%@=
) :: (MonadState
s m,Monoid
b) =>IndexedTraversal
i s s a b -> (i -> a -> b) -> m a
(#%=) :: MonadState s m => ALens s s a b -> (a -> b) -> m ()Source
(<#%=) :: MonadState s m => ALens s s a b -> (a -> b) -> m bSource
(#%%=) :: MonadState s m => ALens s s a b -> (a -> (r, b)) -> m rSource
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 bSource
Compose through a plate
Control.Lens.Review
(#) :: AReview s t a b -> b -> tSource
An infix alias for review
.
unto
f # x ≡ f x l # x ≡ x^.
re
l
This is commonly used when using a Prism
as a smart constructor.
>>>
_Left # 4
Left 4
But it can be used for any Prism
>>>
base 16 # 123
"7b"
(#) ::Iso'
s a -> a -> s (#) ::Prism'
s a -> a -> s (#) ::Review'
s a -> a -> s (#) ::Equality'
s a -> a -> s
Control.Lens.Setter
(%~) :: 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
.
fmap
f ≡mapped
%~
ffmapDefault
f ≡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]]
(%~
) ::Setter
s t a b -> (a -> b) -> s -> t (%~
) ::Iso
s t a b -> (a -> b) -> s -> t (%~
) ::Lens
s t a b -> (a -> b) -> s -> t (%~
) ::Traversal
s t a b -> (a -> 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)
(.~
) ::Setter
s t a b -> b -> s -> t (.~
) ::Iso
s t a b -> b -> s -> t (.~
) ::Lens
s t a b -> b -> s -> t (.~
) ::Traversal
s t a b -> b -> s -> 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 ≡set
l (Just
t)
>>>
Nothing & id ?~ a
Just a
>>>
Map.empty & at 3 ?~ x
fromList [(3,x)]
(?~
) ::Setter
s t a (Maybe
b) -> b -> s -> t (?~
) ::Iso
s t a (Maybe
b) -> b -> s -> t (?~
) ::Lens
s t a (Maybe
b) -> b -> s -> t (?~
) ::Traversal
s t a (Maybe
b) -> b -> s -> t
(<.~) :: 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")]))
(<.~
) ::Setter
s t a b -> b -> s -> (b, t) (<.~
) ::Iso
s t a b -> b -> s -> (b, t) (<.~
) ::Lens
s t a b -> b -> s -> (b, t) (<.~
) ::Traversal
s t a b -> b -> s -> (b, 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")]))
(<?~
) ::Setter
s t a (Maybe
b) -> b -> s -> (b, t) (<?~
) ::Iso
s t a (Maybe
b) -> b -> s -> (b, t) (<?~
) ::Lens
s t a (Maybe
b) -> b -> s -> (b, t) (<?~
) ::Traversal
s t a (Maybe
b) -> b -> s -> (b, 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)]
(+~
) ::Num
a =>Setter'
s a -> a -> s -> s (+~
) ::Num
a =>Iso'
s a -> a -> s -> s (+~
) ::Num
a =>Lens'
s a -> a -> s -> s (+~
) ::Num
a =>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 *~ 2
Just 48
(*~
) ::Num
a =>Setter'
s a -> a -> s -> s (*~
) ::Num
a =>Iso'
s a -> a -> s -> s (*~
) ::Num
a =>Lens'
s a -> a -> s -> s (*~
) ::Num
a =>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]]
(-~
) ::Num
a =>Setter'
s a -> a -> s -> s (-~
) ::Num
a =>Iso'
s a -> a -> s -> s (-~
) ::Num
a =>Lens'
s a -> a -> s -> s (-~
) ::Num
a =>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)
(//~
) ::Fractional
a =>Setter'
s a -> a -> s -> s (//~
) ::Fractional
a =>Iso'
s a -> a -> s -> s (//~
) ::Fractional
a =>Lens'
s a -> a -> s -> s (//~
) ::Fractional
a =>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)
(^~
) :: (Num
a,Integral
e) =>Setter'
s a -> e -> s -> s (^~
) :: (Num
a,Integral
e) =>Iso'
s a -> e -> s -> s (^~
) :: (Num
a,Integral
e) =>Lens'
s a -> e -> s -> s (^~
) :: (Num
a,Integral
e) =>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)
(^^~
) :: (Fractional
a,Integral
e) =>Setter'
s a -> e -> s -> s (^^~
) :: (Fractional
a,Integral
e) =>Iso'
s a -> e -> s -> s (^^~
) :: (Fractional
a,Integral
e) =>Lens'
s a -> e -> s -> s (^^~
) :: (Fractional
a,Integral
e) =>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 **~ 10 $ (3,2)
(3,1024.0)
(**~
) ::Floating
a =>Setter'
s a -> a -> s -> s (**~
) ::Floating
a =>Iso'
s a -> a -> s -> s (**~
) ::Floating
a =>Lens'
s a -> a -> s -> s (**~
) ::Floating
a =>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
(&&~) :: 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
(.=) :: 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)
(.=
) ::MonadState
s m =>Iso'
s a -> a -> m () (.=
) ::MonadState
s m =>Lens'
s a -> a -> m () (.=
) ::MonadState
s m =>Traversal'
s a -> a -> m () (.=
) ::MonadState
s 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 ()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)
(%=
) ::MonadState
s m =>Iso'
s a -> (a -> a) -> m () (%=
) ::MonadState
s m =>Lens'
s a -> (a -> a) -> m () (%=
) ::MonadState
s m =>Traversal'
s a -> (a -> a) -> m () (%=
) ::MonadState
s m =>Setter'
s a -> (a -> a) -> m ()
(%=
) ::MonadState
s m =>ASetter
s s a b -> (a -> b) -> m ()
(?=) :: 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.empty
fromList [(1,a),(2,b)]
>>>
execState (do _1 ?= b; _2 ?= c) (Just a, Nothing)
(Just b,Just c)
(?=
) ::MonadState
s m =>Iso'
s (Maybe
a) -> a -> m () (?=
) ::MonadState
s m =>Lens'
s (Maybe
a) -> a -> m () (?=
) ::MonadState
s m =>Traversal'
s (Maybe
a) -> a -> m () (?=
) ::MonadState
s m =>Setter'
s (Maybe
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 adding a value.
Example:
fresh
::MonadState
Int
m => mInt
fresh
= doid
+=
1use
id
>>>
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")
(+=
) :: (MonadState
s m,Num
a) =>Setter'
s a -> a -> m () (+=
) :: (MonadState
s m,Num
a) =>Iso'
s a -> a -> m () (+=
) :: (MonadState
s m,Num
a) =>Lens'
s a -> a -> m () (+=
) :: (MonadState
s m,Num
a) =>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)
(-=
) :: (MonadState
s m,Num
a) =>Setter'
s a -> a -> m () (-=
) :: (MonadState
s m,Num
a) =>Iso'
s a -> a -> m () (-=
) :: (MonadState
s m,Num
a) =>Lens'
s a -> a -> m () (-=
) :: (MonadState
s m,Num
a) =>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)
(*=
) :: (MonadState
s m,Num
a) =>Setter'
s a -> a -> m () (*=
) :: (MonadState
s m,Num
a) =>Iso'
s a -> a -> m () (*=
) :: (MonadState
s m,Num
a) =>Lens'
s a -> a -> m () (*=
) :: (MonadState
s m,Num
a) =>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)
(//=
) :: (MonadState
s m,Fractional
a) =>Setter'
s a -> a -> m () (//=
) :: (MonadState
s m,Fractional
a) =>Iso'
s a -> a -> m () (//=
) :: (MonadState
s m,Fractional
a) =>Lens'
s a -> a -> m () (//=
) :: (MonadState
s m,Fractional
a) =>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.
(^=
) :: (MonadState
s m,Num
a,Integral
e) =>Setter'
s a -> e -> m () (^=
) :: (MonadState
s m,Num
a,Integral
e) =>Iso'
s a -> e -> m () (^=
) :: (MonadState
s m,Num
a,Integral
e) =>Lens'
s a -> e -> m () (^=
) :: (MonadState
s m,Num
a,Integral
e) =>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.
(^^=
) :: (MonadState
s m,Fractional
a,Integral
e) =>Setter'
s a -> e -> m () (^^=
) :: (MonadState
s m,Fractional
a,Integral
e) =>Iso'
s a -> e -> m () (^^=
) :: (MonadState
s m,Fractional
a,Integral
e) =>Lens'
s a -> e -> m () (^^=
) :: (MonadState
s m,Fractional
a,Integral
e) =>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)
(**=
) :: (MonadState
s m,Floating
a) =>Setter'
s a -> a -> m () (**=
) :: (MonadState
s m,Floating
a) =>Iso'
s a -> a -> m () (**=
) :: (MonadState
s m,Floating
a) =>Lens'
s a -> a -> m () (**=
) :: (MonadState
s m,Floating
a) =>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)
(&&=
) ::MonadState
s m =>Setter'
sBool
->Bool
-> m () (&&=
) ::MonadState
s m =>Iso'
sBool
->Bool
-> m () (&&=
) ::MonadState
s m =>Lens'
sBool
->Bool
-> m () (&&=
) ::MonadState
s m =>Traversal'
sBool
->Bool
-> 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)
(||=
) ::MonadState
s m =>Setter'
sBool
->Bool
-> m () (||=
) ::MonadState
s m =>Iso'
sBool
->Bool
-> m () (||=
) ::MonadState
s m =>Lens'
sBool
->Bool
-> m () (||=
) ::MonadState
s m =>Traversal'
sBool
->Bool
-> m ()
(<~) :: 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.
(<~
) ::MonadState
s m =>Iso
s s a b -> m b -> m () (<~
) ::MonadState
s m =>Lens
s s a b -> m b -> m () (<~
) ::MonadState
s m =>Traversal
s s a b -> m b -> m () (<~
) ::MonadState
s m =>Setter
s 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 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
(<.=
) ::MonadState
s m =>Setter
s s a b -> b -> m b (<.=
) ::MonadState
s m =>Iso
s s a b -> b -> m b (<.=
) ::MonadState
s m =>Lens
s s a b -> b -> m b (<.=
) ::MonadState
s m =>Traversal
s s a b -> b -> m b
(<?=) :: 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 <-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
(<?=
) ::MonadState
s m =>Setter
s s a (Maybe
b) -> b -> m b (<?=
) ::MonadState
s m =>Iso
s s a (Maybe
b) -> b -> m b (<?=
) ::MonadState
s m =>Lens
s s a (Maybe
b) -> b -> m b (<?=
) ::MonadState
s m =>Traversal
s s a (Maybe
b) -> b -> m b
(<>~) :: Monoid a => ASetter s t a a -> a -> s -> tSource
Modify the target of a monoidally valued by mappend
ing 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!!!")
(<>~
) ::Monoid
a =>Setter
s t a a -> a -> s -> t (<>~
) ::Monoid
a =>Iso
s t a a -> a -> s -> t (<>~
) ::Monoid
a =>Lens
s t a a -> a -> s -> t (<>~
) ::Monoid
a =>Traversal
s t a a -> a -> s -> t
(<>=) :: (MonadState s m, Monoid a) => ASetter' s a -> a -> m ()Source
Modify the target(s) of a Lens'
, Iso
, Setter
or Traversal
by mappend
ing 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!!!")
(<>=
) :: (MonadState
s m,Monoid
a) =>Setter'
s a -> a -> m () (<>=
) :: (MonadState
s m,Monoid
a) =>Iso'
s a -> a -> m () (<>=
) :: (MonadState
s m,Monoid
a) =>Lens'
s a -> a -> m () (<>=
) :: (MonadState
s m,Monoid
a) =>Traversal'
s a -> a -> m ()
(%@~) :: 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%@~
const
f
(%@~
) ::IndexedSetter
i s t a b -> (i -> a -> b) -> s -> t (%@~
) ::IndexedLens
i s t a b -> (i -> a -> b) -> s -> t (%@~
) ::IndexedTraversal
i 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%@=
const
f
(%@=
) ::MonadState
s m =>IndexedSetter
i s s a b -> (i -> a -> b) -> m () (%@=
) ::MonadState
s m =>IndexedLens
i s s a b -> (i -> a -> b) -> m () (%@=
) ::MonadState
s m =>IndexedTraversal
i s t a b -> (i -> a -> b) -> m ()