monad-unlift-ref-0.2.1: 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 # 
MonadBase b m => MonadBase b (RWSRefT refw refs r w s m) Source # 

Methods

liftBase :: b α -> RWSRefT refw refs r w s m α #

MonadBaseControl b m => MonadBaseControl b (RWSRefT refw refs r w s m) Source # 

Associated Types

type StM (RWSRefT refw refs r w s m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (RWSRefT refw refs r w s m) b -> b a) -> RWSRefT refw refs r w s m a #

restoreM :: StM (RWSRefT refw refs r w s m) a -> RWSRefT refw refs r w s m a #

Monad m => MonadReader r (RWSRefT refw refs r w s m) Source # 

Methods

ask :: RWSRefT refw refs r w s m r #

local :: (r -> r) -> RWSRefT refw refs r w s m a -> RWSRefT refw refs r w s m a #

reader :: (r -> a) -> RWSRefT refw refs r w s m a #

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

Methods

get :: RWSRefT refw refs r w s m s #

put :: s -> RWSRefT refw refs r w s m () #

state :: (s -> (a, s)) -> RWSRefT refw refs r w s m a #

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

Methods

writer :: (a, w) -> RWSRefT refw refs r w s m a #

tell :: w -> RWSRefT refw refs r w s m () #

listen :: RWSRefT refw refs r w s m a -> RWSRefT refw refs r w s m (a, w) #

pass :: RWSRefT refw refs r w s m (a, w -> w) -> RWSRefT refw refs r w s m a #

MonadTrans (RWSRefT refw refs r w s) Source # 

Methods

lift :: Monad m => m a -> RWSRefT refw refs r w s m a #

MonadTransControl (RWSRefT refw refs r w s) Source # 

Associated Types

type StT (RWSRefT refw refs r w s :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (RWSRefT refw refs r w s) -> m a) -> RWSRefT refw refs r w s m a #

restoreT :: Monad m => m (StT (RWSRefT refw refs r w s) a) -> RWSRefT refw refs r w s m a #

Monad m => Monad (RWSRefT refw refs r w s m) Source # 

Methods

(>>=) :: RWSRefT refw refs r w s m a -> (a -> RWSRefT refw refs r w s m b) -> RWSRefT refw refs r w s m b #

(>>) :: RWSRefT refw refs r w s m a -> RWSRefT refw refs r w s m b -> RWSRefT refw refs r w s m b #

return :: a -> RWSRefT refw refs r w s m a #

fail :: String -> RWSRefT refw refs r w s m a #

Functor m => Functor (RWSRefT refw refs r w s m) Source # 

Methods

fmap :: (a -> b) -> RWSRefT refw refs r w s m a -> RWSRefT refw refs r w s m b #

(<$) :: a -> RWSRefT refw refs r w s m b -> RWSRefT refw refs r w s m a #

Applicative m => Applicative (RWSRefT refw refs r w s m) Source # 

Methods

pure :: a -> RWSRefT refw refs r w s m a #

(<*>) :: RWSRefT refw refs r w s m (a -> b) -> RWSRefT refw refs r w s m a -> RWSRefT refw refs r w s m b #

(*>) :: RWSRefT refw refs r w s m a -> RWSRefT refw refs r w s m b -> RWSRefT refw refs r w s m b #

(<*) :: RWSRefT refw refs r w s m a -> RWSRefT refw refs r w s m b -> RWSRefT refw refs r w s m a #

MonadIO m => MonadIO (RWSRefT refw refs r w s m) Source # 

Methods

liftIO :: IO a -> RWSRefT refw refs r w s m a #

MonadThrow m => MonadThrow (RWSRefT refw refs r w s m) Source # 

Methods

throwM :: Exception e => e -> RWSRefT refw refs r w s m a #

MonadCatch m => MonadCatch (RWSRefT refw refs r w s m) Source # 

Methods

catch :: Exception e => RWSRefT refw refs r w s m a -> (e -> RWSRefT refw refs r w s m a) -> RWSRefT refw refs r w s m a #

MonadMask m => MonadMask (RWSRefT refw refs r w s m) Source # 

Methods

mask :: ((forall a. RWSRefT refw refs r w s m a -> RWSRefT refw refs r w s m a) -> RWSRefT refw refs r w s m b) -> RWSRefT refw refs r w s m b #

uninterruptibleMask :: ((forall a. RWSRefT refw refs r w s m a -> RWSRefT refw refs r w s m a) -> RWSRefT refw refs r w s m b) -> RWSRefT refw refs r w s m b #

MonadResource m => MonadResource (RWSRefT refw refs r w s m) Source # 

Methods

liftResourceT :: ResourceT IO a -> RWSRefT refw refs r w s m a #

type StT (RWSRefT refw refs r w s) a Source # 
type StT (RWSRefT refw refs r w s) a = a
type StM (RWSRefT refw refs r w s m) a Source # 
type StM (RWSRefT refw refs r w s m) a = StM m a

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