classy-effects-0.1.0.1: An interface for a handler-independent, typeclass-based effect system.
Copyright(c) 2023 Yamada Ryo
LicenseMPL-2.0 (see the file LICENSE)
Maintainerymdfield@outlook.jp
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageGHC2021

Control.Effect.Class.Except

Description

 

Documentation

class Throw e (f :: Type -> Type) where Source #

Methods

throw :: e -> f a Source #

Instances

Instances details
SendIns (ThrowI e) f => Throw e (EffectsVia EffectDataHandler f) Source # 
Instance details

Defined in Control.Effect.Class.Except

Methods

throw :: e -> EffectsVia EffectDataHandler f a Source #

class Catch e f where Source #

Methods

catch :: f a -> (e -> f a) -> f a Source #

Instances

Instances details
SendSig (CatchS e) f => Catch e (EffectsVia EffectDataHandler f :: Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Effect.Class.Except

Methods

catch :: forall (a :: k). EffectsVia EffectDataHandler f a -> (e -> EffectsVia EffectDataHandler f a) -> EffectsVia EffectDataHandler f a Source #

data ThrowI (e :: Type) (a :: Type) where Source #

Constructors

Throw :: forall e a. e -> ThrowI e a 

type ThrowS e = LiftIns (ThrowI e) Source #

data CatchS (e :: Type) f (a :: Type) where Source #

Constructors

Catch :: forall e f a. (f a) -> (e -> f a) -> CatchS e f a 

Instances

Instances details
HFunctor (CatchS e) Source # 
Instance details

Defined in Control.Effect.Class.Except

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> CatchS e f :-> CatchS e g #

class (Throw e f, Catch e f) => Except e (f :: Type -> Type) Source #

Instances

Instances details
(Throw e (EffectsVia EffectDataHandler f), Catch e (EffectsVia EffectDataHandler f)) => Except e (EffectsVia EffectDataHandler f) Source # 
Instance details

Defined in Control.Effect.Class.Except

type ExceptD e = (:+:) (CatchS e) (LiftIns (ThrowI e)) Source #

pattern ThrowS :: () => a_6989586621679055785 ~ a => e -> LiftIns (ThrowI e) f a_6989586621679055785 Source #