monad-unlift-ref-0.2.0: Typeclasses for representing monad transformer unlifting

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Trans.Writer.Ref

Description

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

An additional advantage of this transformer over the standard WriterT transformers in the transformers package is that it does not have space leaks. 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 WriterRefT ref w m a Source

Since 0.1.0

Instances

MonadBase b m => MonadBase b (WriterRefT ref w m) Source 
MonadBaseControl b m => MonadBaseControl b (WriterRefT ref w m) Source 
((~) * (MCState (ref w)) (PrimState b), Monad m, (~) * w (RefElement (ref w)), MutableRef (ref w), PrimMonad b, MonadBase b m, Monoid w) => MonadWriter w (WriterRefT ref w m) Source 
MonadTrans (WriterRefT ref w) Source 
MonadTransControl (WriterRefT ref w) Source 
Monad m => Monad (WriterRefT ref w m) Source 
Functor m => Functor (WriterRefT ref w m) Source 
Applicative m => Applicative (WriterRefT ref w m) Source 
MonadThrow m => MonadThrow (WriterRefT ref w m) Source 
MonadCatch m => MonadCatch (WriterRefT ref w m) Source 
MonadMask m => MonadMask (WriterRefT ref w m) Source 
MonadIO m => MonadIO (WriterRefT ref w m) Source 
MonadResource m => MonadResource (WriterRefT ref w m) Source 
type StT (WriterRefT ref w) a = a Source 
type StM (WriterRefT ref w m) a = StM m a Source 

runWriterRefT :: (Monad m, w ~ RefElement (ref w), MCState (ref w) ~ PrimState b, MonadBase b m, MutableRef (ref w), PrimMonad b, Monoid w) => WriterRefT ref w m a -> m (a, w) Source

Since 0.1.0

runWriterIORefT :: (Monad m, RealWorld ~ PrimState b, MonadBase b m, PrimMonad b, Monoid w) => WriterRefT IORef w m a -> m (a, w) Source

Since 0.1.0

runWriterSTRefT :: (Monad m, ps ~ PrimState b, MonadBase b m, PrimMonad b, Monoid w) => WriterRefT (STRef ps) w m a -> m (a, w) Source

Since 0.1.0