polysemy-resume-0.1.0.0: Polysemy error tracking
Safe HaskellNone
LanguageHaskell2010

Polysemy.Resume

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 (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 

Instances

Instances details
type DefiningModule Stop Source # 
Instance details

Defined in Polysemy.Resume.Data.Stop

type DefiningModule Stop = "Polysemy.Resume.Data.Stop"

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

data Resumable err eff m a 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. This 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

resumable :: forall (eff :: Effect) (err :: *) (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.

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

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 eff err 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 (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.

resumeHoist :: forall err err' eff 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 err' eff r a. Members [Resumable err eff, Stop err'] r => err' -> Sem (eff ': r) a -> Sem r a 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 err' eff 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 err' eff 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 a. Members [Resumable err eff, Stop err] r => Sem (eff ': r) a -> Sem r a Source #

Variant of resumeHoist that uses the unchanged error.

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 eff err 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 eff err 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 eff 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 eff handled err r. Members [eff, Error err] r => (err -> Maybe handled) -> InterpreterFor (Resumable handled eff) r Source #

Reinterpreting variant of resumableFor.

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

Convert a program using regular Errors to one using Stop.

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

Convert a program using Stop to one using Error.