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

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Trans.State.Ref

Description

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

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

Synopsis

Documentation

data StateRefT ref s m a Source #

Since: 0.1.0

Instances

MonadBase b m => MonadBase b (StateRefT ref s m) Source # 

Methods

liftBase :: b α -> StateRefT ref s m α #

MonadBaseControl b m => MonadBaseControl b (StateRefT ref s m) Source # 

Associated Types

type StM (StateRefT ref s m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (StateRefT ref s m) b -> b a) -> StateRefT ref s m a #

restoreM :: StM (StateRefT ref s m) a -> StateRefT ref s m a #

MonadReader r m => MonadReader r (StateRefT ref s m) Source #

Since: 0.2.1

Methods

ask :: StateRefT ref s m r #

local :: (r -> r) -> StateRefT ref s m a -> StateRefT ref s m a #

reader :: (r -> a) -> StateRefT ref s m a #

((~) * (MCState (ref s)) (PrimState b), Monad m, (~) * s (RefElement (ref s)), MutableRef (ref s), PrimMonad b, MonadBase b m) => MonadState s (StateRefT ref s m) Source # 

Methods

get :: StateRefT ref s m s #

put :: s -> StateRefT ref s m () #

state :: (s -> (a, s)) -> StateRefT ref s m a #

MonadTrans (StateRefT ref s) Source # 

Methods

lift :: Monad m => m a -> StateRefT ref s m a #

MonadTransControl (StateRefT ref s) Source # 

Associated Types

type StT (StateRefT ref s :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (StateRefT ref s) -> m a) -> StateRefT ref s m a #

restoreT :: Monad m => m (StT (StateRefT ref s) a) -> StateRefT ref s m a #

Monad m => Monad (StateRefT ref s m) Source # 

Methods

(>>=) :: StateRefT ref s m a -> (a -> StateRefT ref s m b) -> StateRefT ref s m b #

(>>) :: StateRefT ref s m a -> StateRefT ref s m b -> StateRefT ref s m b #

return :: a -> StateRefT ref s m a #

fail :: String -> StateRefT ref s m a #

Functor m => Functor (StateRefT ref s m) Source # 

Methods

fmap :: (a -> b) -> StateRefT ref s m a -> StateRefT ref s m b #

(<$) :: a -> StateRefT ref s m b -> StateRefT ref s m a #

Applicative m => Applicative (StateRefT ref s m) Source # 

Methods

pure :: a -> StateRefT ref s m a #

(<*>) :: StateRefT ref s m (a -> b) -> StateRefT ref s m a -> StateRefT ref s m b #

(*>) :: StateRefT ref s m a -> StateRefT ref s m b -> StateRefT ref s m b #

(<*) :: StateRefT ref s m a -> StateRefT ref s m b -> StateRefT ref s m a #

MonadIO m => MonadIO (StateRefT ref s m) Source # 

Methods

liftIO :: IO a -> StateRefT ref s m a #

MonadThrow m => MonadThrow (StateRefT ref s m) Source # 

Methods

throwM :: Exception e => e -> StateRefT ref s m a #

MonadCatch m => MonadCatch (StateRefT ref s m) Source # 

Methods

catch :: Exception e => StateRefT ref s m a -> (e -> StateRefT ref s m a) -> StateRefT ref s m a #

MonadMask m => MonadMask (StateRefT ref s m) Source # 

Methods

mask :: ((forall a. StateRefT ref s m a -> StateRefT ref s m a) -> StateRefT ref s m b) -> StateRefT ref s m b #

uninterruptibleMask :: ((forall a. StateRefT ref s m a -> StateRefT ref s m a) -> StateRefT ref s m b) -> StateRefT ref s m b #

MonadResource m => MonadResource (StateRefT ref s m) Source # 

Methods

liftResourceT :: ResourceT IO a -> StateRefT ref s m a #

type StT (StateRefT ref s) a Source # 
type StT (StateRefT ref s) a = a
type StM (StateRefT ref s m) a Source # 
type StM (StateRefT ref s m) a = StM m a

runStateRefT :: (Monad m, s ~ RefElement (ref s), MCState (ref s) ~ PrimState b, MonadBase b m, MutableRef (ref s), PrimMonad b) => StateRefT ref s m a -> s -> m (a, s) Source #

Since: 0.1.0

runStateIORefT :: (Monad m, RealWorld ~ PrimState b, MonadBase b m, PrimMonad b) => StateRefT IORef s m a -> s -> m (a, s) Source #

Since: 0.1.0

runStateSTRefT :: (Monad m, ps ~ PrimState b, MonadBase b m, PrimMonad b) => StateRefT (STRef ps) s m a -> s -> m (a, s) Source #

Since: 0.1.0