fused-effects-resumable-0.1.0.0: Resumable exceptions for the fused-effects ecosystem.

Safe HaskellNone
LanguageHaskell2010

Control.Effect.Resumable

Contents

Description

An effect providing the ability to throw exceptions from a context. If an exception is thrown, the calling context may choose to resume the computation. Type safety of the resumed operation is preserved by parametricity achieved from the -XGADTs extension.

Predefined carriers:

Synopsis

Resumable effect

data Resumable err m k Source #

Errors which can be resumed with values of some existentially-quantified type.

Since: 0.1.0.0

Constructors

Resumable (err a) (a -> m k) 
Instances
HFunctor (Resumable err) Source # 
Instance details

Defined in Control.Effect.Resumable

Methods

hmap :: Functor m => (forall x. m x -> n x) -> Resumable err m a -> Resumable err n a #

Effect (Resumable err) Source # 
Instance details

Defined in Control.Effect.Resumable

Methods

thread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> n (ctx x)) -> Resumable err m a -> Resumable err n (ctx a) #

Functor m => Functor (Resumable err m) Source # 
Instance details

Defined in Control.Effect.Resumable

Methods

fmap :: (a -> b) -> Resumable err m a -> Resumable err m b #

(<$) :: a -> Resumable err m b -> Resumable err m a #

Algebra sig m => Algebra (Resumable err :+: sig) (ResumableC err m) Source # 
Instance details

Defined in Control.Carrier.Resumable.Resume

Methods

alg :: (Resumable err :+: sig) (ResumableC err m) a -> ResumableC err m a #

(Algebra sig m, Effect sig) => Algebra (Resumable err :+: sig) (ResumableC err m) Source # 
Instance details

Defined in Control.Carrier.Resumable.Either

Methods

alg :: (Resumable err :+: sig) (ResumableC err m) a -> ResumableC err m a #

throwResumable :: Has (Resumable err) sig m => err a -> m a Source #

Throw an error which can be resumed with a value of its result type. Note that the type parameters in the err a paramater and m a parameter must match up; this indicates the type with which the error must be resumed.

Since: 0.1.0.0

Re-exports

type Has (eff :: (Type -> Type) -> Type -> Type) (sig :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) = (Members eff sig, Algebra sig m) #

m is a carrier for sig containing eff.

Note that if eff is a sum, it will be decomposed into multiple Member constraints. While this technically allows one to combine multiple unrelated effects into a single Has constraint, doing so has two significant drawbacks:

  1. Due to a problem with recursive type families, this can lead to significantly slower compiles.
  2. It defeats ghc’s warnings for redundant constraints, and thus can lead to a proliferation of redundant constraints as code is changed.

run :: Identity a -> a #

Run an action exhausted of effects to produce its final result value.

Since: fused-effects-1.0.0.0