representable-functors-2.1: Representable functors

Stabilityexperimental
Maintainerekmett@gmail.com

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 IdentitySource

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

stateSource

Arguments

:: Representable g 
=> (Key g -> (a, Key g))

pure state transformer

-> State g a

equivalent state-passing computation

Construct a state monad computation from a function. (The inverse of runState.)

runStateSource

Arguments

:: Indexable g 
=> State g a

state-passing computation to execute

-> Key g

initial state

-> (a, Key g)

return value and final state

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

evalStateSource

Arguments

:: Indexable g 
=> State g a

state-passing computation to execute

-> Key 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.

execStateSource

Arguments

:: Indexable g 
=> State g a

state-passing computation to execute

-> Key g

initial value

-> Key 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, Key g) -> (b, Key g)) -> State g a -> State g bSource

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 Key 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, Key g))
 

Instances

stateT :: Representable g => (Key g -> m (a, Key g)) -> StateT g m aSource

runStateT :: Indexable g => StateT g m a -> Key g -> m (a, Key g)Source

evalStateT :: (Indexable g, Monad m) => StateT g m a -> Key g -> m aSource

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

execStateT :: (Indexable g, Monad m) => StateT g m a -> Key g -> m (Key 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, Key g) -> n (b, Key g)) -> StateT g m a -> StateT g n bSource

liftCallCC :: Representable g => ((((a, Key g) -> m (b, Key g)) -> m (a, Key g)) -> m (a, Key g)) -> ((a -> StateT g m b) -> StateT g m a) -> StateT g m aSource

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, Key g) -> m (b, Key g)) -> m (a, Key g)) -> m (a, Key g)) -> ((a -> StateT g m b) -> StateT g m a) -> StateT g m aSource

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.

get :: MonadState s m => m s

Return the state from the internals of the monad.

gets :: MonadState s m => (s -> a) -> m a

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

put :: MonadState s m => s -> m ()

Replace the state inside the monad.

modify :: MonadState s m => (s -> s) -> m ()

Monadic state transformer.

Maps an old state to a new state inside a state monad. The old state is thrown away.

      Main> :t modify ((+1) :: Int -> Int)
      modify (...) :: (MonadState Int a) => a ()

This says that modify (+1) acts over any Monad that is a member of the MonadState class, with an Int state.