fused-effects-1.1.1.1: A fast, flexible, fused effect system.
Safe HaskellNone
LanguageHaskell2010

Control.Carrier.State.Church

Description

A church-encoded carrier for the State effect.

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.1.0.0

Synopsis

State carrier

runState :: forall s m a b. (s -> a -> m b) -> s -> StateC s m a -> m b Source #

Run a State effect starting from the passed value, applying a continuation to the final state and result.

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

Since: 1.1.0.0

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

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

evalState = runState (const pure)

Since: 1.1.0.0

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

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

execState = runState (const . pure)

Since: 1.1.0.0

newtype StateC s m a Source #

Since: 1.1.0.0

Constructors

StateC (forall r. (s -> a -> m r) -> s -> m r) 

Instances

Instances details
MonadTrans (StateC s) Source # 
Instance details

Defined in Control.Carrier.State.Church

Methods

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

Monad (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.Church

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 #

Functor (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.Church

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.Church

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.Church

Methods

fail :: String -> StateC s m a #

Applicative (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.Church

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.Church

Methods

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

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

Defined in Control.Carrier.State.Church

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.Church

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.Church

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