Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- zoom :: Monad m => LensLike' (Zooming m c) s a -> StateT a m c -> StateT s m c
- use :: Monad m => FoldLike a s t a b -> StateT s m a
- uses :: Monad m => FoldLike r s t a b -> (a -> r) -> StateT s m r
- (%=) :: Monad m => ASetter s s a b -> (a -> b) -> StateT s m ()
- assign :: Monad m => ASetter s s a b -> b -> StateT s m ()
- (.=) :: Monad m => ASetter s s a b -> b -> StateT s m ()
- (%%=) :: Monad m => LensLike (Writer c) s s a b -> (a -> (c, b)) -> StateT s m c
- (<~) :: Monad m => ASetter s s a b -> StateT s m b -> StateT s m ()
- (+=) :: (Monad m, Num a) => ASetter' s a -> a -> StateT s m ()
- (-=) :: (Monad m, Num a) => ASetter' s a -> a -> StateT s m ()
- (*=) :: (Monad m, Num a) => ASetter' s a -> a -> StateT s m ()
- (//=) :: (Monad m, Fractional a) => ASetter' s a -> a -> StateT s m ()
- (&&=) :: Monad m => ASetter' s Bool -> Bool -> StateT s m ()
- (||=) :: Monad m => ASetter' s Bool -> Bool -> StateT s m ()
- (<>=) :: (Monad m, Monoid a) => ASetter' s a -> a -> StateT s m ()
- (%!=) :: Monad m => ASetter s s a b -> (a -> b) -> StateT s m ()
- (+!=) :: (Monad m, Num a) => ASetter' s a -> a -> StateT s m ()
- (-!=) :: (Monad m, Num a) => ASetter' s a -> a -> StateT s m ()
- (*!=) :: (Monad m, Num a) => ASetter' s a -> a -> StateT s m ()
- (//!=) :: (Monad m, Fractional a) => ASetter' s a -> a -> StateT s m ()
- (&&!=) :: Monad m => ASetter' s Bool -> Bool -> StateT s m ()
- (||!=) :: Monad m => ASetter' s Bool -> Bool -> StateT s m ()
- (<>!=) :: (Monad m, Monoid a) => ASetter' s a -> a -> StateT s m ()
- data Zooming m c a
- type LensLike f s t a b = (a -> f b) -> s -> f t
- type LensLike' f s a = (a -> f a) -> s -> f s
- type FoldLike r s t a b = LensLike (Constant r) s t a b
- data Constant a (b :: k)
- type ASetter s t a b = LensLike Identity s t a b
- type ASetter' s a = LensLike' Identity s a
- data Identity a
- data StateT s (m :: Type -> Type) a
- type Writer w = WriterT w Identity
Documentation
zoom :: Monad m => LensLike' (Zooming m c) s a -> StateT a m c -> StateT s m c Source #
zoom :: Monad m => Lens' s a -> StateT a m c -> StateT s m c
Lift a stateful operation on a field to a stateful operation on the whole state. This is a good way to call a "subroutine" that only needs access to part of the state.
zoom :: (Monad m, Monoid c) => Traversal' s a -> StateT a m c -> StateT s m c
Run the "subroutine" on each element of the traversal in turn and mconcat
all the results together.
zoom :: Monad m => Traversal' s a -> StateT a m () -> StateT s m ()
Run the "subroutine" on each element the traversal in turn.
use :: Monad m => FoldLike a s t a b -> StateT s m a Source #
use :: Monad m => Getter s t a b -> StateT s m a
Retrieve a field of the state
use :: (Monad m, Monoid a) => Fold s t a b -> StateT s m a
Retrieve a monoidal summary of all the referenced fields from the state
uses :: Monad m => FoldLike r s t a b -> (a -> r) -> StateT s m r Source #
uses :: (Monad m, Monoid r) => Fold s t a b -> (a -> r) -> StateT s m r
Retrieve all the referenced fields from the state and foldMap the results together with f :: a -> r
.
uses :: Monad m => Getter s t a b -> (a -> r) -> StateT s m r
Retrieve a field of the state and pass it through the function f :: a -> r
.
uses l f = f <$> use l
(%=) :: Monad m => ASetter s s a b -> (a -> b) -> StateT s m () infix 4 Source #
Modify a field of the state.
(%%=) :: Monad m => LensLike (Writer c) s s a b -> (a -> (c, b)) -> StateT s m c infix 4 Source #
(%%=) :: Monad m => Lens s s a b -> (a -> (c, b)) -> StateT s m c
Modify a field of the state while returning another value.
(%%=) :: (Monad m, Monoid c) => Traversal s s a b -> (a -> (c, b)) -> StateT s m c
Modify each field of the state and return the mconcat
of the other values.
(<~) :: Monad m => ASetter s s a b -> StateT s m b -> StateT s m () infixr 2 Source #
Set a field of the state using the result of executing a stateful command.
Compound Assignments
(<>=) :: (Monad m, Monoid a) => ASetter' s a -> a -> StateT s m () infixr 4 Source #
Monoidally append a value to all referenced fields of the state.
Strict Assignments
(%!=) :: Monad m => ASetter s s a b -> (a -> b) -> StateT s m () infix 4 Source #
Strictly modify a field of the state.
Types
Re-exports
Constant functor.
Instances
Identity functor and monad. (a non-strict monad)
Since: base-4.8.0.0
Instances
data StateT s (m :: Type -> Type) a #
A state transformer monad parameterized by:
s
- The state.m
- The inner monad.
The return
function leaves the state unchanged, while >>=
uses
the final state of the first computation as the initial state of
the second.
Instances
MonadTrans (StateT s) | |
Defined in Control.Monad.Trans.State.Strict | |
Monad m => Monad (StateT s m) | |
Functor m => Functor (StateT s m) | |
MonadFix m => MonadFix (StateT s m) | |
Defined in Control.Monad.Trans.State.Strict | |
MonadFail m => MonadFail (StateT s m) | |
Defined in Control.Monad.Trans.State.Strict | |
(Functor m, Monad m) => Applicative (StateT s m) | |
Defined in Control.Monad.Trans.State.Strict | |
Contravariant m => Contravariant (StateT s m) | |
MonadIO m => MonadIO (StateT s m) | |
Defined in Control.Monad.Trans.State.Strict | |
(Functor m, MonadPlus m) => Alternative (StateT s m) | |
MonadPlus m => MonadPlus (StateT s m) | |