ether-0.3.1.0: Monad transformers and classes

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Trans.Ether.State.Lazy

Contents

Description

Synopsis

The State monad

type State tag r = StateT tag r Identity Source

The parametrizable state monad.

Computations have access to a mutable state.

The return function leaves the state unchanged, while >>= uses the final state of the first computation as the initial state of the second.

state :: Monad m => proxy tag -> (s -> (a, s)) -> StateT tag s m a Source

Constructor for computations in the state monad (the inverse of runState).

runState :: proxy tag -> State tag s a -> s -> (a, s) Source

Runs a State with the given initial state and returns both the final value and the final state.

evalState :: proxy tag -> State tag s a -> s -> a Source

Runs a State with the given initial state and returns the final value, discarding the final state.

execState :: proxy tag -> State tag s a -> s -> s Source

Runs a State with the given initial state and returns the final state, discarding the final value.

The StateT monad transformer

data StateT tag s m a Source

The state monad transformer.

The return function leaves the state unchanged, while >>= uses the final state of the first computation as the initial state of the second.

Instances

Monad m => MonadState tag s (StateT tag s m) Source 
MonadBase b m => MonadBase b (StateT tag s m) Source 
MonadBaseControl b m => MonadBaseControl b (StateT tag s m) Source 
MonadError e m => MonadError e (StateT tag s m) Source 
MonadReader r m => MonadReader r (StateT tag s m) Source 
MonadState s' m => MonadState s' (StateT tag s m) Source 
MonadWriter w m => MonadWriter w (StateT tag s m) Source 
MFunctor (StateT tag s) Source 
MonadTrans (StateT tag s) Source 
MonadTransControl (StateT tag s) Source 
LiftLocal (StateT tag s) Source 
LiftCallCC (StateT tag s) Source 
LiftPass (StateT tag s) Source 
LiftListen (StateT tag s) Source 
LiftCatch (StateT tag s) Source 
Monad m => Monad (StateT tag s m) Source 
Functor m => Functor (StateT tag s m) Source 
MonadFix m => MonadFix (StateT tag s m) Source 
Monad m => Applicative (StateT tag s m) Source 
MonadPlus m => Alternative (StateT tag s m) Source 
MonadPlus m => MonadPlus (StateT tag s m) Source 
MonadIO m => MonadIO (StateT tag s m) Source 
MonadCont m => MonadCont (StateT tag s m) Source 
Taggable (StateT tag s m) Source 
Tagged (StateT tag s m) tag Source 
Generic (StateT tag s m a) Source 
Newtype (StateT tag s m a) Source 
type StT (StateT tag s) a = StT (StateT s) a Source 
type StT (StateT tag s) a = StT (StateT tag s) a Source 
type Untagged (StateT tag s m) = StateT s m Source 
type Tag (StateT tag s m) = Just * tag Source 
type Inner (StateT tag s m) = Just (* -> *) m Source 
type StM (StateT tag s m) a = ComposeSt (StateT tag s) m a Source 
type Rep (StateT tag s m a) Source 
type O (StateT tag s m a) = GO (Rep (StateT tag s m a)) 

stateT :: proxy tag -> (s -> m (a, s)) -> StateT tag s m a Source

Constructor for computations in the state monad transformer.

runStateT :: proxy tag -> StateT tag s m a -> s -> m (a, s) Source

Runs a StateT with the given initial state and returns both the final value and the final state.

evalStateT :: Monad m => proxy tag -> StateT tag s m a -> s -> m a Source

Runs a StateT with the given initial state and returns the final value, discarding the final state.

execStateT :: Monad m => proxy tag -> StateT tag s m a -> s -> m s Source

Runs a StateT with the given initial state and returns the final state, discarding the final value.

State operations

get :: Monad m => proxy tag -> StateT tag s m s Source

Fetch the current value of the state within the monad.

put :: Monad m => proxy tag -> s -> StateT tag s m () Source

Set the value of the state within the monad.