ether-0.1.0.0: Monad transformers and classes

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Trans.Ether.State.Strict

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

MonadReader tag r m => MonadReader tag r (StateT tag' s m) Source 
MonadState tag s m => MonadState tag s (StateT tag' s' m) Source 
Monad m => MonadState tag s (StateT tag s m) Source 
MonadExcept tag e m => MonadExcept tag e (StateT tag' s m) Source 
MonadWriter tag w m => MonadWriter tag w (StateT tag' e 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 
MonadTrans (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 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 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.

mapStateT :: proxy tag -> (m (a, s) -> n (b, s)) -> StateT tag s m a -> StateT tag s n b Source

Transform the computation inside a StateT.

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.

Litfing other operations

liftCatch :: proxy tag -> Catch e m (a, s) -> Catch e (StateT tag s m) a Source

Lift a catchE operation to the new monad.

liftCallCC' :: proxy tag -> CallCC m (a, s) (b, s) -> CallCC (StateT tag s m) a b Source

In-situ lifting of a callCC operation to the new monad. This version uses the current state on entering the continuation. It does not satisfy the uniformity property (see Control.Monad.Signatures).

liftListen :: Monad m => proxy tag -> Listen w m (a, s) -> Listen w (StateT tag s m) a Source

Lift a listen operation to the new monad.

liftPass :: Monad m => proxy tag -> Pass w m (a, s) -> Pass w (StateT tag s m) a Source

Lift a pass operation to the new monad.