extensible-effects-3.1.0.2: An Alternative to Monad Transformers

Safe HaskellTrustworthy
LanguageHaskell2010

Control.Eff.State.Lazy

Description

Lazy state effect

Synopsis

Documentation

data State s v where Source #

State, lazy

Initial design: The state request carries with it the state mutator function We can use this request both for mutating and getting the state. But see below for a better design!

data State s v where
  State :: (s->s) -> State s s

In this old design, we have assumed that the dominant operation is modify. Perhaps this is not wise. Often, the reader is most nominant.

See also below, for decomposing the State into Reader and Writer!

The conventional design of State

Constructors

Get :: State s s 
Put :: s -> State s () 
Instances
(MonadBase m m, SetMember (Lift :: (Type -> Type) -> Type -> Type) (Lift m) r, MonadBaseControl m (Eff r)) => MonadBaseControl m (Eff (State s ': r)) Source # 
Instance details

Defined in Control.Eff.State.Lazy

Associated Types

type StM (Eff (State s ': r)) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (State s ': r)) m -> m a) -> Eff (State s ': r) a #

restoreM :: StM (Eff (State s ': r)) a -> Eff (State s ': r) a #

type StM (Eff (State s ': r)) a Source # 
Instance details

Defined in Control.Eff.State.Lazy

type StM (Eff (State s ': r)) a = StM (Eff r) (a, s)

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

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

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

Write a new value of the state.

runState' :: s -> Eff (State s ': r) a -> Eff r (a, s) Source #

Run a state effect. compared to the runState function, this is implemented naively and is expected to perform slower.

runState Source #

Arguments

:: s

Initial state

-> Eff (State s ': r) a

Effect incorporating State

-> Eff r (a, s)

Effect containing final state and a return value

Run a State effect. This variant is a bit optimized compared to runState'.

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

Transform the state with a function.

evalState :: s -> Eff (State s ': r) a -> Eff r a Source #

Run a State effect, discarding the final state.

execState :: s -> Eff (State s ': r) a -> Eff r s Source #

Run a State effect and return the final state.

data TxState s Source #

An encapsulated State handler, for transactional semantics The global state is updated only if the transactionState finished successfully

Constructors

TxState 

transactionState :: forall s r a. Member (State s) r => TxState s -> Eff r a -> Eff r a Source #

runStateR :: s -> Eff (Writer s ': (Reader s ': r)) a -> Eff r (a, 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.