effectful-core-2.6.0.0: An easy to use, performant extensible effects library.
Safe HaskellNone
LanguageHaskell2010

Effectful.State.Dynamic

Description

The dynamically dispatched variant of the State effect.

Note: unless you plan to change interpretations at runtime, it's recommended to use one of the statically dispatched variants, i.e. Effectful.State.Static.Local or Effectful.State.Static.Shared.

Synopsis

Effect

data State s (a :: Type -> Type) b where Source #

Provide access to a mutable value of type s.

Constructors

Get :: forall s (a :: Type -> Type). State s a s 
Put :: forall s (a :: Type -> Type). s -> State s a () 
State :: forall s b (a :: Type -> Type). (s -> (b, s)) -> State s a b 
StateM :: forall s (a :: Type -> Type) b. (s -> a (b, s)) -> State s a b 

Instances

Instances details
type DispatchOf (State s) Source # 
Instance details

Defined in Effectful.State.Dynamic

Handlers

Local

runStateLocal :: forall s (es :: [(Type -> Type) -> Type -> Type]) a. HasCallStack => s -> Eff (State s ': es) a -> Eff es (a, s) Source #

Run the State effect with the given initial state and return the final value along with the final state (via Effectful.State.Static.Local).

evalStateLocal :: forall s (es :: [(Type -> Type) -> Type -> Type]) a. HasCallStack => s -> Eff (State s ': es) a -> Eff es a Source #

Run the State effect with the given initial state and return the final value, discarding the final state (via Effectful.State.Static.Local).

execStateLocal :: forall s (es :: [(Type -> Type) -> Type -> Type]) a. HasCallStack => s -> Eff (State s ': es) a -> Eff es s Source #

Run the State effect with the given initial state and return the final state, discarding the final value (via Effectful.State.Static.Local).

Shared

runStateShared :: forall s (es :: [(Type -> Type) -> Type -> Type]) a. HasCallStack => s -> Eff (State s ': es) a -> Eff es (a, s) Source #

Run the State effect with the given initial state and return the final value along with the final state (via Effectful.State.Static.Shared).

evalStateShared :: forall s (es :: [(Type -> Type) -> Type -> Type]) a. HasCallStack => s -> Eff (State s ': es) a -> Eff es a Source #

Run the State effect with the given initial state and return the final value, discarding the final state (via Effectful.State.Static.Shared).

execStateShared :: forall s (es :: [(Type -> Type) -> Type -> Type]) a. HasCallStack => s -> Eff (State s ': es) a -> Eff es s Source #

Run the State effect with the given initial state and return the final state, discarding the final value (via Effectful.State.Static.Shared).

Operations

get :: forall s (es :: [Effect]). (HasCallStack, State s :> es) => Eff es s Source #

Fetch the current value of the state.

gets :: forall s (es :: [Effect]) a. (HasCallStack, State s :> es) => (s -> a) -> Eff es a Source #

Get a function of the current state.

gets f ≡ f <$> get

put :: forall s (es :: [Effect]). (HasCallStack, State s :> es) => s -> Eff es () Source #

Set the current state to the given value.

state :: forall s (es :: [Effect]) a. (HasCallStack, State s :> es) => (s -> (a, s)) -> Eff es a Source #

Apply the function to the current state and return a value.

modify :: forall s (es :: [Effect]). (HasCallStack, State s :> es) => (s -> s) -> Eff es () Source #

Apply the function to the current state.

modify f ≡ state (\s -> ((), f s))

stateM :: forall s (es :: [Effect]) a. (HasCallStack, State s :> es) => (s -> Eff es (a, s)) -> Eff es a Source #

Apply the monadic function to the current state and return a value.

modifyM :: forall s (es :: [Effect]). (HasCallStack, State s :> es) => (s -> Eff es s) -> Eff es () Source #

Apply the monadic function to the current state.

modifyM f ≡ stateM (\s -> ((), ) <$> f s)