fused-effects-1.1.2.1: A fast, flexible, fused effect system.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Carrier.State.IORef

Description

A carrier for the State effect. It uses an IORef internally to handle its state, and thus admits a MonadUnliftIO instance. Because the state operations are performed impurely, this carrier will not lose state effects even with nefarious uses of liftWith.

Unlike the other carriers for State, this carrier's effects will not backtrack when run in conjuction with NonDet effects.

Since: 1.1.2.0

Synopsis

Impure state carrier

runState :: MonadIO m => s -> StateC s m a -> m (s, a) Source #

Run a State effect starting from the passed value.

runState s (pure a) = pure (s, a)
runState s get = pure (s, s)
runState s (put t) = pure (t, ())

Since: 1.1.2.0

runStateRef :: MonadIO m => IORef s -> StateC s m a -> m (s, a) Source #

Run a State effect starting from the passed IORef. This function is lawless, given that the underlying IORef can be modified by another thread.

Since: 1.1.2.0

evalState :: forall s m a. MonadIO m => s -> StateC s m a -> m a Source #

Run a State effect, yielding the result value and discarding the final state.

evalState s m = fmap snd (runState s m)

Since: 1.1.2.0

execState :: forall s m a. MonadIO m => s -> StateC s m a -> m s Source #

Run a State effect, yielding the final state and discarding the return value.

execState s m = fmap fst (runState s m)

Since: 1.1.2.0

newtype StateC s m a Source #

Since: 1.1.2.0

Constructors

StateC 

Fields

Instances

Instances details
MonadTrans (StateC s) Source # 
Instance details

Defined in Control.Carrier.State.IORef

Methods

lift :: Monad m => m a -> StateC s m a #

MonadFail m => MonadFail (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.IORef

Methods

fail :: String -> StateC s m a #

MonadFix m => MonadFix (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.IORef

Methods

mfix :: (a -> StateC s m a) -> StateC s m a #

MonadIO m => MonadIO (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.IORef

Methods

liftIO :: IO a -> StateC s m a #

Alternative m => Alternative (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.IORef

Methods

empty :: StateC s m a #

(<|>) :: StateC s m a -> StateC s m a -> StateC s m a #

some :: StateC s m a -> StateC s m [a] #

many :: StateC s m a -> StateC s m [a] #

Applicative m => Applicative (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.IORef

Methods

pure :: a -> StateC s m a #

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

liftA2 :: (a -> b -> c) -> StateC s m a -> StateC s m b -> StateC s m c #

(*>) :: StateC s m a -> StateC s m b -> StateC s m b #

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

Functor m => Functor (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.IORef

Methods

fmap :: (a -> b) -> StateC s m a -> StateC s m b #

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

Monad m => Monad (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.IORef

Methods

(>>=) :: StateC s m a -> (a -> StateC s m b) -> StateC s m b #

(>>) :: StateC s m a -> StateC s m b -> StateC s m b #

return :: a -> StateC s m a #

(Alternative m, Monad m) => MonadPlus (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.IORef

Methods

mzero :: StateC s m a #

mplus :: StateC s m a -> StateC s m a -> StateC s m a #

MonadUnliftIO m => MonadUnliftIO (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.IORef

Methods

withRunInIO :: ((forall a. StateC s m a -> IO a) -> IO b) -> StateC s m b #

(MonadIO m, Algebra sig m) => Algebra (State s :+: sig) (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.IORef

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (StateC s m) -> (State s :+: sig) n a -> ctx () -> StateC s m (ctx a) Source #

State effect