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

Safe HaskellNone
LanguageHaskell2010

Control.Carrier.State.Lazy

Contents

Description

A carrier for the State effect that refrains from evaluating its state until necessary. This is less efficient than Control.Carrier.State.Strict but allows some cyclic computations to terminate that would loop infinitely in a strict state carrier.

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

Lazy state carrier

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

Run a lazy State effect, yielding the result value and the final state. More programs terminate with lazy state than strict state, but injudicious use of lazy state may lead to thunk buildup.

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 lazy 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 lazy 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 

Fields

Instances
MonadTrans (StateC s) Source # 
Instance details

Defined in Control.Carrier.State.Lazy

Methods

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

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

Defined in Control.Carrier.State.Lazy

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

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

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

Methods

fail :: String -> StateC s m a #

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

Defined in Control.Carrier.State.Lazy

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

Methods

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

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

Defined in Control.Carrier.State.Lazy

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

Methods

mzero :: StateC s m a #

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

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

Defined in Control.Carrier.State.Lazy

Methods

alg :: (State s :+: sig) (StateC s m) a -> StateC s m a Source #

State effect