Safe Haskell | None |
---|---|
Language | Haskell2010 |
Defines infix operators for the operations in Optics.State. These
operators are not exposed by the main Optics
module, but must be imported
explicitly.
Synopsis
- (.=) :: (Is k A_Setter, MonadState s m) => Optic k is s s a b -> b -> m ()
- (?=) :: (Is k A_Setter, MonadState s m) => Optic k is s s (Maybe a) (Maybe b) -> b -> m ()
- (%=) :: (Is k A_Setter, MonadState s m) => Optic k is s s a b -> (a -> b) -> m ()
- (%%=) :: (PermeableOptic k r, MonadState s m) => Optic k is s s a b -> (a -> (r, b)) -> m (ViewResult k r)
- (<.=) :: (PermeableOptic k b, MonadState s m) => Optic k is s s a b -> b -> m (ViewResult k b)
- (<?=) :: (PermeableOptic k (Maybe b), MonadState s m) => Optic k is s s (Maybe a) (Maybe b) -> b -> m (ViewResult k (Maybe b))
- (<%=) :: (PermeableOptic k b, MonadState s m) => Optic k is s s a b -> (a -> b) -> m (ViewResult k b)
- (<<.=) :: (PermeableOptic k a, MonadState s m) => Optic k is s s a b -> b -> m (ViewResult k a)
- (<<?=) :: (PermeableOptic k (Maybe a), MonadState s m) => Optic k is s s (Maybe a) (Maybe b) -> b -> m (ViewResult k (Maybe a))
- (<<%=) :: (PermeableOptic k a, MonadState s m) => Optic k is s s a b -> (a -> b) -> m (ViewResult k a)
- class (Is k A_Traversal, ViewableOptic k r) => PermeableOptic k r where
- passthrough :: Optic k is s t a b -> (a -> (r, b)) -> s -> (ViewResult k r, t)
State modifying optics
(?=) :: (Is k A_Setter, MonadState s m) => Optic k is s s (Maybe a) (Maybe b) -> b -> m () infix 4 Source #
State modifying optics with passthrough
(%%=) :: (PermeableOptic k r, MonadState s m) => Optic k is s s a b -> (a -> (r, b)) -> m (ViewResult k r) infix 4 Source #
Modify the target of an PermeableOptic
in the current state returning
some extra information of type depending on the optic (r
, Maybe r
or
monoidal summary).
Returning new value
(<.=) :: (PermeableOptic k b, MonadState s m) => Optic k is s s a b -> b -> m (ViewResult k b) infix 4 Source #
Set with pass-through.
This is useful for chaining assignment without round-tripping through your
Monad
stack.
(<?=) :: (PermeableOptic k (Maybe b), MonadState s m) => Optic k is s s (Maybe a) (Maybe b) -> b -> m (ViewResult k (Maybe b)) infix 4 Source #
(<%=) :: (PermeableOptic k b, MonadState s m) => Optic k is s s a b -> (a -> b) -> m (ViewResult k b) infix 4 Source #
Modify the target of a PermeableOptic
into your Monad'
s state by a user
supplied function and return the result.
Returning old value
(<<.=) :: (PermeableOptic k a, MonadState s m) => Optic k is s s a b -> b -> m (ViewResult k a) infix 4 Source #
Replace the target of a PermeableOptic
into your Monad'
s state with a
user supplied value and return the old value that was replaced.
(<<?=) :: (PermeableOptic k (Maybe a), MonadState s m) => Optic k is s s (Maybe a) (Maybe b) -> b -> m (ViewResult k (Maybe a)) infix 4 Source #
Replace the target of a PermeableOptic
into your Monad'
s state with
Just
a user supplied value and return the old value that was replaced.
(<<%=) :: (PermeableOptic k a, MonadState s m) => Optic k is s s a b -> (a -> b) -> m (ViewResult k a) infix 4 Source #
Modify the target of a PermeableOptic
into your Monad'
s state by a user
supplied function and return the old value that was replaced.
Passthrough
class (Is k A_Traversal, ViewableOptic k r) => PermeableOptic k r where Source #
passthrough :: Optic k is s t a b -> (a -> (r, b)) -> s -> (ViewResult k r, t) Source #
Modify the target of an Optic
returning extra information of type r
.