Proposal: Extensible exceptions

Hi all, This is a proposal to replace the current exception mechanism in the base library with extensible exceptions. It also reimplements the existing exceptions on top of extensible exceptions, for legacy applications. Proposed deadline: 25th July. http://hackage.haskell.org/trac/ghc/ticket/2419 === What are extensible exceptions? Simon's extensible extensions paper is very easy to read, and describes the problems and proposed solution very well: http://www.haskell.org/~simonmar/papers/ext-exceptions.pdf I won't try to reproduce everything the paper says here, but here is the list of what we want extracted from it: * A hierarchy of exception types, such that a particular catch can choose to catch only exceptions that belong to a particular subclass and re-throw all others. * A way to add new exception types at any point in the hierarchy from library or program code. * The boilerplate code required to add a new type to the exception hierarchy should be minimal. * Exceptions should be thrown and caught using the same primitives, regardless of the types involved. I heartily recommend having a read through of the paper. === Patches and examples The patches are here: http://darcs.haskell.org/ext-excep/ I've attached Examples.hs, which gives some examples of using it. The patches aren't polished; if this proposal is accepted then there is some more work to do, moving things around inside the base package to simplify the dependencies, and to maximise the amount of code that can be shared between all the impls. There's also some GHC-specific fiddling to be done, to make GHC.TopHandler use the new exceptions. This can all be done without further library proposals, though. Also, currently it derives Data.Typeable, which is unportable, but we can easily work around that. The only extensions that I don't think that we can do without are ExistentialQuantification and Rank2Types. DeriveDataTypeable makes the implementation easier, and DeriveDataTypeable and PatternSignatures make using it easier. === Library function differences As far as the library functions are concerned, here are the main differences: The old and new types for catch are: Old: catch :: IO a -> (Exception -> IO a) -> IO a New: catch :: Exception e => IO a -> (e -> IO a) -> IO a i.e. catch can now catch any type of exception; we don't have to force all the different types of extension into one fixed datatype. All the other exception functions are similarly changed to handle any type of extension, e.g. we now have try :: Exception e => IO a -> IO (Either e a) Now that you can write handlers for different exception types, you might want to catch multiple different types at the same point. You can use catches for this. For example, the OldException module needs to catch all the new exception types and put them into the old Exception type, so that the legacy handler can be run on them. It looks like this: catch :: IO a -> (Exception -> IO a) -> IO a catch io handler = io `catches` [Handler (\e -> handler e), Handler (\exc -> handler (ArithException exc)), Handler (\exc -> handler (ArrayException exc)), ...] where the first Handler deals with exceptions of type Exception, the second those of type ArithException, and so on. If you want to catch all exceptions, e.g. if you want to cleanup and rethrow the exception, or just print the exception at the top-level, you can use the new function catchAny: catchAny :: IO a -> (forall e . Exception e => e -> IO a) -> IO a You can happily write `catchAny` \e -> print e where `catch` \e -> print e would give you an ambiguous type variable error. There's also ignoreExceptions :: IO () -> IO () which can be used instead of try for things like ignoreExceptions (hClose h) (where we don't look at the result, so the exception type would be ambiguous if we used try). (I'm not sure if this is the best name for this function). All the build failures I've seen with the new exceptions library have been cases where you need to change a "catch" to "catchAny", "try" to "ignoreExceptions", or occassionally a different function, e.g. "bracket" or "handle", is used to handle any extension, so adding a type signature involving the SomeException type solves the problem. The old interface is available in Control.OldException. Currently it doesn't catch exceptions that don't fit into the old Exception type; we could catch them, show them and treat them as user errors, but then the exception has changed if it gets rethrown. Thanks Ian

Ian Lynagh wrote:
This is a proposal to replace the current exception mechanism in the base library with extensible exceptions.
I'm generally in favour of this (of course) ...
There's also ignoreExceptions :: IO () -> IO () which can be used instead of try for things like ignoreExceptions (hClose h) (where we don't look at the result, so the exception type would be ambiguous if we used try). (I'm not sure if this is the best name for this function).
But I think we should omit ignoreExceptions completely, or at least strongly discourage its use. (I mentioned this to Ian privately, he asked me to bring it up on the list). The problem with discarding *any* exception is that it breaks modularity: for example, things like System.Timeout rely on being able to interrupt any computation by using a private exception. Ignoring exceptions should always be limited to a particular class of exceptions that you want to ignore. Existing uses of ignoreExceptions should be scrutinised very carefully. In fact, this applies to catchAny too. It should come with a strong warning, and a suggestion that any unrecognised exceptions should be re-thrown. Most uses of catchAny are to implement an on-error action anyway, I think this ought to be provided as a combinator. We have bracketOnError, but perhaps we should also have onException :: IO a -> IO b -> IO a Cheers, Simon

On Fri, Jul 04, 2008 at 02:56:06PM +0100, Simon Marlow wrote:
Ian Lynagh wrote:
There's also ignoreExceptions :: IO () -> IO () which can be used instead of try for things like ignoreExceptions (hClose h) (where we don't look at the result, so the exception type would be ambiguous if we used try). (I'm not sure if this is the best name for this function).
But I think we should omit ignoreExceptions completely, or at least strongly discourage its use. (I mentioned this to Ian privately, he asked me to bring it up on the list).
The problem with discarding *any* exception is that it breaks modularity: for example, things like System.Timeout rely on being able to interrupt any computation by using a private exception. Ignoring exceptions should always be limited to a particular class of exceptions that you want to ignore. Existing uses of ignoreExceptions should be scrutinised very carefully.
Hmm, I agree, but if people are doing it already (using try) then they'll presumably keep doing so. And this isn't random newbies, this is GHC's bootlibs! Is it better to have a handy function for it, that comes with documentation telling you not to use it and what to do instead, or to not provide it and risk people using try with a type sig? I don't have strong feelings either way.
In fact, this applies to catchAny too. It should come with a strong warning, and a suggestion that any unrecognised exceptions should be re-thrown. Most uses of catchAny are to implement an on-error action anyway, I think this ought to be provided as a combinator. We have bracketOnError, but perhaps we should also have
onException :: IO a -> IO b -> IO a
Sounds good to me. Thanks Ian

Ian Lynagh wrote:
In fact, this applies to catchAny too. It should come with a strong warning, and a suggestion that any unrecognised exceptions should be re-thrown. Most uses of catchAny are to implement an on-error action anyway, I think this ought to be provided as a combinator. We have bracketOnError, but perhaps we should also have
onException :: IO a -> IO b -> IO a
Sounds good to me.
similar to `finally` but only for when there are exceptions. finally :: IO a -> IO b -> IO a bracket is to bracketOnError as finally is to... onException? perhaps we can call it finallyOnError so we can understand the parallelism more naturally? :-) (and why is there no "bracket_OnError" :-) But I'd think that sometimes we want to have the exception (e.g. to print it) even if we're `onException`, so we get a slightly more similar signature to catchAny, but safer because it rethrows the exception after the second clause completes: onAny :: IO a -> (forall e . Exception e => e -> IO b) -> IO a Then we encourage this as another alternative to catchAny depending on user's needs. What should we call it -- onAny is bad? Really, `finally` corresponds to `bracket_` -- I'm not too happy with the Control.Exception naming situation right now, maybe I'll try to rethink all the names at once and post a proposal (even if we decide we don't want the API breakage, it'll be useful to make sure we're not leaving out anything else important). By the way, what happens if a `finally` or `onException` clause throws an exception? That exception replaces the the one that we were planning on rethrowing? Does this already induce a risk of accidentally deleting Timeout exceptions (e.g. we replace it with a DiskFull exception accidentally produced by logging a message, that some higher level code catches and then proceeds as normal)? Or do we ignore exceptions in those blocks? (Similar to how exceptions in C++ destructors are just a Bad Idea.) But that risks ignoring a HeapOverflow or asynchronous exception (killThread, timeout...)? no it doesn't, those are just blocked from arriving until the end of the handling-block, and it's just the *synchronous* exceptions that are swallowed? But if the handler does some blocking I/O and thus (unblock), does that mean we risk losing those exceptions again? This confuses me a lot. Are we any better off than imperative languages, e.g. because most of our code isn't in I/O and so it uses proper data structures (Maybe, Either, etc.), rather than exceptions, for legitimate computational possibilities? -Isaac

On 2008 Jul 4, at 9:56, Simon Marlow wrote:
In fact, this applies to catchAny too. It should come with a strong warning, and a suggestion that any unrecognised exceptions should be re-thrown. Most uses of catchAny are to implement
Given that it just tries a catch with each exception in the list, why couldn't it automatically re-throw if none matches? -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Fri, Jul 04, 2008 at 03:22:23PM -0400, Brandon S. Allbery KF8NH wrote:
On 2008 Jul 4, at 9:56, Simon Marlow wrote:
In fact, this applies to catchAny too. It should come with a strong warning, and a suggestion that any unrecognised exceptions should be re-thrown. Most uses of catchAny are to implement
Given that it just tries a catch with each exception in the list, why couldn't it automatically re-throw if none matches?
I think you're confusing "catchAny" (which catches /any/ sort of exception) with "catches" (which has a list of handlers for different types, and does indeed rethrow exceptions that none of the handlers catch). Thanks Ian

Ian Lynagh wrote:
=== Library function differences
As far as the library functions are concerned, here are the main differences:
The old and new types for catch are: Old: catch :: IO a -> (Exception -> IO a) -> IO a New: catch :: Exception e => IO a -> (e -> IO a) -> IO a i.e. catch can now catch any type of exception; we don't have to force all the different types of extension into one fixed datatype.
Is there any sane way to allow extending or building equivalents to these for MonadIO? -- Chris

On Fri, Jul 4, 2008 at 10:52 AM, Chris Kuklewicz
Ian Lynagh wrote:
The old and new types for catch are: Old: catch :: IO a -> (Exception -> IO a) -> IO a New: catch :: Exception e => IO a -> (e -> IO a) -> IO a i.e. catch can now catch any type of exception; we don't have to force all the different types of extension into one fixed datatype.
Is there any sane way to allow extending or building equivalents to these for MonadIO?
MonadIO currently isn't enough to implement catch. There's been discussion of this in the past, though; for an example solution, see the following module from the haskell-prime wiki: http://hackage.haskell.org/trac/haskell-prime/attachment/ticket/110/Exceptio... I had been thinking of proposing that a Control.Monad.Exception module be added to the mtl package, but any discussion on this subject should probably wait until the extensible exceptions API is nailed down. -Judah

On Fri, Jul 04, 2008 at 03:52:32PM +0100, Chris Kuklewicz wrote:
Ian Lynagh wrote:
=== Library function differences
As far as the library functions are concerned, here are the main differences:
The old and new types for catch are: Old: catch :: IO a -> (Exception -> IO a) -> IO a New: catch :: Exception e => IO a -> (e -> IO a) -> IO a i.e. catch can now catch any type of exception; we don't have to force all the different types of extension into one fixed datatype.
Is there any sane way to allow extending or building equivalents to these for MonadIO?
I don't think that this change makes it any easier or harder. Thanks Ian

Ian Lynagh wrote:
This is a proposal to replace the current exception mechanism in the base library with extensible exceptions...
How does this affect integration between IO exceptions and pure exceptions, in particular Control.Monad.Error from mtl? That is already a bit tricky, but doable. Does this make it worse? At the very least, we should take this opportunity to create Error instances for the standard exceptions, and make sure that the extension mechanism includes an easy way to add compatible Error instances for new exceptions. Besides the mechanism itself, the obvious question is how to do this without making a mess out of the package dependency hierarchy. Thanks, Yitz

On Fri, Jul 04, 2008 at 05:54:11PM +0300, Yitzchak Gale wrote:
Ian Lynagh wrote:
This is a proposal to replace the current exception mechanism in the base library with extensible exceptions...
How does this affect integration between IO exceptions and pure exceptions, in particular Control.Monad.Error from mtl?
I don't think anything needs to change, but it might be desirable to use a similar sort of extensible-errors. It might even be possible to get rid of the Error class and use the Exception class instead. Thanks Ian

I am now opposed to this proposal as it stands, due to code breakage. However, the proposal is nice, and I think that we could get there via a more friendly path. Discussion and suggestions follow. I wrote:
How does this affect integration between IO exceptions and pure exceptions, in particular Control.Monad.Error from mtl?
Ian Lynagh wrote:
I don't think anything needs to change, but it might be desirable to use a similar sort of extensible-errors.
No, the Error class is already extensible. But Exception members are not suitable, since they do not have strMsg and noMsg methods. With the old Exceptions, that was not too bad - you just need to wrap the single Exception data type. This proposed change makes things much messier, and it will break code.
It might even be possible to get rid of the Error class and use the Exception class instead.
I like that idea. In practice, I always find strMsg and noMsg nothing more than an annoyance. What is really needed is a required Show instance, like the Exception class has. And of course, having all Exception instances available as candidates for pure exceptions is nice. But this would be a traumatic change. There would need to be some migration/deprecation path. As Bulat points out, there will be a lot of pain caused even for Exception itself. The fact that it is easy to figure out how to fix code to make it work again (assuming that is true) will not change the fact that many, many programs will no longer compile. Past experience shows that this causes a lot of damage. To get there with less pain, I think we should: o For 6.10, make the new Exceptions available so that everyone can start working on switching, but leave old Exceptions as the default so that existing programs still work. Prominently mark old exceptions as deprecated in all documentation. o In the next version, make the new Exceptions the default. Make sure that programs using new Exceptions for 6.10 will still work (e.g., leave NewException as an alias for Exception, or whatever). In parallel, do something similar for deprecating the mtl Error class and using Exception instead. As a general note - it has been suggested several times that we need a facility like Python's "from future import ...". That would be much better than making up names like "OldException" and "NewException" every time. Though in Python itself, that facility only applies to the core language, not to libraries. When an important library is changed in an incompatible way, they tend to use a new name for the new library and leave the deprecated library around with its old name for years and years. We could also do that here. Another approach would be to build this kind of facility into the package system. Thanks, Yitz

On Sat, Jul 5, 2008 at 7:39 PM, Yitzchak Gale
I wrote:
How does this affect integration between IO exceptions and pure exceptions, in particular Control.Monad.Error from mtl?
Ian Lynagh wrote: [...]
It might even be possible to get rid of the Error class and use the Exception class instead.
I like that idea. In practice, I always find strMsg and noMsg nothing more than an annoyance. What is really needed is a required Show instance, like the Exception class has. And of course, having all Exception instances available as candidates for pure exceptions is nice.
The Error class is cruft anyway. It only exists so that the Error and ErrorT monads can support "fail" and "mzero". From my standpoint, "fail" shouldn't exist, and the error monads shouldn't conflate mzero and throwErr. But that's another topic.
But this would be a traumatic change. There would need to be some migration/deprecation path.
As Bulat points out, there will be a lot of pain caused even for Exception itself. The fact that it is easy to figure out how to fix code to make it work again (assuming that is true) will not change the fact that many, many programs will no longer compile. Past experience shows that this causes a lot of damage.
To get there with less pain, I think we should:
o For 6.10, make the new Exceptions available so that everyone can start working on switching, but leave old Exceptions as the default so that existing programs still work. Prominently mark old exceptions as deprecated in all documentation.
o In the next version, make the new Exceptions the default. Make sure that programs using new Exceptions for 6.10 will still work (e.g., leave NewException as an alias for Exception, or whatever).
I have the guts of an extensible exception library modeled on Simon Marlow's paper that can coexist with the current Control.Exception regime. That is, exceptions thrown by "old" code can be caught by "new" code, and vice versa. The trick is adding two secret methods to the Exception class which handle conversion to and from Control.Exception.Exception.
import qualified Control.Exception as Legacy
class (Show e, Typeable e) => Exception e where toException :: e -> SomeException fromException :: SomeException -> Maybe e toLegacyException :: e -> Legacy.Exception fromLegacyException :: Legacy.Exception -> Maybe e
toException = SomeException fromException (SomeException e) = cast e
toLegacyException = Legacy.DynException . toDyn . toException fromLegacyException (Legacy.DynException d) = fromDynamic d >>= fromException fromLegacyException _ = Nothing
Adding new exceptions works exactly as it does in Simon's paper. The wrappers for already existing exceptions silently translate into their current representations.
data DivideByZero = DivideByZero deriving (Show, Typeable)
instance Exception DivideByZero where toException = SomeException . toLegacyException toLegacyException DivideByZero = Legacy.ArithException Legacy.DivideByZero
fromException (SomeException e) = cast e >>= fromLegacyException
fromLegacyException (Legacy.ArithException Legacy.DivideByZero) = Just DivideByZero fromLegacyException _ = Nothing
This code implements the new exceptions on top of the old exceptions.
Eventually, once the new exceptions have gained acceptance, the
internals of the library can be changed to implement the old
exceptions on top of the new exceptions.
I only ever made a partial implementation, but I can post it if anyone
is interested.
--
Dave Menendez

Ian Lynagh wrote:
It might even be possible to get rid of the Error class and use the Exception class instead.
David Menendez wrote:
The Error class is cruft anyway. It only exists so that the Error and ErrorT monads can support "fail" and "mzero"... the error monads shouldn't conflate mzero and throwErr.
Agreed. So let's get rid of Error. But please - make it a two step process that gives people time to adapt, not a sudden discontinuity that breaks everything all at once.
I have the guts of an extensible exception library modeled on Simon Marlow's paper that can coexist with the current Control.Exception regime. That is, exceptions thrown by "old" code can be caught by "new" code, and vice versa.
Nice. It looks like this addition would allow code that only mentions old exception constructors to keep working, but it would still break code that mentions old exception types. Is this correct? If so, then it would definitely be helpful, but we would still need a two-step deprecation path. Thanks, Yitz

On Sun, Jul 6, 2008 at 6:07 AM, Yitzchak Gale
David Menendez wrote:
I have the guts of an extensible exception library modeled on Simon Marlow's paper that can coexist with the current Control.Exception regime. That is, exceptions thrown by "old" code can be caught by "new" code, and vice versa.
Nice. It looks like this addition would allow code that only mentions old exception constructors to keep working, but it would still break code that mentions old exception types. Is this correct?
My implementation doesn't touch Control.Exception at all, so existing
code would still work unmodified. The new throw and catch are in a
different module, and everything else is exactly the way it was
before. The clever part is that the new code can throw a new version
of a pre-existing exception, e.g. DivByZero, and existing code which
is looking for (ArithException DivByZero) will still catch it, and
vice versa, without changing or even recompiling the old code.
I implemented the new exceptions on top of the current ones because I
didn't want to mess around with GHC's internals. It's possible to
implement extensible exceptions in GHC while still fully supporting
the existing Control.Exception interface. The idea is to re-implement
Old.throw and Old.catch in terms of New.throw and New.catch. (In
contrast, my code implements New.throw and New.catch in terms of
Old.throw and Old.catch.)
The hard part is coming up with a new module name, since
Control.Exception is taken.
--
Dave Menendez

On Sun, 6 Jul 2008, David Menendez wrote:
data DivideByZero = DivideByZero deriving (Show, Typeable)
Maybe I annoy you with my distinction of errors and exceptions, but I consider DivideByZero a bad example for an exception, because it is more an error (I see it is used in the extensible exception paper anyway). A division by zero is not a problem that comes from the outside world like 'file does not exist'. In contrast to that, it's absolutely predictable: It occurs whenever you divide by zero. I'd thus call it a programming error.

On Sun, Jul 6, 2008 at 4:31 PM, Henning Thielemann
On Sun, 6 Jul 2008, David Menendez wrote:
data DivideByZero = DivideByZero deriving (Show, Typeable)
Maybe I annoy you with my distinction of errors and exceptions, but I consider DivideByZero a bad example for an exception, because it is more an error (I see it is used in the extensible exception paper anyway).
It's also in the current Control.Exception library.
While dividing by zero or accessing an array out of bounds isn't the
same as a file not existing, I'm not sure we need different mechanisms
for dealing with them. If your code divides by zero, you still want
any "finally" or "bracket" clauses to get called before the program
terminates.
--
Dave Menendez

On Sun, 6 Jul 2008, David Menendez wrote:
On Sun, Jul 6, 2008 at 4:31 PM, Henning Thielemann
wrote: On Sun, 6 Jul 2008, David Menendez wrote:
data DivideByZero = DivideByZero deriving (Show, Typeable)
Maybe I annoy you with my distinction of errors and exceptions, but I consider DivideByZero a bad example for an exception, because it is more an error (I see it is used in the extensible exception paper anyway).
It's also in the current Control.Exception library.
There are many things wrong about Errors and Exceptions in the current Haskell library: http://www.haskell.org/haskellwiki/Exception http://www.haskell.org/haskellwiki/Error
While dividing by zero or accessing an array out of bounds isn't the same as a file not existing, I'm not sure we need different mechanisms for dealing with them.
Yes! Because there is no need to recover from an error. Instead an error must be fixed by the programmer. The program cannot do this by itself. I consider recovering from an error like in a web-server a hack, like catching and recovering from an 'error' in IO is a hack, just like unsafePerformIO. I accept that we need a hack in order to tell the user "please send a bug-report to XYZ", but a hack should be called a hack, not "proper exception handling".
If your code divides by zero, you still want any "finally" or "bracket" clauses to get called before the program terminates.
A program which divides by zero is broken and must be fixed. A program which divides by zero but cleans up a bit, is still broken and must be fixed. Cleaning up may make things better, but may also make things worse! Handling errors is the task of Debugging, not that of Exception Handling. I suggest special variants of 'finally' and 'bracket' for bracketing bugs should be located below "Debug" in the module hierarchy.

Henning Thielemann wrote:
If your code divides by zero, you still want any "finally" or "bracket" clauses to get called before the program terminates.
A program which divides by zero is broken and must be fixed. A program which divides by zero but cleans up a bit, is still broken and must be fixed. Cleaning up may make things better, but may also make things worse!
it can make things worse? (When cleanup is somehow significantly dependent on the buggy part of the code that led to the error? How often does that happen??) I appreciate how bugs in Haskell are much better-behaved than many languages. For finally-clauses, they should be called equally whether there is a legitimate IO exception (if you believe in such a thing; they're even in Haskell98 in a form), or a buggy-program exception, and there is no good reason to fail to call 'hClose' just because some pure code in some part of the program divided by zero. Especially because of Haskell's laziness, that division by zero might have been lexically called somewhere before opening the handle, but be evaluated after it's been opened and before it's been closed! This way, if my IO uses 'bracket' when it should, a bug in one part of the code is less likely to cause obscure bugs in entirely unrelated IO parts of the code. Exceptions are designed to be ubiquitous and always-possible... especially when you consider asynchronous exceptions. In fact it's possible to use these exception capabilities to isolate different parts of the program from each other's bugs so the whole thing doesn't crash: although that's when it becomes much closer to your assessment of "a hack". That "hack" still can be quite useful, of course, if you agree with the Awkward Squad paper. It depends whether modularity of bugs is part of your worldview?-- I'm glad Linux (and all other modern OS) isolates different processes' address spaces using MMU! -Isaac

On Sun, 6 Jul 2008, Isaac Dupree wrote:
Henning Thielemann wrote:
If your code divides by zero, you still want any "finally" or "bracket" clauses to get called before the program terminates.
A program which divides by zero is broken and must be fixed. A program which divides by zero but cleans up a bit, is still broken and must be fixed. Cleaning up may make things better, but may also make things worse!
it can make things worse? (When cleanup is somehow significantly dependent on the buggy part of the code that led to the error? How often does that happen??)
An error is a programming error, often a stupid mistake where you wonder, how this could happen. How do you predict how evil your mistakes are and whether the assumptions you put into the cleanup routines are fulfilled?
I appreciate how bugs in Haskell are much better-behaved than many languages. For finally-clauses, they should be called equally whether there is a legitimate IO exception (if you believe in such a thing; they're even in Haskell98 in a form), or a buggy-program exception, and there is no good reason to fail to call 'hClose' just because some pure code in some part of the program divided by zero.
As I answered to David, the file might well be deleted in the meantime. Your code is buggy and then it may well be that the file is already deleted. Maybe due to other "error handling code" that tried to recover from the division by zero.
This way, if my IO uses 'bracket' when it should, a bug in one part of the code is less likely to cause obscure bugs in entirely unrelated IO parts of the code. Exceptions are designed to be ubiquitous and always-possible...
That's especially unsatisfying. If you have to expect any exceptional situation at every time, you can no longer concentrate on what you intend to program. Instead, if I open a file I expect exceptions that are specific to that operation, and I handle them. I do not expecct OpenGL exceptions and not division by zero errors. With the design I proposed you can easily see in the type signature what exceptions can occur in an action (and btw. there is even no need to restrict this to IO, you can use this for any monad, e.g. monad transforms of IO).
especially when you consider asynchronous exceptions.
Do you mean the problem of 'readFile' raising an exception? I think we already clarified on Haskell-Cafe how to solve that properly: http://www.haskell.org/pipermail/haskell-cafe/2008-April/042050.html Instead of a signature like readFile :: IO (Either ErrorMsg String) the function should have a type like readFile :: IO (String, Maybe ErrorMsg) where the ErrorMsg is generated lazily when reading the file stops. If the file could be read completely it is Nothing, otherwise it is (Just errorMsg). The consumer of the file content can throw a regular exception after consuming the content. There is no need for complicating the exception handling mechanism.
In fact it's possible to use these exception capabilities to isolate different parts of the program from each other's bugs so the whole thing doesn't crash: although that's when it becomes much closer to your assessment of "a hack". That "hack" still can be quite useful, of course, if you agree with the Awkward Squad paper. It depends whether modularity of bugs is part of your worldview? -- I'm glad Linux (and all other modern OS) isolates different processes' address spaces using MMU!
I'm glad about all tools to help debugging - but please keep debugging and exception handling strictly separated! Let me give another example. We have learned that 'head' and 'tail' are evil, because they are undefined for some inputs. Using them we run into the risk of forgetting some cases. It is better to use a function like 'viewL' http://www.haskell.org/pipermail/haskell-cafe/2008-June/044179.html or to use 'case': case xs of [] -> a (_:ys) -> f ys Now, if we take the perspective that exceptions and errors are interchangeable, then we could also call 'tail' and catch the error in case the input list is empty. Do you consider this a good application of exception handling?

On Sun, Jul 6, 2008 at 6:05 PM, Henning Thielemann
While dividing by zero or accessing an array out of bounds isn't the same as a file not existing, I'm not sure we need different mechanisms for dealing with them.
Yes! Because there is no need to recover from an error. Instead an error must be fixed by the programmer. The program cannot do this by itself. I consider recovering from an error like in a web-server a hack, like catching and recovering from an 'error' in IO is a hack, just like unsafePerformIO. I accept that we need a hack in order to tell the user "please send a bug-report to XYZ", but a hack should be called a hack, not "proper exception handling".
I don't recall calling anything "proper exception handling". I said that it's reasonable to report certain programming errors through the exception handling mechanism because it allows a running program to clean up before it terminates.
If your code divides by zero, you still want any "finally" or "bracket" clauses to get called before the program terminates.
A program which divides by zero is broken and must be fixed. A program which divides by zero but cleans up a bit, is still broken and must be fixed. Cleaning up may make things better, but may also make things worse! Handling errors is the task of Debugging, not that of Exception Handling. I suggest special variants of 'finally' and 'bracket' for bracketing bugs should be located below "Debug" in the module hierarchy.
Yes, a program that divides by zero should be fixed. If a program has,
say, locked a file and then encounters an error, are you suggesting
that the program should crash without unlocking the file? The fact
that the program shouldn't have encountered an error is irrelevant.
--
Dave Menendez

On Sun, 6 Jul 2008, David Menendez wrote:
I don't recall calling anything "proper exception handling". I said that it's reasonable to report certain programming errors through the exception handling mechanism because it allows a running program to clean up before it terminates.
You can try to report programming errors to the user - but that's debugging. Where is the need to mix that with regular exception handling?
If your code divides by zero, you still want any "finally" or "bracket" clauses to get called before the program terminates.
A program which divides by zero is broken and must be fixed. A program which divides by zero but cleans up a bit, is still broken and must be fixed. Cleaning up may make things better, but may also make things worse! Handling errors is the task of Debugging, not that of Exception Handling. I suggest special variants of 'finally' and 'bracket' for bracketing bugs should be located below "Debug" in the module hierarchy.
Yes, a program that divides by zero should be fixed. If a program has, say, locked a file and then encounters an error, are you suggesting that the program should crash without unlocking the file?
If your program is buggy, then it may well be that the file to unlock is already unlocked and deleted. By trying to recover from an error a division by zero can cause even more severe damages. It is not possible to handle errors in a way like exceptions, because exceptions are (rare but) expected situations, that can well be handled. In contrast to that you do not know the concrete errors in your program, otherwise you would have fixed them already.

Henning Thielemann wrote:
It is not possible to handle errors in a way like exceptions, because exceptions are (rare but) expected situations, that can well be handled. In contrast to that you do not know the concrete errors in your program, otherwise you would have fixed them already.
I agree with you that it makes sense to reflect this conceptual distinction in our module system, and in our hierarchy of exceptions and errors. However, this distinction is only really useful during development. Once a system is deployed, there is little difference. In the face of an error, it is often just not an option to print a rude error message and shut down the system. Picture, for example, a program that is controlling an aircraft in flight, or that is participating in sensitive negotiations for a valuable business deal. Instead, the system must do the best it can to keep a smile on its face and keep going. Any condition that could interfere with normal operation is the same, it doesn't matter whether the reason is a programming error or anything else. So we also need a way to treat all exceptional conditions the same in a deployed system, whether or not they are "errors". Historically, a famous example is the cryptic error condition that kept popping up every few seconds as the Apollo 11 lander was about to touch down on the moon. All eyes in Mission Control were on the person who wrote the program. Sweat pouring down his back, he just kept saying quietly, "Go."

On Mon, Jul 7, 2008 at 5:47 AM, Henning Thielemann
On Sun, 6 Jul 2008, David Menendez wrote:
I don't recall calling anything "proper exception handling". I said that it's reasonable to report certain programming errors through the exception handling mechanism because it allows a running program to clean up before it terminates.
You can try to report programming errors to the user - but that's debugging. Where is the need to mix that with regular exception handling?
I wasn't talking about reporting errors to the user. I meant reporting errors to the rest of the program.
Yes, a program that divides by zero should be fixed. If a program has, say, locked a file and then encounters an error, are you suggesting that the program should crash without unlocking the file?
If your program is buggy, then it may well be that the file to unlock is already unlocked and deleted. By trying to recover from an error a division by zero can cause even more severe damages. It is not possible to handle errors in a way like exceptions, because exceptions are (rare but) expected situations, that can well be handled. In contrast to that you do not know the concrete errors in your program, otherwise you would have fixed them already.
I think we're conflating two uses of "recover" here. If a program
divides by zero, it can't sensibly continue, but it may need to clean
up some things before it terminates. And yes, if the cleanup code is
itself buggy it can make things worse, but that's a separate issue.
--
Dave Menendez

Henning Thielemann wrote:
If your program is buggy, then it may well be that the file to unlock is already unlocked and deleted.
I think you're being a tad too simplistic here. In large software systems, you get different perspectives on the code. From your module, that division by zero error may be fatal; but from my module, which may have been developed independently and is responsible for managing a number of other third party code modules, I would like to find out that your code had an error, note it in some kind of log, and then run the next person's code. That is, from my code, your programming errors were entirely anticipated "external" things that could go wrong. This sort of thing doesn't happen in all large software systems, but it's not exactly rare. Even when it's not a requirement, it's often a good idea just in the name of robust programming. A sufficiently large system is bound to have some bugs; and it's nice to be able to isolate their effects enough to continue with the functionality that works. Depends on the situation. So, given that the distinction between "error" and "exception" is not absolutely, but often just depends on your perspective (and I do take that as a given), I'd call it very broken to have different mechanisms for each. -- Chris Smith

On Wed, 9 Jul 2008, Chris Smith wrote:
Henning Thielemann wrote:
If your program is buggy, then it may well be that the file to unlock is already unlocked and deleted.
I think you're being a tad too simplistic here. In large software systems, you get different perspectives on the code. From your module, that division by zero error may be fatal; but from my module, which may have been developed independently and is responsible for managing a number of other third party code modules, I would like to find out that your code had an error, note it in some kind of log, and then run the next person's code. That is, from my code, your programming errors were entirely anticipated "external" things that could go wrong.
Of course, what is an error for one part of the software, can be an exception for the next higher level. If a program crashes this is only an exception for the OS. But how does this justify the use of one handling system for both kinds of break mechanisms in one part of the software architecture?
So, given that the distinction between "error" and "exception" is not absolutely, but often just depends on your perspective (and I do take that as a given), I'd call it very broken to have different mechanisms for each.
The program part that contains the error cannot do much in case it stepped into a bug. I enumerated some possibilities in previous mails. They are clearly distinct from the things to do when an exception occurs.

Henning Thielemann wrote:
On Sun, 6 Jul 2008, David Menendez wrote:
data DivideByZero = DivideByZero deriving (Show, Typeable)
Maybe I annoy you with my distinction of errors and exceptions, but I consider DivideByZero a bad example for an exception, because it is more an error (I see it is used in the extensible exception paper anyway). A division by zero is not a problem that comes from the outside world like 'file does not exist'. In contrast to that, it's absolutely predictable: It occurs whenever you divide by zero. I'd thus call it a programming error.
Indeed, we should give some thought to which exceptions are programming errors (divide by zero, assert-failure, error, but not Neil Mitchell's abort...) and put them in a category. We should give some thought to the hierarchy of exceptions we're establishing! I have some trouble seeing from the patches what the hierarchy of exceptions will be; Ian (or someone), could you describe what the current proposal is for that hierarchy? (if it exists yet) -Isaac

On Sun, Jul 06, 2008 at 05:32:02PM -0400, Isaac Dupree wrote:
I have some trouble seeing from the patches what the hierarchy of exceptions will be;
Right, it's a bit obfuscated at the moment, as some of the types are where we want them to be (portable modules like Control.Exception) while others are where they need to be (GHC.*, to avoid import loops). Hopefully we can improve that later. Anyway, these patches basically only add the machinery for extensible exceptions, but don't define much in the way of a hierarchy themselves. All I've done is to break up the old Extension type: http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Exception... e.g. for constructors like ArithException ArithException the ArithException type is an instance of Exception, for constructors like BlockedOnDeadMVar I've made a new type data BlockedOnDeadMVar = BlockedOnDeadMVar that is an instance of Exception, and for constructors like RecConError String I've made a new type data RecConError = RecConError String that is an instance of Exception,
could you describe what the current proposal is for that hierarchy? (if it exists yet)
So it doesn't really exist yet. That can be done later, either all at once or bit by bit. Thanks Ian

Ian Lynagh wrote:
On Sun, Jul 06, 2008 at 05:32:02PM -0400, Isaac Dupree wrote:
I have some trouble seeing from the patches what the hierarchy of exceptions will be;
Right, it's a bit obfuscated at the moment, as some of the types are where we want them to be (portable modules like Control.Exception) while others are where they need to be (GHC.*, to avoid import loops). Hopefully we can improve that later.
Anyway, these patches basically only add the machinery for extensible exceptions, but don't define much in the way of a hierarchy themselves. All I've done is to break up the old Extension type: http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Exception...
e.g. for constructors like ArithException ArithException the ArithException type is an instance of Exception,
for constructors like BlockedOnDeadMVar I've made a new type data BlockedOnDeadMVar = BlockedOnDeadMVar that is an instance of Exception,
and for constructors like RecConError String I've made a new type data RecConError = RecConError String that is an instance of Exception,
could you describe what the current proposal is for that hierarchy? (if it exists yet)
So it doesn't really exist yet. That can be done later, either all at once or bit by bit.
Okay, let's see: As long as it's a single-level hierarchy as described above, we can't break anything by adding additional levels in the hierarchy; the only difference is that user-added types won't yet be in a new hierarchy where they belong, so we should probably think about this (for 6.10, but it needn't hold up implementing the exceptions). On the other hand, the proposal can't do multiple inheritance, and that would probably require baking certain parts of the hierarchy deep in base-library (whoever has to throw a DivZeroError, for example, for Num Int, has to have access to that whole part of the hierarchy already.) -Isaac

On Sun, 6 Jul 2008, Yitzchak Gale wrote:
I am now opposed to this proposal as it stands, due to code breakage.
If the proposal breaks code, then it should be implemented in new modules. The opportunity could also be used to correct design flaws, that are in the current IO modules. E.g. there should be strict and lazy readFile: readFileStrict :: ErrorT IO IOError [Word8] readFileLazy :: IO ([Word8], Maybe IOError) Then there should be new modules that strictly separate between error handling (they should be located under Debug) and exception handling (they should be under Control.Monad). Exception handling should be done with an ErrorT monad transformer (only renamed) which uses a type isomorphic to Either but distinct from it. This way exception handling can be used for all monads, not only IO. The great thing is, that this is even everything Haskell 98! This should be implemented on top of existing IO, but the new function should assert not to use the exception facility of IO, but only use ErrorT exceptions. It should be in a separate package which can be installed from Hackage, so people can play with it and improve it.
It might even be possible to get rid of the Error class and use the Exception class instead.
I like that idea. In practice, I always find strMsg and noMsg nothing more than an annoyance. What is really needed is a required Show instance, like the Exception class has.
What is it intended for? Exceptions must be reported to the user in many cases. 'Show' is reserved for emitting Haskell code, but that's not of interest for application users. A widely adopted class for generating user friendly, maybe pretty printed, text, does not exist so far. Application users are even interested in localised messages. So there should be a class which generates localised messages for exceptions.
o For 6.10, make the new Exceptions available so that everyone can start working on switching, but leave old Exceptions as the default so that existing programs still work. Prominently mark old exceptions as deprecated in all documentation.
Please wait a bit even with deprecation. In 6.10 the new exception modules will still be in flow, one should not urge users to skip to this construction site. If the advantages become obvious programmers will skip automatically. I would not remove the current modules for a long time. Module interfaces are never perfect. There will be new type extensions which allow for even nicer function types, and then you want to replace all IO modules, again. It's better to start a naming scheme which is open for future extensions and replacements.

Henning Thielemann wrote:
Then there should be new modules that strictly separate between error handling (they should be located under Debug) and exception handling (they should be under Control.Monad).
I would prefer all exceptions - whether or not they are errors - to be handled using the same mechanism. The distinction between what you call "exceptions" and "errors" can be reflected in the hierarchy of Exception objects. For technical reasons, it may still be necessary to have separate mechanisms for pure exceptions and IO exceptions, but we should try to make these compatible as much as possible.
Exception handling should be done with an ErrorT monad transformer... This should be implemented on top of existing IO...
Unfortunately, that is not possible currently. There are primitives, such as "bracket", that do not support this. The IO system itself would need some modification. But it doesn't seem like that would be too hard, as discussed on this list previously. I wrote:
o For 6.10, make the new Exceptions available so that everyone can start working on switching, but leave old Exceptions as the default so that existing programs still work. Prominently mark old exceptions as deprecated in all documentation.
Please wait a bit even with deprecation.
Yes, I was describing the minimal two-step deprecation process. That makes sense only if we are already certain that the new version is production quality. If not, then we need at least a three-step cycle. But don't forget that although Haskell is now also used for production software, it's also still a research language. So there is a need for steady progress at a brisk pace. Since we do have confidence that this proposal is worthwhile, I suggested the two-step cycle as a compromise.
I would not remove the current modules for a long time.
Also a good idea. But given the current assumption that the module names will remain the same, there will still be a need to make small changes to old code to get it to work. Which means bitrot will begin setting in quickly.
Module interfaces are never perfect. There will be new type extensions which allow for even nicer function types, and then you want to replace all IO modules, again. It's better to start a naming scheme which is open for future extensions and replacements.
Indeed. But I don't think a naming scheme will be enough, and it won't be easy. This is really the same versioning issue that people have been working so hard on for Cabal, except more granular, at the module level.

On Mon, 7 Jul 2008, Yitzchak Gale wrote:
Henning Thielemann wrote:
Then there should be new modules that strictly separate between error handling (they should be located under Debug) and exception handling (they should be under Control.Monad).
I would prefer all exceptions - whether or not they are errors - to be handled using the same mechanism. The distinction between what you call "exceptions" and "errors" can be reflected in the hierarchy of Exception objects.
Exception handling is more frequent than error handling. Error "handling" (should be better called "error hiding" or "bug reporting", because you can really handle errors only by fixing them) will occur at the very outer level of a program, as last resort. If you do error hiding more frequently you invest the time at the wrong place. You better invest it in more error prevention. This can be done at best with the type system, and the Extensible Exception as it stands, fools static type checking by hiding the actual Exception type by some type extensions. This design looks very wrong to me.
Exception handling should be done with an ErrorT monad transformer... This should be implemented on top of existing IO...
Unfortunately, that is not possible currently. There are primitives, such as "bracket", that do not support this.
I don't see the problem. Current 'bracket' would be used for bracketing current IO code, new 'bracket' would be used to bracket new ErrorT based IO code. Then we add a function which allows conversion from ErrorT IO to IO by converting exceptions and then we can start replacing IO by ErrorT IO from the inner of the libraries.

Henning Thielemann wrote:
Exception handling should be done with an ErrorT monad transformer... This should be implemented on top of existing IO...
I wrote:
Unfortunately, that is not possible currently. There are primitives, such as "bracket", that do not support this.
I don't see the problem. Current 'bracket' would be used for bracketing current IO code, new 'bracket' would be used to bracket new ErrorT based IO code.
bracket is a GHC primitive. It works only directly with IO, not with other monads. I don't think there is any way to write "new bracket" right now. bracket is an essential part of exception handling. It is built in to the definition of catch. Regards, Yitz

On Mon, 7 Jul 2008, Yitzchak Gale wrote:
Henning Thielemann wrote:
I don't see the problem. Current 'bracket' would be used for bracketing current IO code, new 'bracket' would be used to bracket new ErrorT based IO code.
bracket is a GHC primitive. It works only directly with IO, not with other monads. I don't think there is any way to write "new bracket" right now.
We could catch GHC primitive exceptions and return pure ExceptionalResult (aka Either) in the basic IO routines like 'readFile'. Btw. new IO modules would also give us the opportunity to get rid of hPut, hGetLine and friends, and convert them to H.put, H.getLine etc.

On 7/7/08, Yitzchak Gale
Henning Thielemann wrote:
I don't see the problem. Current 'bracket' would be used for bracketing current IO code, new 'bracket' would be used to bracket new ErrorT based IO code.
bracket is a GHC primitive. It works only directly with IO, not with other monads. I don't think there is any way to write "new bracket" right now.
bracket is an essential part of exception handling. It is built in to the definition of catch.
It might help to clarify whether you're talking about IO.bracket and IO.catch or Control.Exception.bracket and Control.Exception.catch? David

Henning Thielemann wrote:
I don't see the problem. Current 'bracket' would be used for bracketing current IO code, new 'bracket' would be used to bracket new ErrorT based IO code.
I wrote:
bracket is a GHC primitive. It works only directly with IO, not with other monads. I don't think there is any way to write "new bracket" right now. bracket is an essential part of exception handling. It is built in to the definition of catch.
David Roundy wrote:
It might help to clarify whether you're talking about IO.bracket and IO.catch or Control.Exception.bracket and Control.Exception.catch?
Oops, sorry, you're right. The primitive is block, not bracket. More specifically, blockAsyncExceptions# and unblockAsyncExceptions#. Those are used to implement block, which is used to implement bracket, catch, etc. -Yitzchak

Hello Yitzchak, Tuesday, July 8, 2008, 12:42:05 AM, you wrote:
It might help to clarify whether you're talking about IO.bracket and IO.catch or Control.Exception.bracket and Control.Exception.catch?
Oops, sorry, you're right. The primitive is block, not bracket. More specifically, blockAsyncExceptions# and unblockAsyncExceptions#. Those are used to implement block, which is used to implement bracket, catch, etc.
actually it's a catch# used to implement catch used for everything else. primitives you are mentioned only enable/disable delivering of async exceptions -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi Bulat, I wrote:
...The primitive is block, not bracket. More specifically, blockAsyncExceptions# and unblockAsyncExceptions#. Those are used to implement block, which is used to implement bracket, catch, etc.
Bulat Ziganshin wrote:
actually it's a catch# used to implement catch used for everything else.
Yes, there is also that primitive that is only for IO. I don't remember this moment whether it might be possible to work around this one.
primitives you are mentioned only enable/disable delivering of async exceptions
Yes, and they are critical for catch to avoid deadlock. For this, I didn't find any workaround for the current primitives. If instead we had startBlocking :: IO () stopBlocking :: IO () then we could implement block for other monads. At the time, Simon Marlow wrote that this could be done, but that we would lose out on a certain optimization. Regards, Yitz

On Sun, Jul 06, 2008 at 02:39:52AM +0300, Yitzchak Gale wrote:
To get there with less pain, I think we should:
o For 6.10, make the new Exceptions available so that everyone can start working on switching, but leave old Exceptions as the default so that existing programs still work. Prominently mark old exceptions as deprecated in all documentation.
o In the next version, make the new Exceptions the default. Make sure that programs using new Exceptions for 6.10 will still work (e.g., leave NewException as an alias for Exception, or whatever).
We can do that, although to actually get people to change I think we'd need a good helping of DEPRECATED pragmas. So in 6.10 we'd have: module OldException where ... -- everything has DEPRECATED pragmas module NewException where ... module Exception (module OldException) where import OldException and then in 6.12: module OldException where ... -- everything has DEPRECATED pragmas module Exception where ... module {-# DEPRECATED "Use Exception" #-} NewException (module Exception) where import Exception Thanks Ian

Hello Ian, Monday, July 7, 2008, 7:40:34 PM, you wrote:
We can do that, although to actually get people to change I think we'd need a good helping of DEPRECATED pragmas. So in 6.10 we'd have:
module OldException where ... -- everything has DEPRECATED pragmas module NewException where ... module Exception (module OldException) where import OldException
and then in 6.12:
module OldException where ... -- everything has DEPRECATED pragmas module Exception where ... module {-# DEPRECATED "Use Exception" #-} NewException (module Exception) where import Exception
great idea! for even increasing pain, of course -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Ian Lynagh wrote:
We can do that, although to actually get people to change I think we'd need a good helping of DEPRECATED pragmas...
Bulat Ziganshin wrote:
great idea! for even increasing pain, of course
Assuming that the new exceptions will use the same module name (I know, you don't like that assumption), do you think that Ian's suggestion makes things worse? -Yitz

Hello Yitzchak, Sunday, July 6, 2008, 3:39:52 AM, you wrote:
o For 6.10, make the new Exceptions available so that everyone can start working on switching, but leave old Exceptions as the default so that existing programs still work. Prominently mark old exceptions as deprecated in all documentation.
o In the next version, make the new Exceptions the default. Make sure that programs using new Exceptions for 6.10 will still work (e.g., leave NewException as an alias for Exception, or whatever).
oh... all that we need to do is just to use new module name for new exceptions -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi Bulat, I wrote:
o For 6.10, make the new Exceptions available so that everyone can start working on switching, but leave old Exceptions as the default so that existing programs still work. Prominently mark old exceptions as deprecated in all documentation.
o In the next version, make the new Exceptions the default. Make sure that programs using new Exceptions for 6.10 will still work (e.g., leave NewException as an alias for Exception, or whatever).
Bulat Ziganshin wrote:
oh... all that we need to do is just to use new module name for new exceptions
Yes, that would be even better. There seems to be an assumption that the module name will remain the same, so that is why I suggested the above. Regards, Yitz

Hello Ian, Friday, July 4, 2008, 5:29:24 PM, you wrote:
This is a proposal to replace the current exception mechanism in the base library with extensible exceptions.
extensible exceptions, records and syntax are my favorite missing-in-haskell-garden pets, so my +1000 syntax to defining new exceptions is a bit too fat, but it's probably impossible to use something more direct and consistent like it's done in OOP languages? also, are your examples cover all the possible scenarios of using exceptions? you may consider it as tutorial on "New Exceptions" :) is it planned to be included in 6.10? how it will work with legacy code, in particular libraries developed with old base in mind? how mixed code (throwing/catching exceptions in old and new styles) will work together? -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Fri, Jul 04, 2008 at 09:17:47PM +0400, Bulat Ziganshin wrote:
Friday, July 4, 2008, 5:29:24 PM, you wrote:
This is a proposal to replace the current exception mechanism in the base library with extensible exceptions.
extensible exceptions, records and syntax are my favorite missing-in-haskell-garden pets, so my +1000
syntax to defining new exceptions is a bit too fat, but it's probably impossible to use something more direct and consistent like it's done in OOP languages?
If you have alternative suggestions, now is the time to propose them!
is it planned to be included in 6.10?
Yes.
how it will work with legacy code, in particular libraries developed with old base in mind?
If you import Control.OldException instead of Control.Exception then it will be identical. But fixing old code to work with the new library is very easy (e.g. changing catch to catchAny if you get an ambiguous type variable), and as Simon pointed out, places were you actually have to make changes could do with being sanity checked anyway.
how mixed code (throwing/catching exceptions in old and new styles) will work together?
The new catch will catch all the old exceptions. The old catch will catch all the old types of exception thrown by the new throw. Thanks Ian

Hello Ian, Friday, July 4, 2008, 11:14:27 PM, you wrote:
If you import Control.OldException instead of Control.Exception then it will be identical.
But fixing old code to work with the new library is very easy (e.g. changing catch to catchAny if you get an ambiguous type variable), and as Simon pointed out, places were you actually have to make changes could do with being sanity checked anyway.
so, all libs on hackage developed for 6.8 will become obsolete again? :))) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Ian,
Friday, July 4, 2008, 11:14:27 PM, you wrote:
If you import Control.OldException instead of Control.Exception then it will be identical.
But fixing old code to work with the new library is very easy (e.g. changing catch to catchAny if you get an ambiguous type variable), and as Simon pointed out, places were you actually have to make changes could do with being sanity checked anyway.
so, all libs on hackage developed for 6.8 will become obsolete again? :)))
is it equally possible to put a NewException library for hackage ghc<6.9, providing those new function names that we introduce? Would that help reduce gratuituous incompatibility, or would things still break too much, or is it just plain impossible because of module-naming and how base is fixed? :-) -Isaac

On Fri, 4 Jul 2008, Bulat Ziganshin wrote:
Hello Ian,
Friday, July 4, 2008, 5:29:24 PM, you wrote:
This is a proposal to replace the current exception mechanism in the base library with extensible exceptions.
extensible exceptions, records and syntax are my favorite missing-in-haskell-garden pets, so my +1000
In Modula-3 you have to add the exceptions that can be raised to a PROCEDURE header. Java has adopted this mechanism. http://www.cs.sfu.ca/~cameron/Teaching/383/Exceptions.html I think that's a very clean and safe approach and it can be easily adopted in Haskell, although not as a drop-in replacement. If I call an IO action I want to know precisely what exceptions or possible extensions I have to expect. We can nicely formulate this in Haskell. Say, pure IO never throws exceptions and exceptions are implemented as exceptional return values, like readFile :: IO (Either IOError String) Instead of Either we should use a specific datatype, say data ExceptionalResult e a = Success a | Exception e and (IO (ExceptionalResult IOError String)) could be wrapped in a monad transformer like ErrorT (ErrorT is not the right name, because it is not intended to handle 'error's): ExceptionalAction IOError IO String Now 'catch' gets the signature: catch :: ExceptionalAction e0 m a -> (e0 -> ExceptionalAction e1 m a) -> ExceptionalAction e1 m a E.g. a routine that wants to call system routines with IOError exceptions can wrap IOError in a custom datatype like data MyException = TooLazyToday | IOError IOError and a catch call would look like catch m (\e -> case e of TooLazyToday -> return "bla" IOError err -> throw err)

On Sun, Jul 6, 2008 at 10:13 PM, Henning Thielemann
In Modula-3 you have to add the exceptions that can be raised to a PROCEDURE header. Java has adopted this mechanism.
Many people argue that this was a mistake [1, 2, 3, 4]. For one it requires that you rewrap exceptions at every abstraction boundary or expose your implementation details in the API. For example, imagine that you decide to use an SQL database as a data store and declare that your functions throw an SQLException. If you later change your mind and want to use a plain file for storage you need to change your function's type and thereby break clients that use your API. If you don't want this to happen you have to wrap all exception in MyException and throw that. 1. http://radio.weblogs.com/0122027/stories/2003/04/01/JavasCheckedExceptionsWe... 2. http://www.mindview.net/Etc/Discussions/CheckedExceptions 3. http://www.ibm.com/developerworks/java/library/j-jtp05254.html 4. http://www.oreillynet.com/onjava/blog/2004/09/avoiding_checked_exceptions.ht... Cheers, Johan

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1
In Modula-3 you have to add the exceptions that can be raised to a PROCEDURE header. Java has adopted this mechanism.
Many people argue that this was a mistake [...]
well, i nthe first place, the application should not raise exceptions that the API user can or should not know about. if exceptions don't need to be declared, then this design error (lack of abstraction) can go undetected, but that does not solve it. regards, J.W. -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.9 (GNU/Linux) Comment: Using GnuPG with SUSE - http://enigmail.mozdev.org iEYEARECAAYFAkhyCmoACgkQDqiTJ5Q4dm936QCgowTWscNlgCLUBw6Zr0yyAL9l +ncAn23ww2FACJAKBBzmCUDo87ZPq0oI =o5SP -----END PGP SIGNATURE-----

Henning Thielemann wrote:
In Modula-3 you have to add the exceptions that can be raised to a PROCEDURE header. Java has adopted this mechanism.
Johan Tibell wrote:
Many people argue that this was a mistake
Whether you like it or not, we have this already for pure exceptions. The type system requires it for Either and ErrorT. Regards, Yitz

On Mon, 7 Jul 2008, Yitzchak Gale wrote:
Henning Thielemann wrote:
In Modula-3 you have to add the exceptions that can be raised to a PROCEDURE header. Java has adopted this mechanism.
Johan Tibell wrote:
Many people argue that this was a mistake
Whether you like it or not, we have this already for pure exceptions. The type system requires it for Either and ErrorT.
... and I think, that's a good design.

On Mon, Jul 7, 2008 at 9:02 AM, Johan Tibell
On Sun, Jul 6, 2008 at 10:13 PM, Henning Thielemann
wrote: In Modula-3 you have to add the exceptions that can be raised to a PROCEDURE header. Java has adopted this mechanism.
Many people argue that this was a mistake [1, 2, 3, 4]. For one it requires that you rewrap exceptions at every abstraction boundary or expose your implementation details in the API. For example, imagine that you decide to use an SQL database as a data store and declare that your functions throw an SQLException. If you later change your mind and want to use a plain file for storage you need to change your function's type and thereby break clients that use your API. If you don't want this to happen you have to wrap all exception in MyException and throw that.
In Java it was a mistake, but only because their type system sucks (I program in Java in my day job). There was no way to create a generic (i.e. using Java terminology) class that had the option to throw exceptions prior to 1.5 and even then it was just a hack: interface Foo<E extends Throwable> { public int foo() throws E; } We can implement Foo<IOException> and Foo<RuntimeException> but if the implementation throws two distinct exceptions we must use the common superclass of both, because we can't write Foo. Exceptions as part of the types are a good idea but can become problematic: (.) :: (b -> c throws x) -> (a -> b throws y) -> (a -> c throws x + y) This kind of signature is the only correct way to express this without losing information, but it requires some way to encode the typed union without creating too complicated types. Going back to Java, it is problematic to convert exceptions to abstract the implementation, there's no easy way to provide combinator to do that, but in Haskell this is much easier so I don't think it would be as painful as it is in Java.
1. http://radio.weblogs.com/0122027/stories/2003/04/01/JavasCheckedExceptionsWe... 2. http://www.mindview.net/Etc/Discussions/CheckedExceptions 3. http://www.ibm.com/developerworks/java/library/j-jtp05254.html 4. http://www.oreillynet.com/onjava/blog/2004/09/avoiding_checked_exceptions.ht...
Cheers,
Johan
Best regards, Daniel Yokomizo.

On Mon, 7 Jul 2008, Daniel Yokomizo wrote:
Exceptions as part of the types are a good idea but can become problematic:
(.) :: (b -> c throws x) -> (a -> b throws y) -> (a -> c throws x + y)
You mean (Control.Arrow.<<<) ? :-)
This kind of signature is the only correct way to express this without losing information, but it requires some way to encode the typed union without creating too complicated types.
(Control.Arrow.<<<) also answers the question for an appropriate type signature: All involved actions must use the same exception type. If the types mismatch, it would be easy to convert exceptions of different types to a unifying type.

On Mon, 7 Jul 2008, Johan Tibell wrote:
On Sun, Jul 6, 2008 at 10:13 PM, Henning Thielemann
wrote: In Modula-3 you have to add the exceptions that can be raised to a PROCEDURE header. Java has adopted this mechanism.
Many people argue that this was a mistake [1, 2, 3, 4].
...
1. http://radio.weblogs.com/0122027/stories/2003/04/01/JavasCheckedExceptionsWe... 2. http://www.mindview.net/Etc/Discussions/CheckedExceptions 3. http://www.ibm.com/developerworks/java/library/j-jtp05254.html 4. http://www.oreillynet.com/onjava/blog/2004/09/avoiding_checked_exceptions.ht...
When reading those articles I get the impression, that people dislike Java's checked exceptions because of deficiencies in the system. They have seen so many times that programmers just catched exceptions but did not handle them. It's exactly the same like ignoring return values, which is so easy in C - and also in Haskell's do notation. I think we can avoid some of the deficiencies of checked exceptions in Haskell, and should not try to sweep the problems under the carpet. Those people seem to prefer unchecked exceptions now. I believe that this led to the confusion with respect to exceptions and errors. If there would only be checked exceptions and errors would be the same as exceptions, then one would have to write prototypes like void quickSort (...) throws IndexViolation; that is one had to expose possible bugs in the interface, which is certainly not wanted. :-) This way it might become clearer what I said before: Errors aka bugs are unexpected exceptional situations, whereas Exceptions are expected situations. Let me recall how exceptions entered programming languages. In languages which have no exceptions there are only exceptional return values, say NULL instead of a pointer to a valid address, or a negative value where non-negative values are regular results. In other cases a routine returns a success/error code and the computation result is stored in a VAR or pointer parameter. This way programs look like if (file = OpenFileRead("foo")) { if (window = OpenWindow(windowParams)) { if (button = CreateButton (window, buttonParams)) { ... DeleteButton (button); } else { printf ("button not created\n"); } CloseWindow (window); } else { printf ("window not opened\n"); } CloseFile (file); } else { printf ("file could not be read\n"); } Language designers found it unsatisfying that most of the structure of the program is dictated by rare cases, by the _exceptions_. Thus they developed a mechanism, which let you write many commands one after another and handling the exceptional cases once for a block of commands. Ideally this is combined with a mechanism that frees resources, that were already allocated in a block. Thus the exception mechanism was invented for handling rare but expected cases, it was not intended for debugging. A division by zero or an illegal memory access immediately stops a program in a language without exceptions. Trying to cleanup, to show a bug report form or to save user data in case of an error, can be a good thing, but should not be mixed up with handling of exceptions like "file not found". There is also another unintended application: Escaping from loops or deep recursions, maybe even returning a result by an exception. Actually, in order to define the interaction of abort mechanisms like RETURN in a PROCEDURE or EXIT in LOOP, the Modula-3 designers defined RETURN and EXIT in terms of exceptions (although they suggested to implement them more efficiently). These abuses of exceptions made Niklaus Wirth, the inventor of Pascal, fear, that exceptions bring back a GOTO into structured programming languages. In Haskell we have more luck: We can combine exceptional and regular values in a safe way, with Maybe and Either (a type specific to exceptions would be better of course), and we can also return multiple values easily. Thus we can express exceptional situations more easily and safely. We also have overloadable Monad combinators, which allow us to forget the exceptions in a block of consecutive operations. Control.Monad.Error shows the way. In Modula-3 we have a problem with exceptions in call-back functions. A function f, which has the function g as parameter, should certainly f raise all exceptions that g can raise and additionally the exceptions that it raises itself. In Modula-3 you cannot express that, but in Haskell you can: f :: (a -> ErrorT exc IO b) -> a -> ErrorT (Either FException exc) IO b Now it may be that the exceptions in 'exc' overlap with those from FException. This might be resolved by a type class, which merges exc with FException or by some more type hackery, if you like. In the end, people prefering "unchecked exceptions" can still use (ErrorT Dynamic IO a) However the default should be an explicit description of the exceptional cases in the type signature, just as in the Error monad. I have just tried to add support for newer Oracle versions in HSQL's Oracle back-end which uses throwDyn. I wanted to catch the exception, that a system specific table cannot be found, in order to search for another one. However finding out, which exception to catch, means reading the implementation of the table opening function, rather then reading its type signature. This reminds me on programming in dynamically typed languages. I think we can do much better in Haskell.

On Wed, Jul 09, 2008 at 04:17:25PM +0200, Henning Thielemann wrote: ...
There is also another unintended application: Escaping from loops or deep recursions, maybe even returning a result by an exception. Actually, in order to define the interaction of abort mechanisms like RETURN in a PROCEDURE or EXIT in LOOP, the Modula-3 designers defined RETURN and EXIT in terms of exceptions (although they suggested to implement them more efficiently). These abuses of exceptions made Niklaus Wirth, the inventor of Pascal, fear, that exceptions bring back a GOTO into structured programming languages.
Incidentally, the Haskell standard libraries (although not the report) also implement exitWith in terms of an exception. Personally, I think this is a great idea, as I'd rather not deal with two separate mechanisms for cleaning up in unexpected cases (i.e. bugs or exceptions or being passed a function that calls exitWith). Having one exception-handling mechanism allows for modular programming, e.g. I can write a function of type doSomethingThatMightRequireFreeingResources :: ... -> IO a -> IO a rather than requiring some sort of weird trickery to figure out all the possible ways that my argument might possible fail to return so that I can free whatever resources I need to free. David

On Wed, 9 Jul 2008, David Roundy wrote:
On Wed, Jul 09, 2008 at 04:17:25PM +0200, Henning Thielemann wrote: ...
There is also another unintended application: Escaping from loops or deep recursions, maybe even returning a result by an exception. Actually, in order to define the interaction of abort mechanisms like RETURN in a PROCEDURE or EXIT in LOOP, the Modula-3 designers defined RETURN and EXIT in terms of exceptions (although they suggested to implement them more efficiently). These abuses of exceptions made Niklaus Wirth, the inventor of Pascal, fear, that exceptions bring back a GOTO into structured programming languages.
Incidentally, the Haskell standard libraries (although not the report) also implement exitWith in terms of an exception. Personally, I think this is a great idea, as I'd rather not deal with two separate mechanisms for cleaning up in unexpected cases (i.e. bugs or exceptions or being passed a function that calls exitWith).
As I said, in case of a bug, it is not possible to reliably clean up. That an error is encountered proves that your assumptions about your program were wrong, and so the assumptions about allocated resources are probably wrong, too. To pick up Chris Smith's perspectives, cleaning up would be the task for the next higher level, for which your error is only an exception - it has hopefully kept track of the resources you allocated.
Having one exception-handling mechanism allows for modular programming, e.g. I can write a function of type
doSomethingThatMightRequireFreeingResources :: ... -> IO a -> IO a
rather than requiring some sort of weird trickery to figure out all the possible ways that my argument might possible fail to return so that I can free whatever resources I need to free.
Which resource to free does normally not depend on the kind of the exception but on the progress of resource allocation, does it? So resource deallocation would work equally with (IO a) and (ErrorT error IO a). It seems that nobody except me is interested in handling specifically (up to a certain level) the exceptional cases that an IO action can lead to. If I see the type signature getLine :: IO String I have no idea, what kind of exceptions can occur. I even have to be prepared to get OpenGL exceptions. Even error codes in C are more informative in this respect. I would have to handle some exceptions which look reasonable to me, and use a catch-all or rethrow-all mechanism for the rest. Possibly the proposers of the extensible exception method like to rely entirely on catch-all or rethrow-all just like errors. Wouldn't getLine :: ErrorT IOError IO String be much clearer?

Incidentally, the Haskell standard libraries (although not the report) also implement exitWith in terms of an exception. Personally, I think this is a great idea, as I'd rather not deal with two separate mechanisms for cleaning up in unexpected cases (i.e. bugs or exceptions or being passed a function that calls exitWith).
As I said, in case of a bug, it is not possible to reliably clean up. That an error is encountered proves that your assumptions about your program were wrong, and so the assumptions about allocated resources are probably wrong, too. To pick up Chris Smith's perspectives, cleaning up would be the task for the next higher level, for which your error is only an exception - it has hopefully kept track of the resources you allocated.
How would the boundary where an error becomes an exception be defined? Would you have some catch error and rethrow as exception type function which defines the next higher level? In my experience, the "level boundaries" depend a lot on the individual program, and are fuzzy because there are big boundaries and small boundaries. Which ones you think of depend on how disciplined you're being and what level the code is at. Say I have (withFile something_broken). I guess there's some kind of cosmic-ray chance that the broken code could somehow close the file itself and then withFile is in trouble (let's say close a file twice has some dire consequence), but the chance is low enough that there are bigger bugs to chase. Does that mean withFile defines a level boundary that can reliably clean up its broken callee? It seems to me that there are lots of bugs that you can reliably clean up after.
It seems that nobody except me is interested in handling specifically (up to a certain level) the exceptional cases that an IO action can lead to. If I see the type signature getLine :: IO String I have no idea, what kind of exceptions can occur. I even have to be prepared to get OpenGL exceptions. Even error codes in C are more informative in this respect. I would have to handle some exceptions which look reasonable to me, and use a catch-all or rethrow-all mechanism for the rest. Possibly the proposers of the extensible exception method like to rely entirely on catch-all or rethrow-all just like errors. Wouldn't getLine :: ErrorT IOError IO String be much clearer?
It think it would be interesting, though not really solving some big problem I've been having, though sometimes problems are obvious only in retrospect. Is there an implementation to experiment with? But... isn't it out of the scope of this proposal? And I'm not sure how it fits in with the errors vs. exception distinction, or even what the api for errors would look like. A parallel set of throwError catchError etc.? Then it would just be a different kind of exception.

On Thu, 10 Jul 2008, Evan Laforge wrote:
As I said, in case of a bug, it is not possible to reliably clean up. That an error is encountered proves that your assumptions about your program were wrong, and so the assumptions about allocated resources are probably wrong, too. To pick up Chris Smith's perspectives, cleaning up would be the task for the next higher level, for which your error is only an exception - it has hopefully kept track of the resources you allocated.
How would the boundary where an error becomes an exception be defined? Would you have some catch error and rethrow as exception type function which defines the next higher level? In my experience, the "level boundaries" depend a lot on the individual program, and are fuzzy because there are big boundaries and small boundaries. Which ones you think of depend on how disciplined you're being and what level the code is at.
Within the same program you will have a very small number of such boundaries, say one or two. As far as I can judge, in GHC there is one such boundary. If the compiler encounters a strange behaviour of itself, it quits with 'Panic! report bug to ...'. I think that's the most one can do in such a case. Also a GUI driven application will have to quit in case of an error, maybe asking the user to save his data to a different location (not overwriting existing files, because the rescued data might be corrupted). A server will consider its plugins as a sublevel and should not crash, if a plugin crashes.
Say I have (withFile something_broken). I guess there's some kind of cosmic-ray chance that the broken code could somehow close the file itself and then withFile is in trouble (let's say close a file twice has some dire consequence), but the chance is low enough that there are bigger bugs to chase. Does that mean withFile defines a level boundary that can reliably clean up its broken callee?
In my experience (with exceptions in an imperative language) I had cases where some cleanup routines caused crashes, but they were actually correct. They only crashed because something different went wrong before. It's then hard to find the real source of the problem - but let us aside this, since that's an debugging problem.
It seems to me that there are lots of bugs that you can reliably clean up after.
It's certainly worth to explore that possibility, but its different from cleaning up in case of exceptions. Cleaning up in case of an error doesn't resolve the problem, that is, it doesn't fix the bug, but it may make you live more comfortable with the bug.
It seems that nobody except me is interested in handling specifically (up to a certain level) the exceptional cases that an IO action can lead to. If I see the type signature getLine :: IO String I have no idea, what kind of exceptions can occur. I even have to be prepared to get OpenGL exceptions. Even error codes in C are more informative in this respect. I would have to handle some exceptions which look reasonable to me, and use a catch-all or rethrow-all mechanism for the rest. Possibly the proposers of the extensible exception method like to rely entirely on catch-all or rethrow-all just like errors. Wouldn't getLine :: ErrorT IOError IO String be much clearer?
It think it would be interesting, though not really solving some big problem I've been having,
Examples?
though sometimes problems are obvious only in retrospect. Is there an implementation to experiment with?
No sorry. It would be certainly worth to work out a counter-proposal to the currently discussed extensible exception proposal. If time allows it ... It would at least throw a new aspect into the discussion of how to introduce "the" extensible exception modules. If there is more than one reasonable generalization then we should not try to replace the current IO modules with new ones, but provide both alternatives.
But... isn't it out of the scope of this proposal? And I'm not sure how it fits in with the errors vs. exception distinction, or even what the api for errors would look like. A parallel set of throwError catchError etc.? Then it would just be a different kind of exception.
Would you like to differentiate the ways your program crashes? I think division by zero, array index out of range and so on should all be handled by quitting the program and reporting the problem to the user, and eventually to the developer. Errors are indicated by "undefined", "error" or just by an infinite loop. I consider "error" to be a sugared version of an infinite loop. It's uniformly refered to as "bottom", isn't it? In case of an infinite loop you can also not cleanup, save user data or report anything to the user. Since referential transparency disallows distinction of several implementations of "bottom", a routine that handles "error"s differently from infinite loops must be a hack. But that's ok, because that "error handling" is actually debugging, and debugging is allowed to use hacks, just like "trace" is a hack, and an "error" that presents values as strings without having the Show constraint, is a hack, too. So, the "error handling" aka "debugging" system can be rather small: indicating errors (I don't call it 'throw', differently from exceptions) error :: String -> a undefined :: a assert :: Bool -> String -> a (runtime check that can be defined in terms of error) In principle, a compiler flag could turn off the generation of code for 'error', because a correct program would never step into 'error', and thus the flag would keep correct programs correct and buggy programs buggy. The flag would only increase performance and decrease debugging information. Debug.catchError :: IO a -> IO a This is a hack that encapsulates a possibly buggy part of a program and cancels the abort started by 'error' and 'undefined'. It can of course not break an infinite loop or repair corrupted data. Maybe it should start another process or some OS sandbox in order to remain unaffected by the damages of the enclosed action. It will be needed for each layer of "conversion" from error to exception, say one or two times in a program. Debug.cleanupOnError :: IO () -> IO a -> IO a Debug.cleanupOnError cleanup action = ... This routine runs 'action' and invokes 'cleanup' if 'action' is aborted by an error. After cleanup, it is again tried to abort the program by "error". If 'action' terminates regularly, no further action is taken, because it is assumed that 'action' could successfully free all acquired resources. There might be another routine that combines that with 'bracket' for normal exceptions, such that a resource is freed both if an exception occurs and if an error is encountered. Calls of this routine might become ubiquitous in a program.

Henning Thielemann wrote:
It seems that nobody except me is interested in handling specifically (up to a certain level) the exceptional cases that an IO action can lead to. If I see the type signature getLine :: IO String I have no idea, what kind of exceptions can occur.
I agree! I want to see a nice API that exposes exceptions in the type. Go to work, maybe put something on Hackage that has an API like you want, that you'd use, for some important set of IO functions. Changing from non-extensible to extensible exceptions (and the base breakup it allows) doesn't seem to make this harder. (Possibly it even makes it easier in the long run, especially if you find some useful way to leverage the new exception type hierarchy). -Isaac

On Fri, 04 Jul 2008 22:29:24 +0900, Ian Lynagh
This is a proposal to replace the current exception mechanism in the base library with extensible exceptions.
I like this change.
The patches are here: http://darcs.haskell.org/ext-excep/ I've attached Examples.hs, which gives some examples of using it.
But It seems that current patches doesn't change GHC.Conc module's catchSTM type. I think we should change that type, too. catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a But One problem is that these changes also affect stm package's interface. We need following functions, and old interface same as IO type catching functions, for usability. catchesSTM :: STM a -> [Handler a] -> STM a catchSTMAny :: STM a -> (forall e . Exception e => e -> STM a) -> STM a ... Do you think we should have another proposal to change catchSTM type, after accepting this proposal? Best Regards, -- shelarcy <shelarcy hotmail.co.jp> http://page.freett.com/shelarcy/

On Sat, Jul 05, 2008 at 03:00:53AM +0900, shelarcy wrote:
On Fri, 04 Jul 2008 22:29:24 +0900, Ian Lynagh
wrote: The patches are here: http://darcs.haskell.org/ext-excep/ I've attached Examples.hs, which gives some examples of using it.
But It seems that current patches doesn't change GHC.Conc module's catchSTM type. I think we should change that type, too.
I agree; I just hadn't got that far yet. Thanks Ian

I have type issues. Look how inconsistent these types are (I think, copied from the patch); some use forall and some use SomeException: catchAny :: IO a -> (forall e . Exception e => e -> IO a) -> IO a setUncaughtExceptionHandler :: (SomeException -> IO ()) -> IO () getUncaughtExceptionHandler :: IO (SomeException -> IO ()) Obviously we should have catchAny :: IO a -> (forall e . Exception e => e -> IO a) -> IO a setUncaughtExceptionHandler :: (forall e . Exception e => e -> IO ()) -> IO () getUncaughtExceptionHandler :: IO (forall e . Exception e => e -> IO ()) But that requires some kind of impredicative types for getUncaughtExceptionHandler. Then, instead, for consistency, obviously we should have catchAny :: IO a -> (SomeException -> IO a) -> IO a setUncaughtExceptionHandler :: (SomeException -> IO ()) -> IO () getUncaughtExceptionHandler :: IO (SomeException -> IO ()) Then we don't even need the Rank2Types extension? Also, according to the extensible exceptions paper p. 4 (footnote 3), `catch` with SomeException type should suffice, such that catchAny is not needed? Or was it decided that the facility to catch SomeException should be separated from the facility to catch any more-specific group of exceptions (since that implementation in the paper looks like a bit of a hack... or perhaps to warn people that it's a bad idea and should use a function with a name that's a big flashing warning)? On a different note: What about strictness? I'll take an arbitrary example from the paper data SomeFloatException = forall a . (Exception a) => SomeFloatException a deriving Typeable Then, (SomeException (SomeArithException (undefined :: SomeFloatException))) is not _|_. I think it's generally a bad idea to throw exceptions that contain _|_ in their values; it would usually be just as good to evaluate their values first and if they're _|_, let that be the exception instead. In this particular case, should the convention for defining nodes in the exception hierarchy, have a strictness annotation, such as the following? data SomeFloatException = forall a . (Exception a) => SomeFloatException !a deriving Typeable data SomeArithException = forall a . (Exception a) => SomeArithException !a deriving Typeable data SomeException = forall a . (Exception a) => SomeException !a deriving Typeable (Since newtype won't work for existentials, we can't use it here.) This flattens the hierarchy out of the way affecting the semantics, while still allowing actual exception types to be lazy if they want to be, e.g. data DivideByZero = DivideByZero --(a non-lazy error with no variables) deriving (Typeable, Show) data ErrorCall = ErrorCall String --not explicitly strict in the string deriving (Typeable, Show) This way (error (error ("abc"++error ...))) still works :-P. More seriously of a reason lack of strictness was annoying was Debug.Trace.trace interleaving, but that's unsafePerformIO business that can be changed separately, and has not much to do with exceptions. Or, error messages that 'show' arguments that weren't already evaluated, and have errors themselves.. that's happened to me :-) -Isaac

Isaac Dupree wrote:
I have type issues.
Oh, I forgot to mention: this type is probably a mistake: mapException :: (Exception e) => (e -> e) -> a -> a That only allows mapping from any class of exceptions to the same class! Perhaps this would work better: mapException :: (SomeException -> SomeException) -> a -> a although I'm not sure how happy I am with the usage of that type (even though it's a "correct" one). I've never used mapException myself though, so I couldn't say. Maybe, mapException :: (Exception e) => (e -> SomeException) -> a -> a or mapException :: (Exception e1, Exception e2) => (e1 -> e2) -> a -> a , and perhaps mapAnyException :: (SomeException -> SomeException) -> a -> a ? Even, maybe a `mapExceptions` similar to `catches`, although I cringe at what it would do with Handler. I tried replacing catches :: IO a -> [Handler a] -> IO a data Handler a = forall e . Exception e => Handler (e -> IO a) with catches :: IO a -> [Handler (IO a)] -> IO a data Handler a = forall e . Exception e => Handler (e -> a) , but it still doesn't quite seem to work happily? I guess this is tolerable: mapExceptions :: [Handler SomeException] -> a -> a although data Handler2 = forall e1 e2. (Exception e1, Exception e2) => Handler2 (e1 -> e2) might be ideal, and mapExceptions :: [Handler Zero] -> a -> a where "Zero" is the type that only contains _|_, obviously work just as well... I'm not sure how hard it is for user-level code to deal with SomeException directly. If it's not that hard to do, probably mapException :: (SomeException -> SomeException) -> a -> a is the most expedient choice for us? -Isaac

On Mon, Jul 07, 2008 at 01:51:11PM -0400, Isaac Dupree wrote:
I have type issues. Look how inconsistent these types are (I think, copied from the patch); some use forall and some use SomeException: catchAny :: IO a -> (forall e . Exception e => e -> IO a) -> IO a setUncaughtExceptionHandler :: (SomeException -> IO ()) -> IO () getUncaughtExceptionHandler :: IO (SomeException -> IO ())
setUncaughtExceptionHandler/getUncaughtExceptionHandler look like they are really part of GHC.TopHandler, which is really internal to GHC. That still needs to be sorted out properly.
catchAny :: IO a -> (SomeException -> IO a) -> IO a Then we don't even need the Rank2Types extension?
I think that's an option, yes, but we do still need ExistentialQuantification, so I'm not sure how much it buys us.
Also, according to the extensible exceptions paper p. 4 (footnote 3), `catch` with SomeException type should suffice, such that catchAny is not needed?
The reason I added catchAny as a separate function was to avoid having to use a type signature. It's not actually necessary, no.
Or was it decided that the facility to catch SomeException should be separated from the facility to catch any more-specific group of exceptions (since that implementation in the paper looks like a bit of a hack... or perhaps to warn people that it's a bad idea and should use a function with a name that's a big flashing warning)?
That footnote doesn't apply to the final definition of catch, which can catch SomeException without an ugly-looking hack.
On a different note: What about strictness?
data SomeFloatException = forall a . (Exception a) => SomeFloatException !a deriving Typeable
I don't have a strong opinion, but since we can't force all exceptions to be "deeply strict", and we can't stop people forgetting to make one strict, I don't think it buys us much. Thanks Ian

Ian Lynagh wrote:
On Mon, Jul 07, 2008 at 01:51:11PM -0400, Isaac Dupree wrote:
I have type issues. Look how inconsistent these types are (I think, copied from the patch); some use forall and some use SomeException: catchAny :: IO a -> (forall e . Exception e => e -> IO a) -> IO a setUncaughtExceptionHandler :: (SomeException -> IO ()) -> IO () getUncaughtExceptionHandler :: IO (SomeException -> IO ())
setUncaughtExceptionHandler/getUncaughtExceptionHandler look like they are really part of GHC.TopHandler, which is really internal to GHC. That still needs to be sorted out properly.
hmm, they're not really supposed to be part of the Exception API? Fine with me...
catchAny :: IO a -> (SomeException -> IO a) -> IO a Then we don't even need the Rank2Types extension?
I think that's an option, yes, but we do still need ExistentialQuantification, so I'm not sure how much it buys us.
well, IIRC nhc98/Yhc's current type system supports ExistentialQuantification but not Rank2Types, which is why I thought it worth mentioning -Isaac

Hi Ian,
Could you upload a package to hackage with the implementation of the
new exception library, with module names that are separate from the
current version? This would be very useful because:
(i) It would give us a chance to try it out, which would help us give
you more meaningful feedback,
(ii) We can see how much code needs to be changed in our current projects,
(iii) It will provide us with a smoother path to transition between
the two libraries, allowing us to port our projects one at a time
without any breackage.
Otherwise, the trac description seems OK, although if most of the time
"catch" needs to be replaced by "catchAny", then perhaps we should
simply call it "catch"?
Hope this helps,
-Iavor
2008/7/4 Ian Lynagh
Hi all,
This is a proposal to replace the current exception mechanism in the base library with extensible exceptions.
It also reimplements the existing exceptions on top of extensible exceptions, for legacy applications.
Proposed deadline: 25th July. http://hackage.haskell.org/trac/ghc/ticket/2419
=== What are extensible exceptions?
Simon's extensible extensions paper is very easy to read, and describes the problems and proposed solution very well: http://www.haskell.org/~simonmar/papers/ext-exceptions.pdf I won't try to reproduce everything the paper says here, but here is the list of what we want extracted from it:
* A hierarchy of exception types, such that a particular catch can choose to catch only exceptions that belong to a particular subclass and re-throw all others. * A way to add new exception types at any point in the hierarchy from library or program code. * The boilerplate code required to add a new type to the exception hierarchy should be minimal. * Exceptions should be thrown and caught using the same primitives, regardless of the types involved.
I heartily recommend having a read through of the paper.
=== Patches and examples
The patches are here: http://darcs.haskell.org/ext-excep/ I've attached Examples.hs, which gives some examples of using it.
The patches aren't polished; if this proposal is accepted then there is some more work to do, moving things around inside the base package to simplify the dependencies, and to maximise the amount of code that can be shared between all the impls. There's also some GHC-specific fiddling to be done, to make GHC.TopHandler use the new exceptions. This can all be done without further library proposals, though.
Also, currently it derives Data.Typeable, which is unportable, but we can easily work around that. The only extensions that I don't think that we can do without are ExistentialQuantification and Rank2Types. DeriveDataTypeable makes the implementation easier, and DeriveDataTypeable and PatternSignatures make using it easier.
=== Library function differences
As far as the library functions are concerned, here are the main differences:
The old and new types for catch are: Old: catch :: IO a -> (Exception -> IO a) -> IO a New: catch :: Exception e => IO a -> (e -> IO a) -> IO a i.e. catch can now catch any type of exception; we don't have to force all the different types of extension into one fixed datatype.
All the other exception functions are similarly changed to handle any type of extension, e.g. we now have try :: Exception e => IO a -> IO (Either e a)
Now that you can write handlers for different exception types, you might want to catch multiple different types at the same point. You can use catches for this. For example, the OldException module needs to catch all the new exception types and put them into the old Exception type, so that the legacy handler can be run on them. It looks like this: catch :: IO a -> (Exception -> IO a) -> IO a catch io handler = io `catches` [Handler (\e -> handler e), Handler (\exc -> handler (ArithException exc)), Handler (\exc -> handler (ArrayException exc)), ...] where the first Handler deals with exceptions of type Exception, the second those of type ArithException, and so on.
If you want to catch all exceptions, e.g. if you want to cleanup and rethrow the exception, or just print the exception at the top-level, you can use the new function catchAny: catchAny :: IO a -> (forall e . Exception e => e -> IO a) -> IO a You can happily write `catchAny` \e -> print e where `catch` \e -> print e would give you an ambiguous type variable error.
There's also ignoreExceptions :: IO () -> IO () which can be used instead of try for things like ignoreExceptions (hClose h) (where we don't look at the result, so the exception type would be ambiguous if we used try). (I'm not sure if this is the best name for this function).
All the build failures I've seen with the new exceptions library have been cases where you need to change a "catch" to "catchAny", "try" to "ignoreExceptions", or occassionally a different function, e.g. "bracket" or "handle", is used to handle any extension, so adding a type signature involving the SomeException type solves the problem.
The old interface is available in Control.OldException. Currently it doesn't catch exceptions that don't fit into the old Exception type; we could catch them, show them and treat them as user errors, but then the exception has changed if it gets rethrown.
Thanks Ian
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

iavor.diatchki:
Hi Ian, Could you upload a package to hackage with the implementation of the new exception library, with module names that are separate from the current version? This would be very useful because: (i) It would give us a chance to try it out, which would help us give you more meaningful feedback, (ii) We can see how much code needs to be changed in our current projects, (iii) It will provide us with a smoother path to transition between the two libraries, allowing us to port our projects one at a time without any breackage.
Otherwise, the trac description seems OK, although if most of the time "catch" needs to be replaced by "catchAny", then perhaps we should simply call it "catch"?
Seconded. Ian, could you put a working Control.Exception.Extensible or some such on hackage, so we could get some experience with it? -- Don

On Mon, Jul 07, 2008 at 02:34:56PM -0700, Iavor Diatchki wrote:
Could you upload a package to hackage with the implementation of the new exception library, with module names that are separate from the current version?
I've attached a module which hopefully exposes the same interface as the proposed new Exception module, except it doesn't include all the new types. It should be sufficient to see how much change is necessary, though. If you want to fill it out with types or put it on hackage then I have no objections, although personally I think it would make more sense to wait until the interface and hierarchy has settled down first.
Otherwise, the trac description seems OK, although if most of the time "catch" needs to be replaced by "catchAny",
I think you've misunderstood something I said: Most of the problems are solved by replacing catch with catchAny, but I don't know if most of the uses of catch cause problems. I wouldn't be that surprised if you're right, though, and most uses of catch are of the form ... `catch` \e -> cleanup >> throw e but if that's the case then I think we'd be better off replacing them with the onException that Simon proposed. Thanks Ian

I wonder if http://hackage.haskell.org/trac/ghc/ticket/960 / http://hackage.haskell.org/trac/ghc/wiki/ExplicitCallStack will affect exceptions (adding information to (some of) them?) in a way that we should consider it for this round of changing exceptions (probably just affects the information in the exception hierarchy somehow).

On Sat, Jul 12, 2008 at 09:21:56AM -0400, Isaac Dupree wrote:
I wonder if http://hackage.haskell.org/trac/ghc/ticket/960 / http://hackage.haskell.org/trac/ghc/wiki/ExplicitCallStack will affect exceptions (adding information to (some of) them?) in a way that we should consider it for this round of changing exceptions (probably just affects the information in the exception hierarchy somehow).
I think that is right. Exceptions made by things like error may just have a [Location] or something in them. I think that to do it nicely they will all need to be in a subhierarchy, with a class that has getLocations and setLocations methods or something. I haven't thought about this properly, though, so there may be a better way to do it. Thanks Ian

On Fri, Jul 04, 2008 at 02:29:24PM +0100, Ian Lynagh wrote:
Also, currently it derives Data.Typeable, which is unportable, but we can easily work around that. The only extensions that I don't think that we can do without are ExistentialQuantification and Rank2Types. DeriveDataTypeable makes the implementation easier, and DeriveDataTypeable and PatternSignatures make using it easier.
If Typeable is going to be in the language, then I think 'deriving Typeable' should not only be included, but be the _only_ way to get Typeable instances. There is a lot of room for compiler specific representations of TypeRep's and a lot of codes invarients can be broken by nasty Typeable instances. Though, this is more a haskell' issue. But I have no qualms about using DeriveDataTypeable in code if I am going to be using Typeable at all. John -- John Meacham - ⑆repetae.net⑆john⑈

I'm a little concerned about it being a hierarchy that doesn't support multiple inheritance. For example, if we want "exceptions with code location info" to be catchable in such a way that we can manipulate that info (even though those exceptions would span across a sensible hierarchy, yet not all exceptions would provide it). It would be possible to model exceptions as a set of classes, e.g. data Exception = Exception [InTypeable] data InTypeable = forall a. (Typeable a{-,perhaps?? Show a-}) => InTypeable a --then sort of similar datas as we're used to from the proposal data IOException = forall a. (IOException a) => IOException a and you can catch exceptions that match some set of classes somehow. Hopefully all exceptions would provide 'show' somehow. Modelling it as a list [InTypeable] seems not ideal, but typeable doesn't provide anything like an Ordering for Set or anything more abstract? I'm not entirely happy with this particular sketch of a proposal, but do people think that my initial issue is something to be concerned about at all? (I'd be glad to be disproved :-) -Isaac

On Thu, Jul 17, 2008 at 09:16:36AM -0400, Isaac Dupree wrote:
I'm not entirely happy with this particular sketch of a proposal, but do people think that my initial issue is something to be concerned about at all? (I'd be glad to be disproved :-)
It's hard to say if it'll be a problem in practice - we don't have any experience with writing exception hierarchies. However, I /think/ that moving from the current proposal to something like your proposal can be done without breaking any existing code, which makes me think we should stick with the simpler design for now to get some experience. It's a big step in the right direction, at least. Thanks Ian

On 2008 Jul 18, at 11:05, Ian Lynagh wrote:
On Thu, Jul 17, 2008 at 09:16:36AM -0400, Isaac Dupree wrote:
I'm not entirely happy with this particular sketch of a proposal, but do people think that my initial issue is something to be concerned about at all? (I'd be glad to be disproved :-)
It's hard to say if it'll be a problem in practice - we don't have any experience with writing exception hierarchies.
I'm going to ask a possibly silly question: has anyone thought about this vis-a-vis Simon's proposal of a new signals API? It's not that unusual for signals (usually SIGUSR1/SIGUSR2, often SIGINT, SIGHUP, sometimes SIGABRT, SIGQUIT) to be used as asynchronous triggers --- which might be best represented in the "Haskell world" as special exceptions. Likewise, it often makes sense to treat SIGPIPE, SIGHUP, SIGINT as exceptions instead of signals. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Fri, 2008-07-18 at 11:19 -0400, Brandon S. Allbery KF8NH wrote:
On 2008 Jul 18, at 11:05, Ian Lynagh wrote:
On Thu, Jul 17, 2008 at 09:16:36AM -0400, Isaac Dupree wrote:
I'm not entirely happy with this particular sketch of a proposal, but do people think that my initial issue is something to be concerned about at all? (I'd be glad to be disproved :-)
It's hard to say if it'll be a problem in practice - we don't have any experience with writing exception hierarchies.
I'm going to ask a possibly silly question: has anyone thought about this vis-a-vis Simon's proposal of a new signals API? It's not that unusual for signals (usually SIGUSR1/SIGUSR2, often SIGINT, SIGHUP, sometimes SIGABRT, SIGQUIT) to be used as asynchronous triggers --- which might be best represented in the "Haskell world" as special exceptions. Likewise, it often makes sense to treat SIGPIPE, SIGHUP, SIGINT as exceptions instead of signals.
SIGINT will be an exception in ghc-6.10. It will throw an async exception to the main thread. We're just trying to think of the details though, eg how to programs like ghci ignore ^C and can it be done in a portable way. SIGPIPE can be ignored because we get a sync exception when we write to a pipe with no reader. Duncan

On Jul 18, 2008, at 12:04 , Duncan Coutts wrote:
On Fri, 2008-07-18 at 11:19 -0400, Brandon S. Allbery KF8NH wrote:
I'm going to ask a possibly silly question: has anyone thought about this vis-a-vis Simon's proposal of a new signals API? It's not that unusual for signals (usually SIGUSR1/SIGUSR2, often SIGINT, SIGHUP, sometimes SIGABRT, SIGQUIT) to be used as asynchronous triggers --- which might be best represented in the "Haskell world" as special exceptions. Likewise, it often makes sense to treat SIGPIPE, SIGHUP, SIGINT as exceptions instead of signals.
SIGINT will be an exception in ghc-6.10. It will throw an async exception to the main thread. We're just trying to think of the details though, eg how to programs like ghci ignore ^C and can it be done in a portable way.
SIGPIPE can be ignored because we get a sync exception when we write to a pipe with no reader.
I think I was more getting at (a) reserving an exception "class" for remapped signals, and (b) optionally providing a convenience function to install a signal handler for a given signal that maps it to the equivalent exception. This should be possible as a separate library, if the extensible exceptions are designed right... -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Fri, 2008-07-18 at 13:17 -0400, Brandon S. Allbery KF8NH wrote:
On Jul 18, 2008, at 12:04 , Duncan Coutts wrote:
On Fri, 2008-07-18 at 11:19 -0400, Brandon S. Allbery KF8NH wrote:
I'm going to ask a possibly silly question: has anyone thought about this vis-a-vis Simon's proposal of a new signals API? It's not that unusual for signals (usually SIGUSR1/SIGUSR2, often SIGINT, SIGHUP, sometimes SIGABRT, SIGQUIT) to be used as asynchronous triggers --- which might be best represented in the "Haskell world" as special exceptions. Likewise, it often makes sense to treat SIGPIPE, SIGHUP, SIGINT as exceptions instead of signals.
SIGINT will be an exception in ghc-6.10. It will throw an async exception to the main thread. We're just trying to think of the details though, eg how to programs like ghci ignore ^C and can it be done in a portable way.
SIGPIPE can be ignored because we get a sync exception when we write to a pipe with no reader.
I think I was more getting at (a) reserving an exception "class" for remapped signals,
What do you mean exactly?
and (b) optionally providing a convenience function to install a signal handler for a given signal that maps it to the equivalent exception.
That's pretty trivial, one line of code: addSignalHandler sigWHATEVER $ \_ -> throwTo threadid exception I'm not sure it's worth adding anything special. Duncan

On 2008 Jul 18, at 19:26, Duncan Coutts wrote:
On Fri, 2008-07-18 at 13:17 -0400, Brandon S. Allbery KF8NH wrote:
I think I was more getting at (a) reserving an exception "class" for remapped signals,
What do you mean exactly?
A reserved section of the hierarchy for translated signals. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Fri, 2008-07-18 at 19:34 -0400, Brandon S. Allbery KF8NH wrote:
On 2008 Jul 18, at 19:26, Duncan Coutts wrote:
On Fri, 2008-07-18 at 13:17 -0400, Brandon S. Allbery KF8NH wrote:
I think I was more getting at (a) reserving an exception "class" for remapped signals,
What do you mean exactly?
A reserved section of the hierarchy for translated signals.
Oh of the exception hierarchy. Sorry I misunderstood. I thought you were talking about the signals api and was confused :-). Duncan

On Fri, 18 Jul 2008, Brandon S. Allbery KF8NH wrote:
On 2008 Jul 18, at 11:05, Ian Lynagh wrote:
On Thu, Jul 17, 2008 at 09:16:36AM -0400, Isaac Dupree wrote:
I'm not entirely happy with this particular sketch of a proposal, but do people think that my initial issue is something to be concerned about at all? (I'd be glad to be disproved :-)
It's hard to say if it'll be a problem in practice - we don't have any experience with writing exception hierarchies.
I'm going to ask a possibly silly question: has anyone thought about this vis-a-vis Simon's proposal of a new signals API? It's not that unusual for signals (usually SIGUSR1/SIGUSR2, often SIGINT, SIGHUP, sometimes SIGABRT, SIGQUIT) to be used as asynchronous triggers --- which might be best represented in the "Haskell world" as special exceptions. Likewise, it often makes sense to treat SIGPIPE, SIGHUP, SIGINT as exceptions instead of signals.
I have seen this solution in Modula-3 (like exception ThreadAlerted), but I'm not happy with it, since the occurence of a signal is not specific to the IO action you call (like CouldNotOpenFile to 'open'). I would use a separate mechanism for signal handling.

Ian Lynagh wrote:
On Thu, Jul 17, 2008 at 09:16:36AM -0400, Isaac Dupree wrote:
I'm not entirely happy with this particular sketch of a proposal, but do people think that my initial issue is something to be concerned about at all? (I'd be glad to be disproved :-)
It's hard to say if it'll be a problem in practice - we don't have any experience with writing exception hierarchies.
However, I /think/ that moving from the current proposal to something like your proposal can be done without breaking any existing code, which makes me think we should stick with the simpler design for now to get some experience. It's a big step in the right direction, at least.
let's analyze what might get "baked in" to ghc release: SomeException as basic exception type that the RTS deals with: that part of the proposal, including the Exception class, is pretty flexible and probably what we want, and (probably) necessary to be tied to GHC. It's not advised to use `seq` on SomeException because it probably won't do any good, and it just might throw an exception :-) More of a nuisance (1 `div` 0 :: Int). Int is likely in base library that can't be upgraded. If so, DivZeroError (in whatever form) has to be defined there too, including its whole slice of the hierarchy. Actually, pattern-match errors are a better example, since it's the compiler's job to insert them. Probably same for RTS exceptions like StackOverflow (if we have any). If we refactor the hierarchy then (just as we are suffering now) we have redundancy issues when viewing it in the old way vs. the new way. I'm not sure whether it's worse or better when changing just part of the hierarchy to work differently. It doesn't look that painful to have different interfaces yet... anyway I propose something like ImplementationException --> CompileTimeException --mostly pattern-match failure --> RunTimeException and everything else can be upgraded? Not sure if those are good names, and where to define numerical exceptions (while accomodating alternate numeric-preludes as best we can). Any idea how much of 'base' we'll be able to shrink away (or more importantly, whether it's so closely tied to the ghc-version that it might not be practical to make upgraded versions that work with older ghc?) -Isaac

On Sat, Jul 19, 2008 at 01:03:56PM -0400, Isaac Dupree wrote:
anyway I propose something like ImplementationException --> CompileTimeException --mostly pattern-match failure --> RunTimeException
I'm a bit confused - what are you proposing we throw if we have a div-by-zero or unhandled-pattern? And the name CompileTimeException feels wrong to me.
Any idea how much of 'base' we'll be able to shrink away (or more importantly, whether it's so closely tied to the ghc-version that it might not be practical to make upgraded versions that work with older ghc?)
It's hard to tell without actually doing some of the work. Thanks Ian

Ian Lynagh wrote:
On Sat, Jul 19, 2008 at 01:03:56PM -0400, Isaac Dupree wrote:
anyway I propose something like ImplementationException --> CompileTimeException --mostly pattern-match failure --> RunTimeException
I'm a bit confused - what are you proposing we throw if we have a div-by-zero or unhandled-pattern?
And the name CompileTimeException feels wrong to me.
sorry, half my problem is I have no idea what to call these things. And that I'm not quite as knowledgable as I'd like about these exceptions. I'll try again: There are a few kinds of exceptions that are generated by (e.g.) GHC itself: they can't change unless you upgrade GHC, not just because they're often in base (or is it ghc-prim now?), but because the compiler or RTS refers directly to the type or its structure. This doesn't include division by zero. That's what I meant by "ImplementationException". Some of these are ones that, by looking at the syntactical structure of your code, you know that cases will be inserted by the compiler that throw some sort of error. I don't remember if there are any ones other than pattern-match failure (which is mentioned in Haskell98). That's what I meant by my poorly-named "CompileTimeException". Others, like stack overflow, are obviously produced by the RTS. I couldn't think of any kind of "ImplementationException" that isn't described by either this or the previous category. That's what I meant by RunTimeException. But I'm not sure anymore if it's such a wise category, since it seems some exceptions could enter or leave this category (if it's possible to implement throwing them in a library, perhaps depending on things like signal handling -- perhaps the RTS had to handle some of those, but perhaps it might possibly be separated from the RTS too). -Isaac

Isaac Dupree wrote:
Ian Lynagh wrote:
On Sat, Jul 19, 2008 at 01:03:56PM -0400, Isaac Dupree wrote:
anyway I propose something like ImplementationException --> CompileTimeException --mostly pattern-match failure --> RunTimeException
I'm a bit confused - what are you proposing we throw if we have a div-by-zero or unhandled-pattern?
And the name CompileTimeException feels wrong to me.
sorry, half my problem is I have no idea what to call these things. And that I'm not quite as knowledgable as I'd like about these exceptions. I'll try again:
There are a few kinds of exceptions that are generated by (e.g.) GHC itself: they can't change unless you upgrade GHC, not just because they're often in base (or is it ghc-prim now?), but because the compiler or RTS refers directly to the type or its structure. This doesn't include division by zero. That's what I meant by "ImplementationException".
Some of these are ones that, by looking at the syntactical structure of your code, you know that cases will be inserted by the compiler that throw some sort of error. I don't remember if there are any ones other than pattern-match failure (which is mentioned in Haskell98). That's what I meant by my poorly-named "CompileTimeException".
Others, like stack overflow, are obviously produced by the RTS. I couldn't think of any kind of "ImplementationException" that isn't described by either this or the previous category. That's what I meant by RunTimeException. But I'm not sure anymore if it's such a wise category, since it seems some exceptions could enter or leave this category (if it's possible to implement throwing them in a library, perhaps depending on things like signal handling -- perhaps the RTS had to handle some of those, but perhaps it might possibly be separated from the RTS too).
A useful class of exceptions is those that can occur anywhere, because they arise from external stimulus, such as the user pressing Control-C. We currently lump these into "AsyncExceptions", but I'm not wedded to the name. I just thought I'd point out that it's useful to be able to identify exceptions from this class. Cheers, Simon

Hello Simon, Monday, July 21, 2008, 3:01:45 PM, you wrote:
--> CompileTimeException --mostly pattern-match failure And the name CompileTimeException feels wrong to me.
for me, it's like hot ice :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (22)
-
Brandon S. Allbery KF8NH
-
Bulat Ziganshin
-
Chris Kuklewicz
-
Chris Smith
-
Daniel Yokomizo
-
daveroundy@gmail.com
-
David Menendez
-
David Roundy
-
Don Stewart
-
Duncan Coutts
-
Evan Laforge
-
Henning Thielemann
-
Ian Lynagh
-
Iavor Diatchki
-
Isaac Dupree
-
Johan Tibell
-
Johannes Waldmann
-
John Meacham
-
Judah Jacobson
-
shelarcy
-
Simon Marlow
-
Yitzchak Gale