data-effects-0.4.0.2: A basic framework for effect systems based on effects represented by GADTs.
Copyright(c) 2023-2025 Sayo contributors
LicenseMPL-2.0 (see the file LICENSE)
Maintainerymdfield@outlook.jp
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Effect.Except

Description

An effect to escape from the normal control structure with an exception value in the middle of a context.

Synopsis

Documentation

throw :: forall (e :: Type) (b :: Type) a es ff c. (Free c ff, a ~ Eff ff es, (:>) (Throw e) es) => e -> a b Source #

catch :: forall (b :: Type) (e :: Type) a es ff c. (Free c ff, a ~ Eff ff es, (:>) (Catch e) es) => a b -> (e -> a b) -> a b Source #

withExcept Source #

Arguments

:: forall e es a ff c. (Catch e :> es, Throw e :> es, Applicative (Eff ff es), Free c ff) 
=> Eff ff es a

Scope to which the exception handler applies

-> (e -> Eff ff es ())

Exception handler

-> Eff ff es a 

If an exception occurs, executes the given exception handler, but the exception is not stopped there and is rethrown.

liftEither :: forall e es a ff c. (Throw e :> es, Applicative (Eff ff es), Free c ff) => Either e a -> Eff ff es a Source #

Throws the given Either value as an exception if it is Left.

joinEither :: forall e es a ff c. (Throw e :> es, Monad (Eff ff es), Free c ff) => Eff ff es (Either e a) -> Eff ff es a Source #

Throws the result of the given action as an exception if it is Left.

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

If the given Either value is Left, execute it as an action.

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

If the result of the given action is Left, execute it as an action.

onExcept Source #

Arguments

:: forall e es ff a c. (Catch e :> es, Throw e :> es, Applicative (Eff ff es), Free c ff) 
=> Eff ff es a

Scope in which to detect exceptions

-> Eff ff es ()

Action to execute in case of an exception

-> Eff ff es a 

If an exception occurs, executes the specified action, but the exception is not stopped there and is rethrown.

runThrowIO :: forall e es ff a c. (Emb IO :> es, Exception e, Monad (Eff ff es), Free c ff) => Eff ff (Throw e ': es) a -> Eff ff es a Source #

Interpret the Throw effect based on an IO-fused semantics using IO-level exceptions.

runCatchIO :: forall e es ff a c. (UnliftIO :> es, Emb IO :> es, Exception e, Monad (Eff ff es), Free c ff) => Eff ff (Catch e ': es) a -> Eff ff es a Source #

Interpret the Catch effect based on an IO-fused semantics using IO-level exceptions.

throw' :: forall key (e :: Type) (b :: Type) a es ff c. (Free c ff, a ~ Eff ff es, Has key (Throw e) es) => e -> a b Source #

throw'' :: forall tag (e :: Type) (b :: Type) a es ff c. (Free c ff, a ~ Eff ff es, (:>) (Tagged tag (Throw e)) es) => e -> a b Source #

throw'_ :: forall (e :: Type) (b :: Type) a es ff c. (Free c ff, a ~ Eff ff es, In (Throw e) es) => e -> a b Source #

catch' :: forall key (b :: Type) (e :: Type) a es ff c. (Free c ff, a ~ Eff ff es, Has key (Catch e) es) => a b -> (e -> a b) -> a b Source #

catch'' :: forall tag (b :: Type) (e :: Type) a es ff c. (Free c ff, a ~ Eff ff es, (:>) (Tagged tag (Catch e)) es) => a b -> (e -> a b) -> a b Source #

catch'_ :: forall (b :: Type) (e :: Type) a es ff c. (Free c ff, a ~ Eff ff es, In (Catch e) es) => a b -> (e -> a b) -> a b Source #

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

An effect to catch exceptions.

Constructors

Catch

Catches exceptions within a scope and processes them according to the given exception handler.

Fields

  • :: forall (a :: Type -> Type) b e. a b

    The scope in which to catch exceptions.

  • -> (e -> a b)

    Exception handler. Defines the processing to perform when an exception is thrown within the scope.

  • -> Catch e a b
     

Instances

Instances details
HFunctor (Catch w) 
Instance details

Defined in Data.Effect

Methods

hfmap :: (forall x. f x -> g x) -> Catch w f a -> Catch w g a #

type LabelOf (Catch w) 
Instance details

Defined in Data.Effect

type OrderOf (Catch w) 
Instance details

Defined in Data.Effect

data Throw e (a :: Type -> Type) b where #

An effect to escape from the normal control structure with an exception value of type e in the middle of a context.

Constructors

Throw :: forall e (a :: Type -> Type) b. e -> Throw e a b

Throws an exception; that is, escapes from the normal control structure with an exception value in the middle of a context.

Instances

Instances details
FirstOrder (Throw e) 
Instance details

Defined in Data.Effect

HFunctor (Throw e) 
Instance details

Defined in Data.Effect

Methods

hfmap :: (forall x. f x -> g x) -> Throw e f a -> Throw e g a #

type LabelOf (Throw e) 
Instance details

Defined in Data.Effect

type OrderOf (Throw e) 
Instance details

Defined in Data.Effect