ether-0.3.0.0: Monad transformers and classes

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Ether.State.Lazy

Contents

Description

Synopsis

MonadState class

class Monad m => MonadState tag s m | m tag -> s where Source

Minimal complete definition

state | get, put

Methods

get :: proxy tag -> m s Source

Return the state from the internals of the monad.

put :: proxy tag -> s -> m () Source

Replace the state inside the monad.

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

Embed a simple state action into the monad.

Instances

MonadState tag s m => MonadState tag s (MaybeT m) 
MonadState tag s m => MonadState tag s (ListT m) 
MonadState tag s m => MonadState tag s (IdentityT m) 
(Monoid w, MonadState tag s m) => MonadState tag s (WriterT w m) 
(Monoid w, MonadState tag s m) => MonadState tag s (WriterT w m) 
MonadState tag s m => MonadState tag s (StateT s' m) 
MonadState tag s m => MonadState tag s (StateT s' m) 
MonadState tag s m => MonadState tag s (ReaderT r m) 
MonadState tag s m => MonadState tag s (ExceptT e m) 
MonadState tag s m => MonadState tag s (ContT r m) 
MonadState tag s m => MonadState tag s (WrappedEther tag' m) 
MonadState tag s m => MonadState tag s (ExceptT tag' e m) 
(Monoid w, MonadState tag s m) => MonadState tag s (WriterT tag' w m) 
MonadState tag s m => MonadState tag s (ReaderT tag' r m) 
MonadState tag s m => MonadState tag s (StateT tag' s' m) 
Monad m => MonadState tag s (StateT tag s m) 
MonadState tag s m => MonadState tag s (StateT tag' s' m) 
Monad m => MonadState tag s (StateT tag s m) 

modify :: MonadState tag s m => proxy tag -> (s -> s) -> m () Source

Modifies the state inside a state monad.

gets :: MonadState tag s m => proxy tag -> (s -> a) -> m a Source

Gets specific component of the state, using a projection function supplied.

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.

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

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