data-effects-0.2.0.0: A basic framework for effect systems based on effects represented by GADTs.
Copyright(c) 2023 Sayo Koyoneda
LicenseMPL-2.0 (see the file LICENSE)
Maintainerymdfield@outlook.jp
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageGHC2021

Data.Effect.Except

Description

 

Documentation

data Throw e a where Source #

Constructors

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

data Catch e (f :: Type -> Type) a where Source #

Constructors

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

Instances

Instances details
() => HFunctor (Catch e) Source # 
Instance details

Defined in Data.Effect.Except

Methods

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

type LThrow e = LiftFOE (Throw e) Source #

pattern LThrow :: forall a e f a1. () => forall. (a ~ a1, ()) => e -> LiftFOE (Throw e) f a Source #

throw :: forall e a f. SendFOE (Throw e) f => e -> f a Source #

throw' :: forall {k} (tag :: k) e a f. SendFOE (Tag (Throw e) tag) f => e -> f a Source #

throw'' :: forall {k} (key :: k) e a f. SendFOEBy key (Throw e) f => e -> f a Source #

catch :: forall a e f. SendHOE (Catch e) f => f a -> (e -> f a) -> f a Source #

catch' :: forall {k} (tag :: k) a e f. SendHOE (TagH (Catch e) tag) f => f a -> (e -> f a) -> f a Source #

catch'' :: forall {k} (key :: k) a e f. SendHOEBy key (Catch e) f => f a -> (e -> f a) -> f a Source #

liftEither :: (Throw e <: f, Applicative f) => Either e a -> f a Source #

joinEither :: (Throw e <: m, Monad m) => m (Either e a) -> m a Source #

joinExcept :: Monad m => Either (m a) a -> m a Source #

exc :: Monad m => m (Either (m a) a) -> m a Source #

withExcept :: (Catch e <<: f, Throw e <: f, Applicative f) => f a -> (e -> f ()) -> f a Source #

onExcept :: (Catch e <<: f, Throw e <: f, Applicative f) => f a -> f () -> f a Source #