Proposal: Extensible exceptions

Iavor Diatchki iavor.diatchki at gmail.com
Mon Jul 7 17:34:56 EDT 2008


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 <igloo at earth.li>:
>
> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>
>


More information about the Libraries mailing list