dunai-0.6.0: Generalised reactive framework supporting classic, arrowized and monadic FRP.

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Trans.MSF.RWS

Description

This module combines the wrapping and running functions for the Reader, Writer and State monad layers in a single layer.

It is based on the _strict_ RWS 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 RWS or Lazy.

Synopsis

Documentation

rwsS :: (Functor m, Monad m, Monoid w) => MSF m (r, s, a) (w, s, b) -> MSF (RWST r w s m) a b Source #

Wrap an MSF with explicit state variables in RWST monad.

runRWSS :: (Functor m, Monad m, Monoid w) => MSF (RWST r w s m) a b -> MSF m (r, s, a) (w, s, b) Source #

Run the RWST layer by making the state variables explicit.

newtype RWST r w s (m :: Type -> Type) a #

A monad transformer adding reading an environment of type r, collecting an output of type w and updating a state of type s to an inner monad m.

Constructors

RWST 

Fields

Instances
(Monoid w, MonadSplit g m) => MonadSplit g (RWST r w s m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getSplit :: RWST r w s m g #

(Monoid w, MonadBase b m) => MonadBase b (RWST r w s m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> RWST r w s m α #

Monoid w => MonadTrans (RWST r w s) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

lift :: Monad m => m a -> RWST r w s m a #

(Monoid w, Monad m) => Monad (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

(>>=) :: RWST r w s m a -> (a -> RWST r w s m b) -> RWST r w s m b #

(>>) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m b #

return :: a -> RWST r w s m a #

fail :: String -> RWST r w s m a #

Functor m => Functor (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

fmap :: (a -> b) -> RWST r w s m a -> RWST r w s m b #

(<$) :: a -> RWST r w s m b -> RWST r w s m a #

(Monoid w, MonadFix m) => MonadFix (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

mfix :: (a -> RWST r w s m a) -> RWST r w s m a #

(Monoid w, MonadFail m) => MonadFail (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

fail :: String -> RWST r w s m a #

(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

pure :: a -> RWST r w s m a #

(<*>) :: RWST r w s m (a -> b) -> RWST r w s m a -> RWST r w s m b #

liftA2 :: (a -> b -> c) -> RWST r w s m a -> RWST r w s m b -> RWST r w s m c #

(*>) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m b #

(<*) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m a #

(Monoid w, MonadPlus m) => MonadPlus (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

mzero :: RWST r w s m a #

mplus :: RWST r w s m a -> RWST r w s m a -> RWST r w s m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

liftIO :: IO a -> RWST r w s m a #

(Monoid w, MonadRandom m) => MonadRandom (RWST r w s m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomR :: Random a => (a, a) -> RWST r w s m a #

getRandom :: Random a => RWST r w s m a #

getRandomRs :: Random a => (a, a) -> RWST r w s m [a] #

getRandoms :: Random a => RWST r w s m [a] #

(Monoid w, MonadInterleave m) => MonadInterleave (RWST r w s m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

interleave :: RWST r w s m a -> RWST r w s m a #

Contravariant m => Contravariant (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

contramap :: (a -> b) -> RWST r w s m b -> RWST r w s m a #

(>$) :: b -> RWST r w s m b -> RWST r w s m a #

(Monoid w, Functor m, MonadPlus m) => Alternative (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

empty :: RWST r w s m a #

(<|>) :: RWST r w s m a -> RWST r w s m a -> RWST r w s m a #

some :: RWST r w s m a -> RWST r w s m [a] #

many :: RWST r w s m a -> RWST r w s m [a] #

type RWS r w s = RWST r w s Identity #

A monad containing an environment of type r, output of type w and an updatable state of type s.

rws :: (r -> s -> (a, s, w)) -> RWS r w s a #

Construct an RWS computation from a function. (The inverse of runRWS.)

runRWS :: RWS r w s a -> r -> s -> (a, s, w) #

Unwrap an RWS computation as a function. (The inverse of rws.)

evalRWS #

Arguments

:: RWS r w s a

RWS computation to execute

-> r

initial environment

-> s

initial value

-> (a, w)

final value and output

Evaluate a computation with the given initial state and environment, returning the final value and output, discarding the final state.

execRWS #

Arguments

:: RWS r w s a

RWS computation to execute

-> r

initial environment

-> s

initial value

-> (s, w)

final state and output

Evaluate a computation with the given initial state and environment, returning the final state and output, discarding the final value.

mapRWS :: ((a, s, w) -> (b, s, w')) -> RWS r w s a -> RWS r w' s b #

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

withRWS :: (r' -> s -> (r, s)) -> RWS r w s a -> RWS r' w s a #

withRWS f m executes action m with an initial environment and state modified by applying f.

evalRWST #

Arguments

:: Monad m 
=> RWST r w s m a

computation to execute

-> r

initial environment

-> s

initial value

-> m (a, w)

computation yielding final value and output

Evaluate a computation with the given initial state and environment, returning the final value and output, discarding the final state.

execRWST #

Arguments

:: Monad m 
=> RWST r w s m a

computation to execute

-> r

initial environment

-> s

initial value

-> m (s, w)

computation yielding final state and output

Evaluate a computation with the given initial state and environment, returning the final state and output, discarding the final value.

mapRWST :: (m (a, s, w) -> n (b, s, w')) -> RWST r w s m a -> RWST r w' s n b #

Map the inner computation using the given function.

withRWST :: (r' -> s -> (r, s)) -> RWST r w s m a -> RWST r' w s m a #

withRWST f m executes action m with an initial environment and state modified by applying f.

liftCallCC' :: Monoid w => CallCC m (a, s, w) (b, s, w) -> CallCC (RWST r w 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.

gets :: (Monoid w, Monad m) => (s -> a) -> RWST r w s m a #

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

modify :: (Monoid w, Monad m) => (s -> s) -> RWST r w s m () #

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

put :: (Monoid w, Monad m) => s -> RWST r w s m () #

put s sets the state within the monad to s.

get :: (Monoid w, Monad m) => RWST r w s m s #

Fetch the current value of the state within the monad.

state :: (Monoid w, Monad m) => (s -> (a, s)) -> RWST r w s m a #

Construct a state monad computation from a state transformer function.

censor :: Monad m => (w -> w) -> RWST r w s m a -> RWST r w s m a #

censor f m is an action that executes the action m and applies the function f to its output, leaving the return value unchanged.

pass :: Monad m => RWST r w s m (a, w -> w) -> RWST r w s m a #

pass m is an action that executes the action m, which returns a value and a function, and returns the value, applying the function to the output.

listens :: Monad m => (w -> b) -> RWST r w s m a -> RWST r w s m (a, b) #

listens f m is an action that executes the action m and adds the result of applying f to the output to the value of the computation.

listen :: Monad m => RWST r w s m a -> RWST r w s m (a, w) #

listen m is an action that executes the action m and adds its output to the value of the computation.

tell :: Monad m => w -> RWST r w s m () #

tell w is an action that produces the output w.

writer :: Monad m => (a, w) -> RWST r w s m a #

Construct a writer computation from a (result, output) pair.

asks :: (Monoid w, Monad m) => (r -> a) -> RWST r w s m a #

Retrieve a function of the current environment.

local :: (r -> r) -> RWST r w s m a -> RWST r w s m a #

Execute a computation in a modified environment

ask :: (Monoid w, Monad m) => RWST r w s m r #

Fetch the value of the environment.

reader :: (Monoid w, Monad m) => (r -> a) -> RWST r w s m a #

Constructor for computations in the reader monad (equivalent to asks).