dunai-0.8.2: Generalised reactive framework supporting classic, arrowized and monadic FRP.
Copyright(c) Ivan Perez and Manuel Baerenz 2016
LicenseBSD3
Maintainerivan.perez@keera.co.uk
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Trans.MSF.State

Description

MSFs with a State monadic layer.

This module contains functions to work with MSFs that include a State monadic layer. This includes functions to create new MSFs that include an additional layer, and functions to flatten that layer out of the MSF's transformer stack.

It is based on the _strict_ state monad Strict, so when combining it with other modules such as mtl's, the strict version has to be included, i.e. Strict instead of State or Lazy.

Synopsis

Documentation

newtype StateT s (m :: Type -> Type) a #

A state transformer monad parameterized by:

  • s - The state.
  • 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

Instances

Instances details
MonadSplit g m => MonadSplit g (StateT s m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getSplit :: StateT s m g #

MonadBase b m => MonadBase b (StateT s m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> StateT s m α #

MonadTrans (StateT s) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

lift :: Monad m => m a -> StateT s m a #

Monad m => Monad (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

(>>=) :: StateT s m a -> (a -> StateT s m b) -> StateT s m b #

(>>) :: StateT s m a -> StateT s m b -> StateT s m b #

return :: a -> StateT s m a #

Functor m => Functor (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

fmap :: (a -> b) -> StateT s m a -> StateT s m b #

(<$) :: a -> StateT s m b -> StateT s m a #

MonadFix m => MonadFix (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

mfix :: (a -> StateT s m a) -> StateT s m a #

MonadFail m => MonadFail (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

fail :: String -> StateT s m a #

(Functor m, Monad m) => Applicative (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

pure :: a -> StateT s m a #

(<*>) :: StateT s m (a -> b) -> StateT s m a -> StateT s m b #

liftA2 :: (a -> b -> c) -> StateT s m a -> StateT s m b -> StateT s m c #

(*>) :: StateT s m a -> StateT s m b -> StateT s m b #

(<*) :: StateT s m a -> StateT s m b -> StateT s m a #

MonadPlus m => MonadPlus (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

mzero :: StateT s m a #

mplus :: StateT s m a -> StateT s m a -> StateT s m a #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

liftIO :: IO a -> StateT s m a #

MonadRandom m => MonadRandom (StateT s m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomR :: Random a => (a, a) -> StateT s m a #

getRandom :: Random a => StateT s m a #

getRandomRs :: Random a => (a, a) -> StateT s m [a] #

getRandoms :: Random a => StateT s m [a] #

MonadInterleave m => MonadInterleave (StateT s m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

interleave :: StateT s m a -> StateT s m a #

Contravariant m => Contravariant (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

contramap :: (a -> b) -> StateT s m b -> StateT s m a #

(>$) :: b -> StateT s m b -> StateT s m a #

(Functor m, MonadPlus m) => Alternative (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

empty :: StateT s m a #

(<|>) :: StateT s m a -> StateT s m a -> StateT s m a #

some :: StateT s m a -> StateT s m [a] #

many :: StateT s m a -> StateT s m [a] #

type State s = StateT s Identity #

A state monad parameterized by the type s of 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 #

Arguments

:: State s a

state-passing computation to execute

-> s

initial state

-> (a, s)

return value and final state

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

evalState #

Arguments

:: State s a

state-passing computation to execute

-> s

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 #

Arguments

:: State s a

state-passing computation to execute

-> s

initial value

-> s

final state

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

mapState :: ((a, s) -> (b, s)) -> State s a -> State s b #

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

withState :: (s -> s) -> State s a -> State s a #

withState f m executes action m on a state modified by applying f.

evalStateT :: Monad m => StateT s m a -> s -> m a #

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

execStateT :: Monad m => StateT s m a -> s -> m s #

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

mapStateT :: (m (a, s) -> n (b, s)) -> StateT s m a -> StateT s n b #

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

withStateT :: forall s (m :: Type -> Type) a. (s -> s) -> StateT s m a -> StateT s m a #

withStateT f m executes action m on a state modified by applying f.

liftCallCC' :: CallCC m (a, s) (b, s) -> CallCC (StateT s m) a b #

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

gets :: forall (m :: Type -> Type) s a. Monad m => (s -> a) -> StateT s m a #

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

modify' :: forall (m :: Type -> Type) s. Monad m => (s -> s) -> StateT s m () #

A variant of modify in which the computation is strict in the new state.

modify :: forall (m :: Type -> Type) s. Monad m => (s -> s) -> StateT s m () #

modify f is an action that updates the state to the result of applying f to the current state.

put :: forall (m :: Type -> Type) s. Monad m => s -> StateT s m () #

put s sets the state within the monad to s.

get :: forall (m :: Type -> Type) s. Monad m => StateT s m s #

Fetch the current value of the state within the monad.

state #

Arguments

:: forall (m :: Type -> Type) s a. Monad m 
=> (s -> (a, s))

pure state transformer

-> StateT s m a

equivalent state-passing computation

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

State MSF running and wrapping

stateS :: (Functor m, Monad m) => MSF m (s, a) (s, b) -> MSF (StateT s m) a b Source #

Build an MSF in the State monad from one that takes the state as an extra input. This is the opposite of runStateS.

runStateS :: (Functor m, Monad m) => MSF (StateT s m) a b -> MSF m (s, a) (s, b) Source #

Build an MSF that takes a state as an extra input from one on the State monad. This is the opposite of stateS.

runStateS_ :: (Functor m, Monad m) => MSF (StateT s m) a b -> s -> MSF m a (s, b) Source #

Build an MSF function that takes a fixed state as additional input, from an MSF in the State monad, and outputs the new state with every transformation step.

runStateS__ :: (Functor m, Monad m) => MSF (StateT s m) a b -> s -> MSF m a b Source #

Build an MSF function that takes a fixed state as additional input, from an MSF in the State monad.