Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
Lazy state effect
Synopsis
- data OnDemandState s v where
- Get :: OnDemandState s s
- Put :: s -> OnDemandState s ()
- Delay :: Eff '[OnDemandState s] a -> OnDemandState s a
- get :: Member (OnDemandState s) r => Eff r s
- put :: Member (OnDemandState s) r => s -> Eff r ()
- onDemand :: Member (OnDemandState s) r => Eff '[OnDemandState s] v -> Eff r v
- runState :: s -> Eff (OnDemandState s ': r) w -> Eff r (w, s)
- modify :: Member (OnDemandState s) r => (s -> s) -> Eff r ()
- evalState :: s -> Eff (OnDemandState s ': r) w -> Eff r w
- execState :: s -> Eff (OnDemandState s ': r) w -> Eff r s
- runStateR :: s -> Eff (Writer s ': (Reader s ': r)) w -> Eff r (w, s)
- runStateBack0 :: Eff '[OnDemandState s] a -> (a, s)
- runStateBack :: Eff '[OnDemandState s] a -> (a, s)
Documentation
data OnDemandState s v where Source #
State, lazy (i.e., on-demand)
Extensible effects make it clear that where the computation is delayed (which I take as an advantage) and they do maintain the degree of extensibility (the delayed computation must be effect-closed, but the whole computation does not have to be).
Get :: OnDemandState s s | |
Put :: s -> OnDemandState s () | |
Delay :: Eff '[OnDemandState s] a -> OnDemandState s a |
Instances
(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (OnDemandState s ': r)) Source # | |
Defined in Control.Eff.State.OnDemand type StM (Eff (OnDemandState s ': r)) a :: Type # liftBaseWith :: (RunInBase (Eff (OnDemandState s ': r)) m -> m a) -> Eff (OnDemandState s ': r) a # restoreM :: StM (Eff (OnDemandState s ': r)) a -> Eff (OnDemandState s ': r) a # | |
Handle (OnDemandState s) r a (s -> k) Source # | Given a continuation, respond to requests |
Defined in Control.Eff.State.OnDemand handle :: (Eff r a -> s -> k) -> Arrs r v a -> OnDemandState s v -> s -> k Source # handle_relay :: (r ~ (OnDemandState s ': r'), Relay (s -> k) r') => (a -> s -> k) -> (Eff r a -> s -> k) -> Eff r a -> s -> k Source # respond_relay :: (a -> s -> k) -> (Eff r a -> s -> k) -> Eff r a -> s -> k Source # | |
type StM (Eff (OnDemandState s ': r)) a Source # | |
Defined in Control.Eff.State.OnDemand |
get :: Member (OnDemandState s) r => Eff r s Source #
Return the current value of the state. The signatures are inferred
onDemand :: Member (OnDemandState s) r => Eff '[OnDemandState s] v -> Eff r v Source #
:: s | Initial state |
-> Eff (OnDemandState s ': r) w | Effect incorporating State |
-> Eff r (w, s) | Effect containing final state and a return value |
Run a State effect
modify :: Member (OnDemandState s) r => (s -> s) -> Eff r () Source #
Transform the state with a function.
evalState :: s -> Eff (OnDemandState s ': r) w -> Eff r w Source #
Run a State effect, discarding the final state.
execState :: s -> Eff (OnDemandState s ': r) w -> Eff r s Source #
Run a State effect and return the final state.
runStateR :: s -> Eff (Writer s ': (Reader s ': r)) w -> Eff r (w, s) Source #
A different representation of State: decomposing State into mutation (Writer) and Reading. We don't define any new effects: we just handle the existing ones. Thus we define a handler for two effects together.
runStateBack0 :: Eff '[OnDemandState s] a -> (a, s) Source #
Backwards state
The overall state is represented with two attributes: the inherited
getAttr and the synthesized putAttr.
At the root node, putAttr becomes getAttr, tying the knot.
As usual, the inherited attribute is the argument (i.e., the environment
)
and the synthesized is the result of the handler |go| below.
runStateBack :: Eff '[OnDemandState s] a -> (a, s) Source #
A different notion of backwards is realized if we change the Put handler slightly. How?
Another implementation, exploring Haskell's laziness to make putAttr also technically inherited, to accumulate the sequence of updates. This implementation is compatible with deep handlers, and lets us play with different notions of backwardness.