Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Identity a = Identity {
- runIdentity :: a
- type State s = StateT s Identity
- state :: Monad m => (s -> (a, s)) -> StateT s m a
- runState :: State s a -> s -> (a, s)
- evalState :: State s a -> s -> a
- execState :: State s a -> s -> s
- mapState :: ((a, s) -> (b, s)) -> State s a -> State s b
- withState :: (s -> s) -> State s a -> State s a
- newtype StateT s m a = StateT {
- runStateT :: s -> m (a, s)
- evalStateT :: Monad m => StateT s m a -> s -> m a
- execStateT :: Monad m => StateT s m a -> s -> m s
- mapStateT :: (m (a, s) -> n (b, s)) -> StateT s m a -> StateT s n b
- withStateT :: (s -> s) -> StateT s m a -> StateT s m a
- get :: Monad m => StateT s m s
- put :: Monad m => s -> StateT s m ()
- modify :: Monad m => (s -> s) -> StateT s m ()
- modify' :: Monad m => (s -> s) -> StateT s m ()
- gets :: Monad m => (s -> a) -> StateT s m a
Documentation
Identity functor and monad.
Identity | |
|
Instances
Monad Identity Source # | |
Functor Identity Source # | |
MonadFix Identity Source # | |
Defined in Control.NumericalMonad.State.Strict | |
Applicative Identity Source # | |
Foldable Identity Source # | |
Defined in Control.NumericalMonad.State.Strict fold :: Monoid m => Identity m -> m # foldMap :: Monoid m => (a -> m) -> Identity a -> m # foldr :: (a -> b -> b) -> b -> Identity a -> b # foldr' :: (a -> b -> b) -> b -> Identity a -> b # foldl :: (b -> a -> b) -> b -> Identity a -> b # foldl' :: (b -> a -> b) -> b -> Identity a -> b # foldr1 :: (a -> a -> a) -> Identity a -> a # foldl1 :: (a -> a -> a) -> Identity a -> a # elem :: Eq a => a -> Identity a -> Bool # maximum :: Ord a => Identity a -> a # minimum :: Ord a => Identity a -> a # | |
Traversable Identity Source # | |
Defined in Control.NumericalMonad.State.Strict |
type State s = StateT s Identity Source #
A state monad parameterized by the type s
of the state to carry.
The return
function leaves the state unchanged, while >>=
uses
the final state of the first computation as the initial state of
the second.
:: Monad m | |
=> (s -> (a, s)) | pure state transformer |
-> StateT s m a | equivalent state-passing computation |
Construct a state monad computation from a function.
(The inverse of runState
.)
:: State s a | state-passing computation to execute |
-> s | initial state |
-> (a, s) | return value and final state |
Unwrap a state monad computation as a function.
(The inverse of state
.)
:: State s a | state-passing computation to execute |
-> s | initial value |
-> a | return value of the state computation |
:: State s a | state-passing computation to execute |
-> s | initial value |
-> s | final state |
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) Source # | |
Defined in Control.NumericalMonad.State.Strict | |
Monad m => Monad (StateT s m) Source # | |
Functor m => Functor (StateT s m) Source # | |
MonadFix m => MonadFix (StateT s m) Source # | |
Defined in Control.NumericalMonad.State.Strict | |
(Functor m, Monad m) => Applicative (StateT s m) Source # | |
Defined in Control.NumericalMonad.State.Strict | |
MonadIO m => MonadIO (StateT s m) Source # | |
Defined in Control.NumericalMonad.State.Strict | |
(Functor m, MonadPlus m) => Alternative (StateT s m) Source # | |
MonadPlus m => MonadPlus (StateT s m) Source # | |
evalStateT :: Monad m => StateT s m a -> s -> m a Source #
Evaluate a state computation with the given initial state and return the final value, discarding the final state.
evalStateT
m s =liftM
fst
(runStateT
m s)
execStateT :: Monad m => StateT s m a -> s -> m s Source #
Evaluate a state computation with the given initial state and return the final state, discarding the final value.
execStateT
m s =liftM
snd
(runStateT
m s)
withStateT :: (s -> s) -> StateT s m a -> StateT s m a Source #
executes action withStateT
f mm
on a state modified by
applying f
.
withStateT
f m =modify
f >> m