polysemy-resume-0.8.0.1: Polysemy error tracking
Safe HaskellSafe-Inferred
LanguageGHC2021

Polysemy.Resume

Description

 
Synopsis

Introduction

This library provides the Polysemy effects Resumable and Stop for the purpose of safely connecting throwing and catching errors across different interpreters.

Consider the effect:

data Stopper :: Effect where
  StopBang :: Stopper m ()
  StopBoom :: Stopper m ()

makeSem ''Stopper

data Boom =
  Boom { unBoom :: Text }
  |
  Bang { unBang :: Int }
  deriving stock (Eq, Show)

interpretStopper ::
  Member (Error Boom) r =>
  InterpreterFor Stopper r
interpretStopper =
  interpret \case
    StopBang -> throw (Bang 13)
    StopBoom -> throw (Boom "ouch")

If we want to use Stopper in the interpreter of another effect, we have no way of knowing about the errors thrown by its interpreter, even though we can catch Boom! This library makes the connection explicit by changing Error to Stop and wrapping Stopper in Resumable when using it in an effect stack:

data Stop e :: Effect where Source #

An effect similar to Error without the ability to be caught. Used to signal that an error is supposed to be expected by dependent programs.

interpretStopper ::
  Member (Stop Boom) r =>
  InterpreterFor Stopper r
interpretStopper =
  interpret \case
    StopBang -> stop (Bang 13)
    StopBoom -> stop (Boom "ouch")

Constructors

Stop :: e -> Stop e m a

Abort a computation with an error value.

stop :: forall e r a. Member (Stop e) r => e -> Sem r a Source #

Abort a computation with an error value.

type (!!) eff err = Resumable err eff Source #

Infix alias for Resumable.

Member (Stopper !! Boom) r =>

data Resumable err eff :: Effect Source #

Effect that wraps another effect eff, marking it as throwing errors of type err using Stop.

Resuming a Stopped Computation

resume :: forall err eff r a. Member (Resumable err eff) r => Sem (eff : r) a -> (err -> Sem r a) -> Sem r a Source #

Execute the action of a regular effect eff so that any error of type err that maybe be thrown by the (unknown) interpreter used for eff will be caught here and handled by the handler argument. This is similar to catch with the additional guarantee that the error will have to be explicitly matched, therefore preventing accidental failure to handle an error and bubbling it up to main. It also imposes a membership of Resumable err eff on the program, requiring the interpreter for eff to be adapted with resumable.

data Resumer :: Effect where
  MainProgram :: Resumer m Int

makeSem ''Resumer

interpretResumer ::
  Member (Resumable Boom Stopper) r =>
  InterpreterFor Resumer r
interpretResumer =
  interpret \ MainProgram ->
    resume (192 <$ stopBang) \ _ ->
      pure 237

(!!) :: forall err eff r a. Member (Resumable err eff) r => Sem (eff : r) a -> (err -> Sem r a) -> Sem r a Source #

Operator version of resume.

Since: 0.2.0.0

interpretResumable :: forall (err :: Type) (eff :: Effect) r. FirstOrder eff "interpretResumable" => (forall x r0. eff (Sem r0) x -> Sem (Stop err : r) x) -> InterpreterFor (Resumable err eff) r Source #

Create an interpreter for Resumable err eff by supplying a handler function for eff, analogous to interpret. If the handler throws errors with Stop, they will be absorbed into Resumable, to be caught by resume in a downstream interpreter.

interpretStopperResumable ::
  InterpreterFor Stopper r
interpretStopperResumable =
  interpretResumable \case
    StopBang -> stop (Bang 13)
    StopBoom -> stop (Boom "ouch")
>>> run $ interpretStopperResumable (interpretResumer mainProgram)
237

interpretResumableH Source #

Arguments

:: forall (err :: Type) (eff :: Effect) (r :: EffectRow). (forall x r0. eff (Sem r0) x -> Tactical (Resumable err eff) (Sem r0) (Stop err : r) x)

This handler function has Stop err in its stack, allowing it to absorb errors.

-> InterpreterFor (Resumable err eff) r 

Like interpretResumable, but for higher-order effects.

interceptResumable :: forall (err :: Type) (eff :: Effect) (r :: EffectRow) (a :: Type). Member (Resumable err eff) r => FirstOrder eff "interceptResumable" => (forall x r0. eff (Sem r0) x -> Sem (Stop err : r) x) -> Sem r a -> Sem r a Source #

Interceptor variant of interpretResumable.

interceptResumableH :: forall (err :: Type) (eff :: Effect) (r :: EffectRow) (a :: Type). Member (Resumable err eff) r => (forall x r0. eff (Sem r0) x -> Tactical (Resumable err eff) (Sem r0) (Stop err : r) x) -> Sem r a -> Sem r a Source #

Interceptor variant of interpretResumableH.

interceptResumableUsing :: forall (err :: Type) (eff :: Effect) (r :: EffectRow) (a :: Type). FirstOrder eff "interceptResumableUsing" => ElemOf (Resumable err eff) r -> (forall x r0. eff (Sem r0) x -> Sem (Stop err : r) x) -> Sem r a -> Sem r a Source #

Interceptor variant of interpretResumable.

interceptResumableUsingH :: forall (err :: Type) (eff :: Effect) (r :: EffectRow) (a :: Type). ElemOf (Resumable err eff) r -> (forall x r0. eff (Sem r0) x -> Tactical (Resumable err eff) (Sem r0) (Stop err : r) x) -> Sem r a -> Sem r a Source #

Interceptor variant of interpretResumableH.

resumable :: forall (err :: Type) (eff :: Effect) (r :: EffectRow). InterpreterFor eff (Stop err : r) -> InterpreterFor (Resumable err eff) r Source #

Convert a bare interpreter for eff, which (potentially) uses Stop to signal errors, into an interpreter for Resumable. Beware: This will display unsound behaviour if: * the interpreter is wrapped with actions of another effect, as in:

  interpretEff :: InterpreterFor Eff r
  ...

  interpretEffResumable :: InterpreterFor (Resumable Text Eff) r
  interpretEffResumable sem =
  resumable (interpretEff (sem finally releaseResources))
  

In this case, releaseResources will be called after every use of Eff in sem, not after the entire thunk.

  • the interpreter of a higher-order effect uses a different interpreter after using runT/bindT. In this case, it will use the original interpreter instead.

If your use case matches one of these conditions, you'll need to use interpretResumable.

>>> run $ resumable interpretStopper (interpretResumer mainProgram)
237

raiseResumable :: forall (err :: Type) (eff :: Effect) (r :: EffectRow). InterpreterTrans (Resumable err eff) eff r Source #

Convenience combinator for turning an interpreter that doesn't use Stop into a Resumable.

resumableIO :: forall (err :: Type) (eff :: Effect) (r :: EffectRow). Exception (StopExc err) => Member (Final IO) r => InterpreterFor eff (Stop err : r) -> InterpreterFor (Resumable err eff) r Source #

Like resumable, but use exceptions instead of ExceptT.

interpretScopedResumable :: forall param resource effect err r. (forall q x. param -> (resource -> Sem (Stop err : (Opaque q : r)) x) -> Sem (Stop err : (Opaque q : r)) x) -> (forall q r0 x. resource -> effect (Sem r0) x -> Sem (Stop err : (Opaque q : r)) x) -> InterpreterFor (Scoped param effect !! err) r Source #

Combined interpreter for Scoped and Resumable. This allows Stop to be sent from within the resource allocator so that the consumer receives it, terminating the entire scope.

interpretScopedResumableH :: forall param resource effect err r. (forall q x. param -> (resource -> Sem (Stop err : (Opaque q : r)) x) -> Sem (Stop err : (Opaque q : r)) x) -> (forall q r0 x. resource -> effect (Sem r0) x -> Tactical effect (Sem r0) (Stop err : (Opaque q : r)) x) -> InterpreterFor (Scoped param effect !! err) r Source #

Combined higher-order interpreter for Scoped and Resumable. This allows Stop to be sent from within the resource allocator so that the consumer receives it, terminating the entire scope.

interpretScopedResumable_ :: forall param resource effect err r. (forall q. param -> Sem (Stop err : (Opaque q : r)) resource) -> (forall q r0 x. resource -> effect (Sem r0) x -> Sem (Stop err : (Opaque q : r)) x) -> InterpreterFor (Scoped param effect !! err) r Source #

Combined interpreter for Scoped and Resumable. This allows Stop to be sent from within the resource allocator so that the consumer receives it, terminating the entire scope. In this variant, the resource allocator is a plain action.

interpretScopedResumableWith :: forall extra param resource effect err r. KnownList extra => (forall q x. param -> (resource -> Sem (extra ++ (Stop err : (Opaque q : r))) x) -> Sem (Stop err : (Opaque q : r)) x) -> (forall q r0 x. resource -> effect (Sem r0) x -> Sem (extra ++ (Stop err : (Opaque q : r))) x) -> InterpreterFor (Scoped param effect !! err) r Source #

Combined interpreter for Scoped and Resumable that allows the handler to use additional effects that are interpreted by the resource allocator. This allows Stop to be sent from within the resource allocator so that the consumer receives it, terminating the entire scope.

interpretScopedResumableWithH :: forall extra param resource effect err r. KnownList extra => (forall q x. param -> (resource -> Sem (extra ++ (Stop err : (Opaque q : r))) x) -> Sem (Stop err : (Opaque q : r)) x) -> (forall q r0 x. resource -> effect (Sem r0) x -> Tactical effect (Sem r0) (extra ++ ([Stop err, Opaque q] ++ r)) x) -> InterpreterFor (Scoped param effect !! err) r Source #

Combined higher-order interpreter for Scoped and Resumable that allows the handler to use additional effects that are interpreted by the resource allocator. This allows Stop to be sent from within the resource allocator so that the consumer receives it, terminating the entire scope.

interpretScopedResumableWith_ :: forall extra param effect err r. KnownList extra => (forall q x. param -> Sem (extra ++ (Stop err : (Opaque q : r))) x -> Sem (Stop err : (Opaque q : r)) x) -> (forall q r0 x. effect (Sem r0) x -> Sem (extra ++ (Stop err : (Opaque q : r))) x) -> InterpreterFor (Scoped param effect !! err) r Source #

Combined interpreter for Scoped and Resumable that allows the handler to use additional effects that are interpreted by the resource allocator. This allows Stop to be sent from within the resource allocator so that the consumer receives it, terminating the entire scope. In this variant, no resource is used and the allocator is a plain interpreter.

interpretResumableScoped :: forall param resource effect err r. (forall q x. param -> (resource -> Sem (Opaque q : r) x) -> Sem (Opaque q : r) x) -> (forall q r0 x. resource -> effect (Sem r0) x -> Sem (Stop err : (Opaque q : r)) x) -> InterpreterFor (Scoped param (effect !! err)) r Source #

Combined interpreter for Resumable and Scoped. In this variant, only the handler may send Stop, but this allows resumption to happen on each action inside of the scope.

interpretResumableScopedH :: forall param resource effect err r. (forall q x. param -> (resource -> Sem (Opaque q : r) x) -> Sem (Opaque q : r) x) -> (forall q r0 x. resource -> effect (Sem r0) x -> Tactical (effect !! err) (Sem r0) (Stop err : (Opaque q : r)) x) -> InterpreterFor (Scoped param (effect !! err)) r Source #

Combined higher-order interpreter for Resumable and Scoped. In this variant, only the handler may send Stop, but this allows resumption to happen on each action inside of the scope.

interpretResumableScoped_ :: forall param resource effect err r. (param -> Sem r resource) -> (forall q r0 x. resource -> effect (Sem r0) x -> Sem (Stop err : (Opaque q : r)) x) -> InterpreterFor (Scoped param (effect !! err)) r Source #

Combined interpreter for Resumable and Scoped. In this variant: - Only the handler may send Stop, but this allows resumption to happen on each action inside of the scope. - The resource allocator is a plain action.

interpretResumableScopedWith :: forall extra param resource effect err r. KnownList extra => (forall q x. param -> (resource -> Sem (extra ++ (Opaque q : r)) x) -> Sem (Opaque q : r) x) -> (forall r0 x. resource -> effect (Sem r0) x -> Sem (Stop err : (extra ++ r)) x) -> InterpreterFor (Scoped param (effect !! err)) r Source #

Combined interpreter for Resumable and Scoped that allows the handler to use additional effects that are interpreted by the resource allocator. In this variant, only the handler may send Stop, but this allows resumption to happen on each action inside of the scope.

interpretResumableScopedWithH :: forall extra param resource effect err r. KnownList extra => (forall q x. param -> (resource -> Sem (extra ++ (Opaque q : r)) x) -> Sem (Opaque q : r) x) -> (forall q r0 x. resource -> effect (Sem r0) x -> Tactical (effect !! err) (Sem r0) (Stop err : (extra ++ (Opaque q : r))) x) -> InterpreterFor (Scoped param (effect !! err)) r Source #

Combined higher-order interpreter for Resumable and Scoped that allows the handler to use additional effects that are interpreted by the resource allocator. In this variant, only the handler may send Stop, but this allows resumption to happen on each action inside of the scope.

interpretResumableScopedWith_ :: forall extra param effect err r. KnownList extra => (forall q x. param -> Sem (extra ++ (Opaque q : r)) x -> Sem (Opaque q : r) x) -> (forall r0 x. effect (Sem r0) x -> Sem (Stop err : (extra ++ r)) x) -> InterpreterFor (Scoped param (effect !! err)) r Source #

Combined interpreter for Resumable and Scoped that allows the handler to use additional effects that are interpreted by the resource allocator. In this variant: - Only the handler may send Stop, but this allows resumption to happen on each action inside of the scope. - No resource is used and the allocator is a plain interpreter.

interpretScopedR :: forall param resource effect eo ei r. (forall q x. param -> (resource -> Sem (Stop eo : (Opaque q : r)) x) -> Sem (Stop eo : (Opaque q : r)) x) -> (forall q r0 x. resource -> effect (Sem r0) x -> Sem (Stop ei : (Stop eo : (Opaque q : r))) x) -> InterpreterFor (Scoped param (effect !! ei) !! eo) r Source #

Combined interpreter for Scoped and Resumable. In this variant, both the handler and the scope may send different errors via Stop, encoding the concept that the resource allocation may fail to prevent the scope from being executed, and each individual scoped action may fail, continuing the scope execution on resumption.

interpretScopedRH :: forall param resource effect eo ei r. (forall q x. param -> (resource -> Sem (Stop eo : (Opaque q : r)) x) -> Sem (Stop eo : (Opaque q : r)) x) -> (forall q r0 x. resource -> effect (Sem r0) x -> Tactical (effect !! ei) (Sem r0) (Stop ei : (Stop eo : (Opaque q : r))) x) -> InterpreterFor (Scoped param (effect !! ei) !! eo) r Source #

Combined higher-order interpreter for Resumable and Scoped. In this variant, both the handler and the scope may send different errors via Stop, encoding the concept that the resource allocation may fail to prevent the scope from being executed, and each individual scoped action may fail, continuing the scope execution on resumption.

interpretScopedR_ :: forall param resource effect eo ei r. (param -> Sem (Stop eo : r) resource) -> (forall q r0 x. resource -> effect (Sem r0) x -> Sem (Stop ei : (Stop eo : (Opaque q : r))) x) -> InterpreterFor (Scoped param (effect !! ei) !! eo) r Source #

Combined interpreter for Scoped and Resumable. In this variant: - Both the handler and the scope may send different errors via Stop, encoding the concept that the resource allocation may fail to prevent the scope from being executed, and each individual scoped action may fail, continuing the scope execution on resumption. - The resource allocator is a plain action.

interpretScopedRWith :: forall extra param resource effect eo ei r. KnownList extra => (forall q x. param -> (resource -> Sem (extra ++ (Stop eo : (Opaque q : r))) x) -> Sem (Stop eo : (Opaque q : r)) x) -> (forall q r0 x. resource -> effect (Sem r0) x -> Sem (Stop ei : (extra ++ (Stop eo : (Opaque q : r)))) x) -> InterpreterFor (Scoped param (effect !! ei) !! eo) r Source #

Combined interpreter for Scoped and Resumable that allows the handler to use additional effects that are interpreted by the resource allocator. In this variant, both the handler and the scope may send different errors via Stop, encoding the concept that the resource allocation may fail to prevent the scope from being executed, and each individual scoped action may fail, continuing the scope execution on resumption.

interpretScopedRWithH :: forall extra param resource effect eo ei r. KnownList extra => (forall q x. param -> (resource -> Sem (extra ++ (Stop eo : (Opaque q : r))) x) -> Sem (Stop eo : (Opaque q : r)) x) -> (forall q r0 x. resource -> effect (Sem r0) x -> Tactical (effect !! ei) (Sem r0) (Stop ei : (extra ++ (Stop eo : (Opaque q : r)))) x) -> InterpreterFor (Scoped param (effect !! ei) !! eo) r Source #

Combined higher-order interpreter for Scoped and Resumable that allows the handler to use additional effects that are interpreted by the resource allocator. In this variant, both the handler and the scope may send different errors via Stop, encoding the concept that the resource allocation may fail to prevent the scope from being executed, and each individual scoped action may fail, continuing the scope execution on resumption.

interpretScopedRWith_ :: forall extra param effect eo ei r. KnownList extra => (forall q x. param -> Sem (extra ++ (Stop eo : (Opaque q : r))) x -> Sem (Stop eo : (Opaque q : r)) x) -> (forall q r0 x. effect (Sem r0) x -> Sem (Stop ei : (extra ++ (Stop eo : (Opaque q : r)))) x) -> InterpreterFor (Scoped param (effect !! ei) !! eo) r Source #

Combined interpreter for Scoped and Resumable that allows the handler to use additional effects that are interpreted by the resource allocator. - Both the handler and the scope may send different errors via Stop, encoding the concept that the resource allocation may fail to prevent the scope from being executed, and each individual scoped action may fail, continuing the scope execution on resumption. - The resource allocator is a plain action.

Partial Handlers

In some cases, the errors thrown by an interpreter contain details about the implementation, which we might want to hide from dependents; or it may throw fatal errors we don't want to handle at all. For this purpose, we can create partial Resumables by transforming errors before handling them:

resumableOr :: forall (err :: Type) (eff :: Effect) unhandled handled r. Member (Error unhandled) r => (err -> Either unhandled handled) -> InterpreterFor eff (Stop err : r) -> InterpreterFor (Resumable handled eff) r Source #

Convert an interpreter for eff that throws errors of type err into a Resumable, but limiting the errors handled by consumers to the type handled, which rethrowing Errors of type unhandled.

The function canHandle determines how the errors are split.

newtype Blip =
  Blip { unBlip :: Int }
  deriving stock (Eq, Show)

bangOnly :: Boom -> Either Text Blip
bangOnly = \case
  Bang n -> Right (Blip n)
  Boom msg -> Left msg

interpretResumerPartial ::
  Member (Resumable Blip Stopper) r =>
  InterpreterFor Resumer r
interpretResumerPartial =
  interpret \ MainProgram ->
    resume (192 <$ stopBang) \ (Blip num) ->
      pure (num * 3)
>>> runError (resumableFor bangOnly interpretStopper (interpretResumerPartial mainProgram))
Right 39

Various Combinators

resumeAs :: forall err eff r a. Member (Resumable err eff) r => a -> Sem (eff : r) a -> Sem r a Source #

Variant of resume that unconditionally recovers with a constant value.

(<!) :: forall err eff r a. Member (Resumable err eff) r => a -> Sem (eff : r) a -> Sem r a Source #

Operator version of resumeAs.

Since: 0.2.0.0

(!>) :: forall err eff r a. Member (Resumable err eff) r => Sem (eff : r) a -> a -> Sem r a Source #

Operator version of resumeAs, flipped version of (<!).

Since: 0.2.0.0

resumeWith :: forall err eff r a. Member (Resumable err eff) r => Sem (eff : r) a -> Sem r a -> Sem r a Source #

Variant of resume that unconditionally recovers with an action.

Since: 0.2.0.0

(!>>) :: forall err eff r a. Member (Resumable err eff) r => Sem (eff : r) a -> Sem r a -> Sem r a Source #

Operator variant of resumeWith.

Since: 0.2.0.0

resumingWith :: forall err eff r a. Member (Resumable err eff) r => Sem r a -> Sem (eff : r) a -> Sem r a Source #

Variant of resuming that unconditionally recovers with an action.

Since: 0.2.0.0

(<<!) :: forall err eff r a. Member (Resumable err eff) r => Sem r a -> Sem (eff : r) a -> Sem r a Source #

Operator variant of resumingWith.

Since: 0.2.0.0

resume_ :: forall err eff r. Member (Resumable err eff) r => Sem (eff : r) () -> Sem r () Source #

Convenience specialization of resume that silently discards errors for void programs.

resumeHoist :: forall err eff err' r a. Members [Resumable err eff, Stop err'] r => (err -> err') -> Sem (eff : r) a -> Sem r a Source #

Variant of resume that propagates the error to another Stop effect after applying a function.

resumeHoistAs :: forall err eff err' r. Members [Resumable err eff, Stop err'] r => err' -> InterpreterFor eff r Source #

Variant of resumeHoist that uses a constant value.

resuming :: forall err eff r a. Member (Resumable err eff) r => (err -> Sem r a) -> Sem (eff : r) a -> Sem r a Source #

Flipped variant of resume.

resumeHoistError :: forall err eff err' r a. Members [Resumable err eff, Error err'] r => (err -> err') -> Sem (eff : r) a -> Sem r a Source #

Variant of resume that propagates the error to an Error effect after applying a function.

resumeHoistErrorAs :: forall err eff err' r a. Members [Resumable err eff, Error err'] r => err' -> Sem (eff : r) a -> Sem r a Source #

Variant of resumeHoistError that uses the unchanged error.

restop :: forall err eff r. Members [Resumable err eff, Stop err] r => InterpreterFor eff r Source #

Variant of resumeHoist that uses the unchanged error.

resumeEither :: forall err eff r a. Member (Resumable err eff) r => Sem (eff : r) a -> Sem r (Either err a) Source #

Variant of resume that immediately produces an Either.

resumeOr :: forall err eff r a b. Member (Resumable err eff) r => Sem (eff : r) a -> (a -> Sem r b) -> (err -> Sem r b) -> Sem r b Source #

Variant of resume that takes a branch for error and success. This allows the success branch to contain other resumptions.

Since: 0.2.0.0

resumingOr :: forall err eff r a b. Member (Resumable err eff) r => (err -> Sem r b) -> Sem (eff : r) a -> (a -> Sem r b) -> Sem r b Source #

Variant of resuming that takes a branch for error and success. This allows the success branch to contain other resumptions.

Since: 0.2.0.0

resumeError :: forall err eff r a. Members [Resumable err eff, Error err] r => Sem (eff : r) a -> Sem r a Source #

Variant of resumeHoistError that uses the unchanged error.

resumableError :: forall (err :: Type) (eff :: Effect) r. InterpreterFor eff (Error err : (Stop err : r)) -> InterpreterFor (Resumable err eff) r Source #

Convert an interpreter for eff that uses Error into one using Stop and wrap it using resumable.

resumableFor :: forall (err :: Type) (eff :: Effect) handled r. Member (Error err) r => (err -> Maybe handled) -> InterpreterFor eff (Stop err : r) -> InterpreterFor (Resumable handled eff) r Source #

Variant of resumableOr that uses Maybe and rethrows the original error.

runAsResumable :: forall (err :: Type) (eff :: Effect) r. Members [Resumable err eff, Stop err] r => InterpreterFor eff r Source #

Interpret an effect eff by wrapping it in Resumable and Stop and leaving the rest up to the user.

catchResumable :: forall (err :: Type) (eff :: Effect) handled r. Members [eff, Error err] r => (err -> Maybe handled) -> InterpreterFor (Resumable handled eff) r Source #

Reinterpreting variant of resumableFor.

stopToFailWith :: forall err r. Member Fail r => (err -> Text) -> InterpreterFor (Stop err) r Source #

Transform Stop to Fail using the supplied error message rendering function.

stopToFail :: forall err r. Show err => Member Fail r => InterpreterFor (Stop err) r Source #

Transform Stop to Fail using show.

resumeFailWith :: forall err eff r. Members [Fail, Resumable err eff] r => (err -> Text) -> InterpreterFor eff r Source #

Resume a computation, converting Stop to Fail.

resumeFail :: forall err eff r. Show err => Members [Fail, Resumable err eff] r => InterpreterFor eff r Source #

Resume a computation, converting Stop to Fail using show.

mapStop :: forall err e' r a. Member (Stop e') r => (err -> e') -> Sem (Stop err : r) a -> Sem r a Source #

Map over the error type in a Stop.

replaceStop :: forall err e' r a. Member (Stop e') r => e' -> Sem (Stop err : r) a -> Sem r a Source #

Replace the error in a Stop with another type.

runStop :: Sem (Stop err : r) a -> Sem r (Either err a) Source #

Equivalent of runError.

showStop :: forall err r a. Show err => Member (Stop Text) r => Sem (Stop err : r) a -> Sem r a Source #

Convert the error type in a Stop to Text.

stopEither :: forall err r a. Member (Stop err) r => Either err a -> Sem r a Source #

Stop if the argument is Left.

stopEitherAs :: forall err err' r a. Member (Stop err') r => err' -> Either err a -> Sem r a Source #

Stop if the argument is Left, using the supplied error.

stopEitherWith :: forall err err' r a. Member (Stop err') r => (err -> err') -> Either err a -> Sem r a Source #

Stop if the argument is Left, transforming the error with f.

stopNote :: forall err r a. Member (Stop err) r => err -> Maybe a -> Sem r a Source #

Stop with the supplied error if the argument is Nothing.

stopOnError :: forall err r a. Member (Stop err) r => Sem (Error err : r) a -> Sem r a Source #

Convert a program using regular Errors to one using Stop.

stopOnErrorWith :: forall err err' r a. Member (Stop err') r => (err -> err') -> Sem (Error err : r) a -> Sem r a Source #

Convert a program using regular Errors to one using Stop.

stopToError :: forall err r a. Member (Error err) r => Sem (Stop err : r) a -> Sem r a Source #

Convert a program using Stop to one using Error.

stopToErrorIO :: forall err r a. Exception (StopExc err) => Members [Error err, Final IO] r => Sem (Stop err : r) a -> Sem r a Source #

Convert a program using Stop to one using Error.

stopToErrorWith :: forall err err' r a. Member (Error err') r => (err -> err') -> Sem (Stop err : r) a -> Sem r a Source #

Convert a program using Stop to one using Error, transforming the error with the supplied function.

stopToIOFinal :: forall err r a. Exception (StopExc err) => Member (Final IO) r => Sem (Stop err : r) a -> Sem r (Either err a) Source #

Run Stop by throwing and catching exceptions.

stopTryAny :: forall err r a. Members [Stop err, Embed IO] r => (Text -> err) -> IO a -> Sem r a Source #

Convert an IO exception to Stop using the provided transformation from Text.

stopTryIO :: forall exc err r a. Exception exc => Members [Stop err, Embed IO] r => (Text -> err) -> IO a -> Sem r a Source #

Convert an IO exception of type err to Stop using the provided transformation from Text.

stopTryIOE :: forall exc err r a. Exception exc => Members [Stop err, Embed IO] r => (exc -> err) -> IO a -> Sem r a Source #

Convert an IO exception to Stop using the provided transformation.

stopTryIOError :: forall err r a. Members [Stop err, Embed IO] r => (Text -> err) -> IO a -> Sem r a Source #

Convert an IO exception of type IOError to Stop using the provided transformation from Text.