Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

How to catch all exceptions instantiating specific class?

Tags:

haskell

ghc

I am trying to achieve an expressiveness in catching exceptions similar to Java/C#, where I can specify an interface of exceptions I want to catch, otherwise I need to enumerate all possible types.

interface I {void f();}
class AE extends Exception implements I {}
class BE extends Exception implements I {}
try {
  throw (new Random().next() % 2 == 0 
          ? new AE() 
          : new BE());   
} catch (I e) {
  e.f();
}
class I e where f :: e -> IO ()
data AE = AE deriving (Show)
data BE = BE deriving (Show)
instance Exception AE
instance Exception BE
instance I AE where f _ = putStrLn "f AE"
instance I BE where f _ = putStrLn "f BE"

run m = try @(forall e . (I e, Exception e) => e) m >>= \case
    Left er -> f er
    Right () -> pure ()

Compiler complains:

  GHC doesn't yet support impredicative polymorphism 

Original error is produced by ghc 8.10.7.

GHC 9.2.1 has been released. With ImpredicitveTypes turned on the error is different:

    • No instance for (Exception (forall e. I e => e))
        arising from a use of ‘try’
like image 323
Daniil Iaitskov Avatar asked Mar 01 '23 09:03

Daniil Iaitskov


2 Answers

I'm undeleting this answer again, but please read Fyodor Solkin's first.


As I already commented, this is probably the wrong approach entirely and you should instead be using a single exception type

data I = AE | BE ...

However, if you insist on having the open-type-class capability, this type can also be an existential (which is what OO references-to-base-class are, basically). Do note that existentials should not be used unless you really have a good reason for doing it that way.

{-# LANGUAGE GADTs, LambdaCase, StandaloneDeriving #-}

import Control.Exception


class I e where f :: e -> IO ()

data AE = AE deriving (Show)
instance I AE where f _ = putStrLn "f AE"
data BE = BE deriving (Show)
instance I BE where f _ = putStrLn "f BE"

data AnI where
  AnI :: (I e, Show e) => e -> AnI
deriving instance Show AnI
instance Exception AnI

run m = try m >>= \case
    Left (AnI er) -> f er
    Right () -> pure ()

main :: IO ()
main = run (throw (AnI BE))

The exception-via library seems to address the awkwardness of explicitly wrapping up these existentials, and to allow creating actual hierarchies of exceptions. I haven't tried the library yet, but it looks promising.


An alternative, which allows you to throw the types “raw” without a wrapper but on the flip side requires a priori listing all the supported exceptions (but literally just listing them), is

{-# LANGUAGE DataKinds, KindSignatures, ScopedTypeVariables, UnicodeSyntax
           , MultiParamTypeClasses, FlexibleInstances, ConstraintKinds
           , AllowAmbiguousTypes
           , TypeApplications, RankNTypes, DeriveAnyClass, TypeOperators #-}

import Control.Exception
import Data.Kind


class PolyExcept (c :: Type -> Constraint) (l :: [Type]) where
  handleAll :: (∀ e . c e => e -> IO a) -> IO a -> IO a

instance PolyExcept c '[] where
  handleAll _ = id

instance ∀ c e l . (Exception e, c e, PolyExcept c l)
            => PolyExcept c (e ': l) where
  handleAll h a = handle @e h (handleAll @c @l h a)

class I e where f :: e -> IO ()

data AE = AE deriving (Show, Exception)
instance I AE where f _ = putStrLn "f AE"
data BE = BE deriving (Show, Exception)
instance I BE where f _ = putStrLn "f BE"

run :: IO () -> IO ()
run = handleAll @I @'[AE, BE] f

main :: IO ()
main = run (throw BE)
like image 151
leftaroundabout Avatar answered Mar 06 '23 17:03

leftaroundabout


The answer by @leftaroundabout (now deleted) was pretty good at explaining the basics, and I think it should be undeleted. But I am adding this answer to explain the "standard" GHC system of exceptions (see also docs).

First you have the Exception class, and all your exceptions should implement that. What you don't know is that when you throw an exception, it actually gets wrapped in SomeException, and it is that SomeException value that is actually thrown.

SomeException is defined as an existential wrapping the Exception class:

data SomeException where
  SomeException :: Exception e => e -> SomeException

And the wrapping happens via the toException method of the Exception class. In the code you posted, you're implementing the Exception instance without defining any methods, so the default implementations are used. And the default implementation of toException is just straight up wrapping:

toException e = SomeException e

Q: Ok, that's cool, but when I catch such exception, won't I just get a value of type SomeException? What's the use of that?

Ah, but that's only half the story! When you catch an exception, a reverse unwrapping happens: the fromException method unwraps the SomeException wrapper and then sees if the value inside matches the type you were trying to catch.

Q: Hold right there! "Sees if value matches the type"? Didn't you just say there was no runtime type information in Haskell?

Well, there is. Kinda. Only when you need it.

It's called Typeable. It's a magic class that you don't have to implement or derive, but GHC will make you an instance of it whenever you require. And it just so happens (well, it's actually on purpose) that the Exception class has Typeable as a superclass, meaning any type implementing Exception has to also implement Typeable. Except you don't have to actually implement Typeable, the compiler does it for you.

The only thing Typeable really allows to do is to get a sort of "type ID" - an opaque value that uniquely identifies a specific type. And then you can use those values to compare, and thus determine if a generic value you're given is of a specific type. This whole comparison + coercion business is wrapped neatly in a function called cast. You give it a value and a target type, and it compares their "type IDs" obtained from Typeable (so both the value and the target type have to implement it), and then returns you the same value, but coerced to the target type. Or not, if it turns out to be of a different type. So it returns a Maybe.

And that's how the SomeException unwrapping basically happens in fromException, which is the second method of Exception:

fromException :: Exception e => SomeException -> Maybe e
fromException (SomeException x) = cast x

Remember: this happens every time you catch an exception. Basically the catch function calls fromException, then calls your handler if the result is Just (meaning the exception is of your type) or doesn't if it's Nothing.

Q: Ok, that's even cooler, but that doesn't solve my problem: do I really need to catch every single specific type of exception? Can't I catch them all at once somehow?

Yes, you can! You can use this whole framework to set up yourself a hierarchy of existentials. Say, we'd like a hierarchy that looks like this:

hierarchy

Just like in good ol' OOP! :-)

In order to do that, MyException would be another existential, just like SomeException itself:

data MyException where
  MyException :: forall e. Exception e => MyException

instance Exception MyException

Then you make sure that, during the "wrapping" process that happens when you throw an exception, both AE and BE get wrapped in MyException before getting wrapped in SomeException:

instance Exception AE where
  toException e = SomeException $ MyException e

-- Same implementation for BE

And similarly, when the "unwrapping" happens on catching, make sure both AE and BE can unwrap themselves by first making sure it's a MyException that is wrapped inside SomeException, and then that it's AE or BE respectively that is wrapped inside MyException:

instance Exception AE where
  fromException x = do
    MyException m <- cast x
    cast m

-- Same implementation for BE

Of course, doing it this way is a bit fragile: both AE and BE have to know not only their own "ancestor" type MyException, but also its ancestor type SomeException. So in practice both wrapping and unwrapping of MyException is usually delegated to MyException's own Exception instance:

instance Exception AE where
  toException e = toException $ MyException e

  fromException x = do
    MyException m <- fromException x
    cast m

And voila: now you can catch either AE or BE individually or MyException, which would apply to them both. Why? Because if you're catching MyException, as SomeException gets unwrapped, the MyException's implementation of fromException will be used for unwrapping. But if you're catching AE, then it's AE's implementation of fromException that will be used, unwrapping MyException first and then AE itself.

Q: Ok, great, now I get all that, but still: can I query for the exception implementing a certain type class?

Yes and no.

If you just have an arbitrary value lying around, you cannot tell if it implements a certain type class, let's call it I. Because Haskell doesn't have runtime type information, unless you specifically asked for it, and even then, Typeable can only answer "is this value of type X?"

But it's even more than that: "does this value implement class I?" is not even a valid question, because it depends on scope. In modules where the I implementation module is imported, you do have such instance. In modules without such import, the instance doesn't exist. And you could even have two different instances of I for the same type, in different modules, which are imported in different parts of the program. Sure, it's a bad practice, don't do it, but it can happen.

The root of the problem here is that, unlike OOP interfaces, a class instance is not a property of the type itself, but a relationship between a type (or several types) and a class.

But! You still kinda can.

What you can do is require that any exception that "inherits" (see the diagram above) from MyException must have an instance of a certain class:

data MyException where
  MyException :: (Exception e, I e) => e -> MyException

Now anybody who wants to wrap a value inside MyException must provide an instance I e, and that instance will be wrapped inside the MyException value, and you'll get access to it when you unwrap it. For example:

class I a where 
  i :: a -> String

instance I AE where
  i _ = "This is AE"

throw AE `catch` \(MyException e) -> purStrLn (i e)

I can use the method i in the handler, because I just unwrapped MyException and got an I dictionary out of it.

But the important point is: the dictionary didn't come out of thin air. It was put inside the MyException value by whoever threw the exception in the first place.


A tangent: you can actually hijack (sort of) the exception wrapping/unwrapping mechanism to allow catching types that haven't been thrown. All you do is make a "dishonest" implementation of fromException:

data Hijacked = Hijacked deriving Show

instance Exception Hijacked where
  fromException x = do
    AE <- fromException x  -- See if it's an AE
    pure Hijacked

throw AE `catch` \Hijacked -> putStrLn "I caught a Hijacked!"    
like image 39
Fyodor Soikin Avatar answered Mar 06 '23 15:03

Fyodor Soikin