adjunctions-4.2.2: Adjunctions and representable functors

Copyright(c) Edward Kmett & Sjoerd Visscher 2011
LicenseBSD3
Maintainerekmett@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

Control.Monad.Representable.State

Description

A generalized State monad, parameterized by a Representable functor. The representation of that functor serves as the state.

Synopsis

Documentation

type State g = StateT g Identity Source

A memoized state monad parameterized by a representable functor g, where the representatation of g, Rep g is 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.

runState Source

Arguments

:: Representable g 
=> State g a

state-passing computation to execute

-> Rep g

initial state

-> (a, Rep g)

return value and final state

Unwrap a state monad computation as a function. (The inverse of state.)

evalState Source

Arguments

:: Representable g 
=> State g a

state-passing computation to execute

-> Rep g

initial value

-> a

return value of the state computation

Evaluate a state computation with the given initial state and return the final value, discarding the final state.

execState Source

Arguments

:: Representable g 
=> State g a

state-passing computation to execute

-> Rep g

initial value

-> Rep g

final state

Evaluate a state computation with the given initial state and return the final state, discarding the final value.

mapState :: Functor g => ((a, Rep g) -> (b, Rep g)) -> State g a -> State g b Source

Map both the return value and final state of a computation using the given function.

newtype StateT g m a Source

A state transformer monad parameterized by:

  • g - A representable functor used to memoize results for a state Rep g
  • 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.

Constructors

StateT 

Fields

getStateT :: g (m (a, Rep g))
 

Instances

stateT :: Representable g => (Rep g -> m (a, Rep g)) -> StateT g m a Source

runStateT :: Representable g => StateT g m a -> Rep g -> m (a, Rep g) Source

evalStateT :: (Representable g, Monad m) => StateT g m a -> Rep g -> m a Source

Evaluate a state computation with the given initial state and return the final value, discarding the final state.

execStateT :: (Representable g, Monad m) => StateT g m a -> Rep g -> m (Rep g) Source

Evaluate a state computation with the given initial state and return the final state, discarding the final value.

mapStateT :: Functor g => (m (a, Rep g) -> n (b, Rep g)) -> StateT g m a -> StateT g n b Source

liftCallCC :: Representable g => ((((a, Rep g) -> m (b, Rep g)) -> m (a, Rep g)) -> m (a, Rep g)) -> ((a -> StateT g m b) -> StateT g m a) -> StateT g m a Source

Uniform lifting of a callCC operation to the new monad. This version rolls back to the original state on entering the continuation.

liftCallCC' :: Representable g => ((((a, Rep g) -> m (b, Rep g)) -> m (a, Rep g)) -> m (a, Rep g)) -> ((a -> StateT g m b) -> StateT g m a) -> StateT g m a 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 laws of a monad transformer.

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

Minimal definition is either both of get and put or just state

Minimal complete definition

Nothing

Methods

get :: m s

Return the state from the internals of the monad.

put :: s -> m ()

Replace the state inside the monad.

state :: (s -> (a, s)) -> m a

Embed a simple state action into the monad.

Instances

MonadState s m => MonadState s (MaybeT m) 
MonadState s m => MonadState s (ListT m) 
MonadState s m => MonadState s (IdentityT m) 
(Functor m, MonadState s m) => MonadState s (Free m) 
(Representable g, Monad m, (~) * (Rep g) s) => MonadState s (StateT g m) 
(Monoid w, MonadState s m) => MonadState s (WriterT w m) 
(Monoid w, MonadState s m) => MonadState s (WriterT w m) 
Monad m => MonadState s (StateT s m) 
Monad m => MonadState s (StateT s m) 
MonadState s m => MonadState s (ReaderT r m) 
(Error e, MonadState s m) => MonadState s (ErrorT e m) 
MonadState s m => MonadState s (ContT r m) 
(Monad m, Monoid w) => MonadState s (RWST r w s m) 
(Monad m, Monoid w) => MonadState s (RWST r w s m)