monad-unlift-0.1.2.0: Typeclasses for representing monad transformer unlifting

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Trans.RWS.Ref

Description

An implementation of RWST built on top of mutable references, providing a proper monad morphism.

An additional advantage of this transformer over the standard RWST transformers in the transformers package is that it does not have space leaks in the writer component. For more information, see https://mail.haskell.org/pipermail/libraries/2012-October/018599.html.

Please see the documentation at https://www.stackage.org/package/monad-unlift for more details on using this module.

Synopsis

Documentation

data RWSRefT refw refs r w s m a Source

Since 0.1.0

Instances

((~) * (MCState (refw w)) (PrimState b), (~) * (MCState (refs s)) (PrimState b), Monad m, (~) * w (RefElement (refw w)), (~) * s (RefElement (refs s)), MutableRef (refw w), MutableRef (refs s), PrimMonad b, MonadBase b m, Monoid w) => MonadRWS r w s (RWSRefT refw refs r w s m) Source 
((~) * (MCState (refs s)) (PrimState b), Monad m, (~) * s (RefElement (refs s)), MutableRef (refs s), PrimMonad b, MonadBase b m) => MonadState s (RWSRefT refw refs r w s m) Source 
Monad m => MonadReader r (RWSRefT refw refs r w s m) Source 
MonadBase b m => MonadBase b (RWSRefT refw refs r w s m) Source 
MonadBaseControl b m => MonadBaseControl b (RWSRefT refw refs r w s m) Source 
((~) * (MCState (refw w)) (PrimState b), Monad m, (~) * w (RefElement (refw w)), MutableRef (refw w), PrimMonad b, MonadBase b m, Monoid w) => MonadWriter w (RWSRefT refw refs r w s m) Source 
MonadTrans (RWSRefT refw refs r w s) Source 
MonadTransControl (RWSRefT refw refs r w s) Source 
Monad m => Monad (RWSRefT refw refs r w s m) Source 
Functor m => Functor (RWSRefT refw refs r w s m) Source 
Applicative m => Applicative (RWSRefT refw refs r w s m) Source 
MonadThrow m => MonadThrow (RWSRefT refw refs r w s m) Source 
MonadCatch m => MonadCatch (RWSRefT refw refs r w s m) Source 
MonadMask m => MonadMask (RWSRefT refw refs r w s m) Source 
MonadIO m => MonadIO (RWSRefT refw refs r w s m) Source 
MonadResource m => MonadResource (RWSRefT refw refs r w s m) Source 
type StT (RWSRefT refw refs r w s) a = a Source 
type StM (RWSRefT refw refs r w s m) a = StM m a Source 

runRWSRefT :: (Monad m, w ~ RefElement (refw w), s ~ RefElement (refs s), MCState (refw w) ~ PrimState b, MCState (refs s) ~ PrimState b, MonadBase b m, MutableRef (refw w), MutableRef (refs s), PrimMonad b, Monoid w) => RWSRefT refw refs r w s m a -> r -> s -> m (a, s, w) Source

Since 0.1.0

runRWSIORefT :: (Monad m, RealWorld ~ PrimState b, MonadBase b m, PrimMonad b, Monoid w) => RWSRefT IORef IORef r w s m a -> r -> s -> m (a, s, w) Source

Since 0.1.0

runRWSSTRefT :: (Monad m, ps ~ PrimState b, MonadBase b m, PrimMonad b, Monoid w) => RWSRefT (STRef ps) (STRef ps) r w s m a -> r -> s -> m (a, s, w) Source

Since 0.1.0