extensible-effects-1.2.1: An Alternative to Monad Transformers

Safe HaskellTrustworthy

Control.Eff.State.Strict

Description

Strict state effect

Example: implementing Fresh

 runFresh' :: (Typeable i, Enum i, Num i) => Eff (Fresh i :> r) w -> i -> Eff r w
 runFresh' m s = fst <$> runState s (loop $ admin m)
  where
   loop (Val x) = return x
   loop (E u)   = case decomp u of
     Right (Fresh k) -> do
                       n <- get
                       put (n + 1)
                       loop (k n)
     Left u' -> send (\k -> unsafeReUnion $ k <$> u') >>= loop

Synopsis

Documentation

data State s w Source

Strict state effect

Instances

get :: (Typeable e, Member (State e) r) => Eff r eSource

Return the current value of the state.

put :: (Typeable e, Member (State e) r) => e -> Eff r ()Source

Write a new value of the state.

modify :: (Typeable s, Member (State s) r) => (s -> s) -> Eff r ()Source

Transform the state with a function.

runStateSource

Arguments

:: Typeable s 
=> s

Initial state

-> Eff (State s :> r) w

Effect incorporating State

-> Eff r (s, w)

Effect containing final state and a return value

Run a State effect.

evalState :: Typeable s => s -> Eff (State s :> r) w -> Eff r wSource

Run a State effect, discarding the final state.

execState :: Typeable s => s -> Eff (State s :> r) w -> Eff r sSource

Run a State effect and return the final state.