concurrent-state-0.5.1.2: MTL-like library using TVars

Portabilityportable
Stabilityexperimental
Maintainerme@joelt.io
Safe HaskellSafe-Inferred

Control.Monad.RWS.Concurrent.Lazy

Contents

Description

Concurrent RWS monad, combining a Reader, a Writer, and a State monad.

This module performs computations lazily. For a strict version, see Control.Monad.RWS.Concurrent.Strict.

Synopsis

Documentation

The RWSC monad transformer

data RWSC r w s m a Source

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

This is very similar to transformers' RWST, with the exception of the MonadIO constraint on every instance, which is necessary to perform STM actions.

Instances

(Monoid w, MonadIO m, MonadReader r m, MonadWriter w m, MonadState s m) => MonadRWS r w s (RWSC r w s m) 
MonadReader r m => MonadReader r (RWSC r w s m) 
(MonadIO m, MonadState s m) => MonadState s (RWSC r w s m) 
(Monoid w, MonadIO m, MonadWriter w m) => MonadWriter w (RWSC r w s m) 
MonadTrans (RWSC r w s) 
Monad m => Monad (RWSC r w s m) 
Functor m => Functor (RWSC r w s m) 
MonadFix m => MonadFix (RWSC r w s m) 
MonadPlus m => MonadPlus (RWSC r w s m) 
(Functor m, Monad m) => Applicative (RWSC r w s m) 
(Functor m, MonadPlus m) => Alternative (RWSC r w s m) 
(MonadIO m, MonadCatch m) => MonadCatch (RWSC r w s m) 
MonadIO m => MonadIO (RWSC r w s m) 
MonadFork m => MonadFork (RWSC r w s m) 

Running RWSC actions

runRWSCSource

Arguments

:: MonadIO m 
=> RWSC r w s m a

computation to execute

-> r

environment to read

-> TVar s

state to modify

-> TVar w

output channel

-> m (a, s, w)

return value, final state, and collected output

Unwrap a concurrent RWS monad computation as a function.

evalRWSCSource

Arguments

:: MonadIO m 
=> RWSC r w s m a

computation to execute

-> r

environment to read

-> TVar s

state to modify

-> TVar w

output channel

-> m (a, w)

return value and collected output

Unwrap a concurrent RWS monad computation as a function, discarding the final state.

execRWSCSource

Arguments

:: MonadIO m 
=> RWSC r w s m a

computation to execute

-> r

environment to read

-> TVar s

state to modify

-> TVar w

output channel

-> m (s, w)

final state and collected output

Unwrap a concurrent RWS monad computation as a function, discarding the return value.

mapRWSC :: (m (a, TVar s, TVar w) -> n (b, TVar s, TVar w)) -> RWSC r w s m a -> RWSC r w s n bSource

Map the inner computation using the given function.

withRWSC :: (r' -> TVar s -> TVar w -> (r, TVar s, TVar w)) -> RWSC r w s m a -> RWSC r' w s m aSource

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

Lifting other operations

liftCallCCC :: ((((a, TVar s, TVar w) -> m (b, TVar s, TVar w)) -> m (a, TVar s, TVar w)) -> m (a, TVar s, TVar w)) -> ((a -> RWSC r w s m b) -> RWSC r w s m a) -> RWSC r w s m aSource

Uniform lifting of a callCC operation to the new monad.

liftCatch :: (m (a, TVar s, TVar w) -> (e -> m (a, TVar s, TVar w)) -> m (a, TVar s, TVar w)) -> RWSC l w s m a -> (e -> RWSC l w s m a) -> RWSC l w s m aSource

Lift a catchError operation to the new monad.