fused-effects-1.0.2.1: A fast, flexible, fused effect system.

Safe HaskellNone
LanguageHaskell2010

Control.Carrier.State.Strict

Contents

Description

A carrier for the State effect. It evaluates its inner state strictly, which is the correct choice for the majority of use cases.

Note that the parameter order in runState, evalState, and execState is reversed compared the equivalent functions provided by transformers. This is an intentional decision made to enable the composition of effect handlers with . without invoking flip.

Since: 1.0.0.0

Synopsis

Strict state carrier

runState :: 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.0.0.0

evalState :: forall s m a. Functor 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.0.0.0

execState :: forall s m a. Functor 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.0.0.0

newtype StateC s m a Source #

Since: 1.0.0.0

Constructors

StateC (s -> m (s, a)) 
Instances
MonadTrans (StateC s) Source # 
Instance details

Defined in Control.Carrier.State.Strict

Methods

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

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

Defined in Control.Carrier.State.Strict

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 #

fail :: String -> StateC s m a #

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

Defined in Control.Carrier.State.Strict

Methods

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

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

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

Defined in Control.Carrier.State.Strict

Methods

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

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

Defined in Control.Carrier.State.Strict

Methods

fail :: String -> StateC s m a #

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

Defined in Control.Carrier.State.Strict

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 #

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

Defined in Control.Carrier.State.Strict

Methods

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

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

Defined in Control.Carrier.State.Strict

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] #

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

Defined in Control.Carrier.State.Strict

Methods

mzero :: StateC s m a #

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

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

Defined in Control.Carrier.State.Strict

Methods

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

State effect