extensible-effects-2.6.3.0: An Alternative to Monad Transformers

Safe HaskellTrustworthy
LanguageHaskell2010

Control.Eff.State.OnDemand

Description

Lazy state effect

Synopsis

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

Constructors

Get :: OnDemandState s s 
Put :: s -> OnDemandState s () 
Delay :: Eff '[OnDemandState s] a -> OnDemandState s a 

Instances

(MonadBase m m, SetMember (* -> *) (Lift *) (Lift * m) r, MonadBaseControl m (Eff r)) => MonadBaseControl m (Eff ((:) (* -> *) (OnDemandState s) r)) Source # 

Associated Types

type StM (Eff (((* -> *) ': OnDemandState s) r) :: * -> *) a :: * #

Methods

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 #

type StM (Eff ((:) (* -> *) (OnDemandState s) r)) a Source # 
type StM (Eff ((:) (* -> *) (OnDemandState s) r)) a = StM (Eff r) (a, s)

get :: Member (OnDemandState s) r => Eff r s Source #

Return the current value of the state. The signatures are inferred

put :: Member (OnDemandState s) r => s -> Eff r () Source #

Write a new value of the state.

onDemand :: Member (OnDemandState s) r => Eff '[OnDemandState s] v -> Eff r v Source #

runState' :: s -> Eff (OnDemandState s ': r) w -> Eff r (w, s) Source #

runState Source #

Arguments

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