effet-0.3.0.2: An Effect System based on Type Classes

Copyright(c) Michael Szvetits 2020
LicenseBSD3 (see the file LICENSE)
Maintainertypedbyte@qualified.name
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Control.Effect.Error

Contents

Description

The error effect, similar to the MonadError type class from the mtl library.

Synopsis

Tagged Error Effect

class Monad m => Error' tag e m | tag m -> e where Source #

An effect that equips a computation with the ability to throw and catch exceptions.

Methods

throwError' :: e -> m a Source #

Throws an exception during the computation and begins exception processing.

catchError' :: m a -> (e -> m a) -> m a Source #

Catches an exception in order to handle it and return to normal execution.

Instances
Monad m => Error' (tag :: k) e (ExceptT e m) Source # 
Instance details

Defined in Control.Effect.Error

Methods

throwError' :: e -> ExceptT e m a Source #

catchError' :: ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a Source #

Handle (Error' tag e) t m => Error' (tag :: k) e (EachVia (Error' tag e ': effs) t m) Source # 
Instance details

Defined in Control.Effect.Error

Methods

throwError' :: e -> EachVia (Error' tag e ': effs) t m a Source #

catchError' :: EachVia (Error' tag e ': effs) t m a -> (e -> EachVia (Error' tag e ': effs) t m a) -> EachVia (Error' tag e ': effs) t m a Source #

Find (Error' tag e) effs t m => Error' (tag :: k) e (EachVia (other ': effs) t m) Source # 
Instance details

Defined in Control.Effect.Error

Methods

throwError' :: e -> EachVia (other ': effs) t m a Source #

catchError' :: EachVia (other ': effs) t m a -> (e -> EachVia (other ': effs) t m a) -> EachVia (other ': effs) t m a Source #

Control (Error' tag e) t m => Error' (tag :: k) e (EachVia ([] :: [Effect]) t m) Source # 
Instance details

Defined in Control.Effect.Error

Methods

throwError' :: e -> EachVia [] t m a Source #

catchError' :: EachVia [] t m a -> (e -> EachVia [] t m a) -> EachVia [] t m a Source #

Error' new e m => Error' (tag :: k2) e (Tagger tag new m) Source # 
Instance details

Defined in Control.Effect.Error

Methods

throwError' :: e -> Tagger tag new m a Source #

catchError' :: Tagger tag new m a -> (e -> Tagger tag new m a) -> Tagger tag new m a Source #

Untagged Error Effect

If you don't require disambiguation of multiple error effects (i.e., you only have one error effect in your monadic context), it is recommended to always use the untagged error effect.

type Error e = Error' G e Source #

throwError :: Error e m => e -> m a Source #

catchError :: Error e m => m a -> (e -> m a) -> m a Source #

Convenience Functions

If you don't require disambiguation of multiple error effects (i.e., you only have one error effect in your monadic context), it is recommended to always use the untagged functions.

liftEither' :: forall tag e m a. Error' tag e m => Either e a -> m a Source #

Lifts an Either e into any Error' e.

liftEither :: Error e m => Either e a -> m a Source #

The untagged version of liftEither'.

Interpretations

runError' :: (Error' tag e `Via` ExceptT e) m a -> m (Either e a) Source #

Runs the error effect by wrapping exceptions in the Either type.

runError :: (Error e `Via` ExceptT e) m a -> m (Either e a) Source #

The untagged version of runError'.

Tagging and Untagging

Conversion functions between the tagged and untagged error effect, usually used in combination with type applications, like:

    tagError' @"newTag" program
    retagError' @"oldTag" @"newTag" program
    untagError' @"erasedTag" program

tagError' :: forall new e m a. Via (Error' G e) (Tagger G new) m a -> m a Source #

retagError' :: forall tag new e m a. Via (Error' tag e) (Tagger tag new) m a -> m a Source #

untagError' :: forall tag e m a. Via (Error' tag e) (Tagger tag G) m a -> m a Source #