effectful-st-0.0.0.0: `ST`-style mutation for `effectful`.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Effectful.ST

Description

This modules provides the STE effect; a way to run the effect purely, with Prim, or with IOE; and functions for lifting abstract and concrete state-transformer actions into Eff.

Synopsis

Effect

data STE s :: Effect Source #

An effect for delimited primitive state-transformer actions.

Instances

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

Defined in Effectful.ST

data StaticRep (STE s) Source # 
Instance details

Defined in Effectful.ST

data StaticRep (STE s) = STERep

Handlers

runSTE :: (forall s. Eff (STE s ': es) a) -> Eff es a Source #

Run an Eff computation with primitive state-transformer actions purely.

steAsPrim :: Prim :> es => Eff (STE (PrimState (Eff es)) ': es) a -> Eff es a Source #

Interpret STE as Prim.

steAsIOE :: IOE :> es => Eff (STE RealWorld ': es) a -> Eff es a Source #

Interpret STE as IOE.

Operations

Prim to STE

primToSTE :: (PrimBase m, STE s :> es, PrimState m ~ s) => m a -> Eff es a Source #

Lift a primitive state-transformer action with STE.

stToSTE :: STE s :> es => ST s a -> Eff es a Source #

Lift a strict ST action with STE.

stToSTE' :: STE s :> es => ST s a -> Eff es a Source #

Lift a lazy ST action with STE.

ioToSTE :: STE RealWorld :> es => IO a -> Eff es a Source #

Lift an IO action with STE.

Prim to IOE

primToIOE :: (PrimBase m, IOE :> es, PrimState m ~ RealWorld) => m a -> Eff es a Source #

Lift a primitive state-transformer action with IOE.

stToIOE :: IOE :> es => ST RealWorld a -> Eff es a Source #

Lift a strict ST action with IOE.

stToIOE' :: IOE :> es => ST RealWorld a -> Eff es a Source #

Lift a lazy ST action with IOE.