monad-unlift-ref-0.2.1: 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 # 

Methods

liftBase :: b α -> WriterRefT ref w m α #

MonadBaseControl b m => MonadBaseControl b (WriterRefT ref w m) Source # 

Associated Types

type StM (WriterRefT ref w m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (WriterRefT ref w m) b -> b a) -> WriterRefT ref w m a #

restoreM :: StM (WriterRefT ref w m) a -> WriterRefT ref w m a #

MonadReader r m => MonadReader r (WriterRefT ref w m) Source #

Since: 0.2.1

Methods

ask :: WriterRefT ref w m r #

local :: (r -> r) -> WriterRefT ref w m a -> WriterRefT ref w m a #

reader :: (r -> a) -> WriterRefT ref w m a #

((~) * (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 # 

Methods

writer :: (a, w) -> WriterRefT ref w m a #

tell :: w -> WriterRefT ref w m () #

listen :: WriterRefT ref w m a -> WriterRefT ref w m (a, w) #

pass :: WriterRefT ref w m (a, w -> w) -> WriterRefT ref w m a #

MonadTrans (WriterRefT ref w) Source # 

Methods

lift :: Monad m => m a -> WriterRefT ref w m a #

MonadTransControl (WriterRefT ref w) Source # 

Associated Types

type StT (WriterRefT ref w :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (WriterRefT ref w) -> m a) -> WriterRefT ref w m a #

restoreT :: Monad m => m (StT (WriterRefT ref w) a) -> WriterRefT ref w m a #

Monad m => Monad (WriterRefT ref w m) Source # 

Methods

(>>=) :: WriterRefT ref w m a -> (a -> WriterRefT ref w m b) -> WriterRefT ref w m b #

(>>) :: WriterRefT ref w m a -> WriterRefT ref w m b -> WriterRefT ref w m b #

return :: a -> WriterRefT ref w m a #

fail :: String -> WriterRefT ref w m a #

Functor m => Functor (WriterRefT ref w m) Source # 

Methods

fmap :: (a -> b) -> WriterRefT ref w m a -> WriterRefT ref w m b #

(<$) :: a -> WriterRefT ref w m b -> WriterRefT ref w m a #

Applicative m => Applicative (WriterRefT ref w m) Source # 

Methods

pure :: a -> WriterRefT ref w m a #

(<*>) :: WriterRefT ref w m (a -> b) -> WriterRefT ref w m a -> WriterRefT ref w m b #

(*>) :: WriterRefT ref w m a -> WriterRefT ref w m b -> WriterRefT ref w m b #

(<*) :: WriterRefT ref w m a -> WriterRefT ref w m b -> WriterRefT ref w m a #

MonadIO m => MonadIO (WriterRefT ref w m) Source # 

Methods

liftIO :: IO a -> WriterRefT ref w m a #

MonadThrow m => MonadThrow (WriterRefT ref w m) Source # 

Methods

throwM :: Exception e => e -> WriterRefT ref w m a #

MonadCatch m => MonadCatch (WriterRefT ref w m) Source # 

Methods

catch :: Exception e => WriterRefT ref w m a -> (e -> WriterRefT ref w m a) -> WriterRefT ref w m a #

MonadMask m => MonadMask (WriterRefT ref w m) Source # 

Methods

mask :: ((forall a. WriterRefT ref w m a -> WriterRefT ref w m a) -> WriterRefT ref w m b) -> WriterRefT ref w m b #

uninterruptibleMask :: ((forall a. WriterRefT ref w m a -> WriterRefT ref w m a) -> WriterRefT ref w m b) -> WriterRefT ref w m b #

MonadResource m => MonadResource (WriterRefT ref w m) Source # 

Methods

liftResourceT :: ResourceT IO a -> WriterRefT ref w m a #

type StT (WriterRefT ref w) a Source # 
type StT (WriterRefT ref w) a = a
type StM (WriterRefT ref w m) a Source # 
type StM (WriterRefT ref w m) a = StM m a

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