polysemy-resume: Polysemy error tracking

[ error, library ] [ Propose Tags ]
Versions [RSS] 0.1.0.0, 0.1.0.1, 0.1.0.2, 0.1.0.3, 0.1.0.4, 0.2.0.0, 0.3.0.0, 0.4.0.0, 0.5.0.0, 0.6.0.0, 0.7.0.0, 0.8.0.0, 0.8.0.1
Change log changelog.md
Dependencies base (>=4 && <5), incipit-core (>=0.4 && <0.6), polysemy (>=1.9 && <1.10), transformers [details]
License BSD-2-Clause-Patent
Copyright 2023 Torsten Schmits
Author Torsten Schmits
Maintainer hackage@tryp.io
Category Error
Home page https://github.com/tek/polysemy-resume#readme
Bug tracker https://github.com/tek/polysemy-resume/issues
Source repo head: git clone https://github.com/tek/polysemy-resume
Uploaded by tek at 2023-09-23T16:41:14Z
Distributions
Reverse Dependencies 5 direct, 23 indirect [details]
Downloads 1449 total (45 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for polysemy-resume-0.8.0.1

[back to package description]

About

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

Example

Given these two effects and an error:

import Polysemy.Resume (Resumable, Stop, resumable, resumableFor, resume, runStop, stop)

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

makeSem ''Stopper

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

makeSem ''Resumer

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

we implement an interpreter for Stopper that may throw the error Boom, but we do not want to hardcode that fact into the effect constructors, as in:

data Stopper :: Effect where
  StopBang :: Stopper m (Either Boom ())

because we might want to provide alternative interpreters that do not have this requirement, and Boom might contain information about the interpreter implementation that we don't want to leak into the effect signature.

On the other hand, having no guarantee that the consumer program knows about or catches the error requires us to manually ensure we handle them at the appropriate location. This is especially critical due to the fact that using catch requires an Error membership, which in turn requires the Error to be handled outside of the consumer again, hiding any new uses of the throwing interpreter in another part of the program.

A first attempt at making this situation safer is to introduce a wrapping effect:

data Resumable err eff m a where
  Resumable ::
    ∀ err eff r a .
    Weaving eff (Sem r) a ->
    Resumable err eff (Sem r) (Either err a)

which we now use instead of the raw eff in consumers:

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

For a nicer syntax, there is a type alias for Resumable:

Member (Stopper !! Boom) r =>

We have now marked the interpreter for Resumer, which consumes Stopper, as being capable of handling the Boom error when it occurs in Stopper. The function resume takes an error handler as its second argument with which we can catch Boom.

The interpreter for Stopper could look like this:

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

Instead of Error, we are using Stop here, which is identical except for not providing Catch. This only serves to be more explicit about the intention of the error, but a regular Error can be converted with stopOnError.

In order to convert this interpreter to a Resumable, we use resumable:

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

resumable weaves interpretStopper and its Stop together into a Resumable, which is then consumed entirely by resume inside interpretResumer, so no additional effects have to be handled.

Higher-Order Effects

Converting an interpreter with resumable only works in rather simple conditions. If there are higher-order effects involved, you may get incorrect semantics, for example when inserting a finally around the entire resumable program:

resumable (interpretStopper (sem `finally` releaseResources))

In this case, releaseResources is executed after each use of StopBang or StopBoom. This requires the use of interpretResumable and interpretResumableH, which take handler functions like interpret:

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

Partial Error Handling

Of course, one requirement in the problem description still remains unsatisfied: We might want to hide implementation details of interpretStopper from consumers. We can do that by transforming the Boom error into a more abstract version at the interpretation site:

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

bangOnly :: Boom -> Maybe Blip
bangOnly = \case
  Bang n -> Just (Blip n)
  Boom _ -> Nothing

Now Boom might have contained information about e.g. an http client backend, and we're transforming that into an error that just says "http error". If a consumer also deals with that backend, we might keep that information.

This modified error can now be used for Resumable. First, we change the Resumer interpreter to use Blip:

interpretResumerPartial ::
  Member (Resumable Blip Stopper) r =>
  InterpreterFor Resumer r
interpretResumerPartial =
  interpret \ MainProgram ->
    resume (192 <$ stopBang) \ (Blip num) ->
      pure (num * 3)

Then we use a different adapter function for interpretStopper:

>>> runError (resumableFor bangOnly interpretStopper (interpretResumerPartial mainProgram))
Right 39

resumableFor transforms the error and passes it to the consumer if it is a Just, and rethrows it if not. Since the error was only partially handled and unhandled errors get thrown as Error, we have to call runError on the result, to obtain an Either.

If the consumer uses a constructor that throws an unhandled variant of the error, it propagates to the call site:

interpretResumerPartialUnhandled ::
  Member (Resumable Blip Stopper) r =>
  InterpreterFor Resumer r
interpretResumerPartialUnhandled =
  interpret \ MainProgram ->
    resume (192 <$ stopBoom) \ (Blip num) ->
      pure (num * 3)

>>> runError ((resumableFor bangOnly interpretStopper) (interpretResumerPartialUnhandled mainProgram))
Left (Boom "ouch")

Thanks

to @KingOfTheHomeless for providing the initial implementation and lots of consultation!