[Haskell-cafe] Best way to implement "scoped exceptions"?
Tom Ellis
tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk
Wed Dec 28 20:38:04 UTC 2022
I'd like to implement "scoped exceptions"[1], that is, a combinator of
type
withScopedException ::
((forall a. e -> IO a) -> IO r) ->
IO (Either e r)
so I can use exceptions in a convenient way, without having to
set up fragile "action at a distance" based on the type of the thing
I'm throwing and catching, for example:
scopedExceptionExample :: IO (Either String (Either Int Void))
scopedExceptionExample = do
withScopedException $ \throw1 ->
withScopedException $ \throw2 ->
if (1 :: Int) < 0
then throw1 "Hello"
else throw2 1234
-- ghci> scopedExceptionExample
-- Right (Left 1234)
Here's a hacky way of doing it, based on tagging each exception with a
unique value, and then filtering when handling:
data MyException where
MyException :: e -> Data.Unique.Unique -> MyException
instance Show MyException where
show _ = "<MyException>"
instance Exception MyException
withScopedException ::
((forall a. e -> IO a) -> IO r) -> IO (Either e r)
wiathScopedException f = do
fresh <- Data.Unique.newUnique
flip tryJust (f (\e -> throwIO (MyException e fresh))) $ \case
MyException e tag ->
-- unsafeCoerce is very unpleasant
if tag == fresh then Just (unsafeCoerce e) else Nothing
This is the approach taken by the effectful library[2]. But is there
a better way? Can I persuade GHC's RTS to work like this directly?
Tom
[1] I don't know if these already have a name
[2] https://hackage.haskell.org/package/effectful-core-2.2.1.0/docs/src/Effectful.Error.Static.html#catchError
More information about the Haskell-Cafe
mailing list