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

Safe HaskellNone
LanguageHaskell2010

Control.Effect.State.Internal

Synopsis

Documentation

data State s (m :: * -> *) k Source #

Constructors

Get (s -> k) 
Put s k 
Instances
Effect (State s) Source # 
Instance details

Defined in Control.Effect.State.Internal

Methods

handle :: Functor f => f () -> (forall x. f (m x) -> n (f x)) -> State s m (m a) -> State s n (n (f a)) Source #

HFunctor (State s) Source # 
Instance details

Defined in Control.Effect.State.Internal

Methods

fmap' :: (a -> b) -> State s m a -> State s m b Source #

hmap :: (forall x. m x -> n x) -> State s m a -> State s n a Source #

Functor (State s m) Source # 
Instance details

Defined in Control.Effect.State.Internal

Methods

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

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

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

Defined in Control.Effect.State.Strict

Methods

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

ret :: a -> StateC s m a Source #

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

Defined in Control.Effect.State.Lazy

Methods

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

ret :: a -> StateC s m a Source #

get :: (Member (State s) sig, Carrier sig m) => m s Source #

Get the current state value.

snd (run (runState a get)) == a

gets :: (Member (State s) sig, Carrier sig m) => (s -> a) -> m a Source #

Project a function out of the current state value.

snd (run (runState a (gets (applyFun f)))) == applyFun f a

put :: (Member (State s) sig, Carrier sig m) => s -> m () Source #

Replace the state value with a new value.

fst (run (runState a (put b))) == b
snd (run (runState a (get <* put b))) == a
snd (run (runState a (put b *> get))) == b

modify :: (Member (State s) sig, Carrier sig m) => (s -> s) -> m () Source #

Replace the state value with the result of applying a function to the current state value. This is strict in the new state.

fst (run (runState a (modify (+1)))) == (1 + a :: Integer)

modifyLazy :: (Member (State s) sig, Carrier sig m) => (s -> s) -> m () Source #

Replace the state value with the result of applying a function to the current state value. This is lazy in the new state; injudicious use of this function may lead to space leaks.