
Control.Exception currently lacks a good way to supply extra information along with exceptions. For example, exceptions could be thrown along with their callstack[1] or implicit stack[2], but we have no generic way to include this information with exceptions. Proposed Solution ================= The proposed solution is to add a list of `SomeExceptionInfo` to the `SomeException` datatype. This list stores additional information about the exception. These `ExceptionInfo` instances use a mechanism which is pretty much identical to the dynamic way the `Exception` type works: data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo] data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a class Typeable a => ExceptionInfo a where displayExceptionInfo :: a -> String addExceptionInfo :: (ExceptionInfo a, Exception e) => a -> e -> SomeException addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = SomeExceptionWithInfo e (SomeExceptionInfo x : xs) `ExceptionInfo` lacks the to / from functions that `Exception` has, because I don't see much point in supporting a hierarchy for exception info. The `Typeable` superclass constraint supplies the necessary casting. `SomeExceptionInfo` could validly instead just use the constraint `(Typeable a, Show a)`. However, I believe it's good to have a new class for this so that: * The user can specify a custom `displayExceptionInfo` implementation, for when this extra info is presented to the user. This function would be invoked by the `show` implementation for `SomeException`. * Types need to opt-in to be usable with `SomeExceptionInfo`. Similarly to exceptions, I imagine that a type with a `ExceptionInfo` instance won't be used for anything but acting as such an annotation. Having a class for this allows you to ask GHCI about all in-scope exception info types via `:info ExceptionInfo`. Backwards Compatibility ======================= GHC 7.10 adds support for bidirectional pattern synonyms. This means that this change could be made without breaking code: pattern SomeException x <- SomeExceptionWithInfo x _ where SomeException x = SomeExceptionWithInfo x [] Note that consumers of this do not need to enable `-XPatternSynonyms`. Applications ============ Callstacks ---------- As mentioned at the beginning, this can be used to add callstacks to exceptions: newtype ExceptionCallStack = ExceptionCallStack { unExceptionCallStack :: [String] } deriving Typeable instance ExceptionInfo ExceptionCallStack where displayExceptionInfo = unlines . unExceptionCallStack throwIOWithStack :: Exception e => e -> IO a throwIOWithStack e = do stack <- currentCallStack if null stack then throwIO e else throwIO (addExceptionInfo (ExceptionCallStack stack) e) I see little downside for making something like this the default implementation `throwIO`. Each rethrowing of the `SomeException` would add an additional stacktrace to its annotation, much like the output of `+RTS -xc`. Unlike this debug output, though, the stacktraces would be associated with the exception, rather than just listing locations that exceptions were thrown. This makes it tractable to debug exceptions that occur in concurrent programs, or in programs which frequently throw exceptions during normal functioning. Throwing Exceptions in Handlers ------------------------------- Example: main = throwIO InformativeErrorMessage `finally` throwIO ObscureCleanupIssue While `InformativeErrorMessage` got thrown, the user doesn't see it, since `ObscureCleanupIssue` is thrown instead. This causes a few issues: 1. If the exception is handled by the default handler and yielded to the user, then the more informative error is lost. 2. Callers who expect to catch the "Informative error message" won't run their handlers for this exception type. Problem 1 can now easily be resolved by adding some info to the exception: data ExceptionCause = ExceptionCause { unExceptionCause :: SomeException } deriving Typeable instance ExceptionInfo ExceptionCause where displayExceptionInfo fe = "thrown while handling " ++ displayException (unExceptionCause fe) catch :: Exception e => IO a -> (e -> IO a) -> IO a catch f g = f `oldCatch` handler where handler ex = g ex `oldCatch` \(ex' :: SomeException) -> throwIO (addExceptionInfo info ex') where info = ExceptionCause (toException ex) This implementation of `catch` is written in a backwards-compatible way, such that the exception thrown during finalization is still the one that gets rethrown. The "original" exception is recorded in the added info. This is the same approach used by Python 3's `__context__` attribute[3]. This was brought to my attention in a post by Mike Meyer[4], in a thread about having bracket not suppress the original exception[5]. This doesn't directly resolve issue #2, due to this backwards compatibility. With the earlier example, a `catch` handler for `InformativeErrorMessage` won't be invoked, because it isn't the exception being rethrown. This can be resolved by having a variant of catch which instead throws the original exception. This might be a good default for finalization handlers like `bracket` and `finally`. Asynchronous Exceptions ----------------------- Currently, the only reliable way to catch exceptions, ignoring async exceptions, is to fork a new thread. This is the approach used by the enclosed-exceptions[6] package. I think it's quite ugly that we need to go to such lengths due to the lack of one bit of information about the exception! This would resolve ghc trac #5902[7]. base-4.7 added the `SomeAsyncException` type, but this doesn't enforce anything. Any exception can be thrown as a sync or async exception. Instead, we ought to have a reliable way to know if an exception is synchronous or asynchronous. Here's what this would look like: data IsAsync = IsAsync deriving (Typeable, Show) instance ExceptionInfo IsAsync where displayExceptionInfo IsAsync = "thrown asynchronously" throwTo :: Exception e => ThreadId -> e -> IO () throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync The details of this get a bit tricky: What happens if `throwIO` is used to rethrow a `SomeException` which has this `IsAsync` flag set? I'm going to leave out my thoughts on this for now as the interactions between unsafePerformIO and the concept of "rethrowing" async exceptions. Such details are explained in a post by Edsko de Vries[8] and ghc trac #2558[9]. Issue: fromException loses info =============================== I can think of one main non-ideal aspect of this proposal: Currently, the `toException` and `fromException` methods usually form a prism. In other words, when `fromException` yields a `Just`, you should get the same `SomeException` when using `toException` on that value. For example, fail "testing 1 2 3" `catch` \(ex :: SomeException) -> throwIO ex is equivalent to fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex However, with exception info added to just `SomeException`, and no changes to existing `Exception` instances, this doesn't hold. Exceptions caught as a specific exception type get rethrown with less information. One resolution to this is be to add `[SomeExceptionInfo]` as a field to existing `Exception` instances. This would require the use of non-default implementations of the `toException` and `fromException` instances. Another approach is to have variants of `catch` and `throw` which also pass around the `[SomeExceptionInfo]`. [1] https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... [2] https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations [3] https://www.python.org/dev/peps/pep-3134/ [4] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html [5] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html [6] https://hackage.haskell.org/package/enclosed-exceptions [7] https://ghc.haskell.org/trac/ghc/ticket/5902 [8] http://www.edsko.net/2013/06/11/throwTo/ [9] https://ghc.haskell.org/trac/ghc/ticket/2558

Hey Michael, I actually proposed something along these lines that got OK'd by libraries early this past fall, the main challenge we hit was actually doing the enginering to add the stack traces to exceptions! theres some nasty module cycles in base that happen when you try to weave things around so that the standard error "message here" call includes some stack trace info. Have you tried to do that simple starter patch to base? Chris Allen and I spent like 2 days trying to get it to work and just gave up because of the cycles. We (and others) would probably love some headway on that front. Theres also some in progress work to use the dwarf debugging info data in
7.10 to provide useful stack traces in the default builds for GHC afaik, 'cause the stack trace functionality you're pointing at currenlty only work on profiled builds
cheers
-Carter
On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan
Control.Exception currently lacks a good way to supply extra information along with exceptions. For example, exceptions could be thrown along with their callstack[1] or implicit stack[2], but we have no generic way to include this information with exceptions.
Proposed Solution =================
The proposed solution is to add a list of `SomeExceptionInfo` to the `SomeException` datatype. This list stores additional information about the exception. These `ExceptionInfo` instances use a mechanism which is pretty much identical to the dynamic way the `Exception` type works:
data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
class Typeable a => ExceptionInfo a where displayExceptionInfo :: a -> String
addExceptionInfo :: (ExceptionInfo a, Exception e) => a -> e -> SomeException addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = SomeExceptionWithInfo e (SomeExceptionInfo x : xs)
`ExceptionInfo` lacks the to / from functions that `Exception` has, because I don't see much point in supporting a hierarchy for exception info. The `Typeable` superclass constraint supplies the necessary casting.
`SomeExceptionInfo` could validly instead just use the constraint `(Typeable a, Show a)`. However, I believe it's good to have a new class for this so that:
* The user can specify a custom `displayExceptionInfo` implementation, for when this extra info is presented to the user. This function would be invoked by the `show` implementation for `SomeException`.
* Types need to opt-in to be usable with `SomeExceptionInfo`. Similarly to exceptions, I imagine that a type with a `ExceptionInfo` instance won't be used for anything but acting as such an annotation. Having a class for this allows you to ask GHCI about all in-scope exception info types via `:info ExceptionInfo`.
Backwards Compatibility =======================
GHC 7.10 adds support for bidirectional pattern synonyms. This means that this change could be made without breaking code:
pattern SomeException x <- SomeExceptionWithInfo x _ where SomeException x = SomeExceptionWithInfo x []
Note that consumers of this do not need to enable `-XPatternSynonyms`.
Applications ============
Callstacks ----------
As mentioned at the beginning, this can be used to add callstacks to exceptions:
newtype ExceptionCallStack = ExceptionCallStack { unExceptionCallStack :: [String] } deriving Typeable
instance ExceptionInfo ExceptionCallStack where displayExceptionInfo = unlines . unExceptionCallStack
throwIOWithStack :: Exception e => e -> IO a throwIOWithStack e = do stack <- currentCallStack if null stack then throwIO e else throwIO (addExceptionInfo (ExceptionCallStack stack) e)
I see little downside for making something like this the default implementation `throwIO`. Each rethrowing of the `SomeException` would add an additional stacktrace to its annotation, much like the output of `+RTS -xc`. Unlike this debug output, though, the stacktraces would be associated with the exception, rather than just listing locations that exceptions were thrown. This makes it tractable to debug exceptions that occur in concurrent programs, or in programs which frequently throw exceptions during normal functioning.
Throwing Exceptions in Handlers -------------------------------
Example:
main = throwIO InformativeErrorMessage `finally` throwIO ObscureCleanupIssue
While `InformativeErrorMessage` got thrown, the user doesn't see it, since `ObscureCleanupIssue` is thrown instead. This causes a few issues:
1. If the exception is handled by the default handler and yielded to the user, then the more informative error is lost.
2. Callers who expect to catch the "Informative error message" won't run their handlers for this exception type.
Problem 1 can now easily be resolved by adding some info to the exception:
data ExceptionCause = ExceptionCause { unExceptionCause :: SomeException } deriving Typeable
instance ExceptionInfo ExceptionCause where displayExceptionInfo fe = "thrown while handling " ++ displayException (unExceptionCause fe)
catch :: Exception e => IO a -> (e -> IO a) -> IO a catch f g = f `oldCatch` handler where handler ex = g ex `oldCatch` \(ex' :: SomeException) -> throwIO (addExceptionInfo info ex') where info = ExceptionCause (toException ex)
This implementation of `catch` is written in a backwards-compatible way, such that the exception thrown during finalization is still the one that gets rethrown. The "original" exception is recorded in the added info. This is the same approach used by Python 3's `__context__` attribute[3]. This was brought to my attention in a post by Mike Meyer[4], in a thread about having bracket not suppress the original exception[5].
This doesn't directly resolve issue #2, due to this backwards compatibility. With the earlier example, a `catch` handler for `InformativeErrorMessage` won't be invoked, because it isn't the exception being rethrown. This can be resolved by having a variant of catch which instead throws the original exception. This might be a good default for finalization handlers like `bracket` and `finally`.
Asynchronous Exceptions -----------------------
Currently, the only reliable way to catch exceptions, ignoring async exceptions, is to fork a new thread. This is the approach used by the enclosed-exceptions[6] package. I think it's quite ugly that we need to go to such lengths due to the lack of one bit of information about the exception! This would resolve ghc trac #5902[7].
base-4.7 added the `SomeAsyncException` type, but this doesn't enforce anything. Any exception can be thrown as a sync or async exception. Instead, we ought to have a reliable way to know if an exception is synchronous or asynchronous. Here's what this would look like:
data IsAsync = IsAsync deriving (Typeable, Show)
instance ExceptionInfo IsAsync where displayExceptionInfo IsAsync = "thrown asynchronously"
throwTo :: Exception e => ThreadId -> e -> IO () throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync
The details of this get a bit tricky: What happens if `throwIO` is used to rethrow a `SomeException` which has this `IsAsync` flag set? I'm going to leave out my thoughts on this for now as the interactions between unsafePerformIO and the concept of "rethrowing" async exceptions. Such details are explained in a post by Edsko de Vries[8] and ghc trac #2558[9].
Issue: fromException loses info ===============================
I can think of one main non-ideal aspect of this proposal:
Currently, the `toException` and `fromException` methods usually form a prism. In other words, when `fromException` yields a `Just`, you should get the same `SomeException` when using `toException` on that value.
For example,
fail "testing 1 2 3" `catch` \(ex :: SomeException) -> throwIO ex
is equivalent to
fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex
However, with exception info added to just `SomeException`, and no changes to existing `Exception` instances, this doesn't hold. Exceptions caught as a specific exception type get rethrown with less information.
One resolution to this is be to add `[SomeExceptionInfo]` as a field to existing `Exception` instances. This would require the use of non-default implementations of the `toException` and `fromException` instances.
Another approach is to have variants of `catch` and `throw` which also pass around the `[SomeExceptionInfo]`.
[1] https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... [2] https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations [3] https://www.python.org/dev/peps/pep-3134/ [4] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html [5] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html [6] https://hackage.haskell.org/package/enclosed-exceptions [7] https://ghc.haskell.org/trac/ghc/ticket/5902 [8] http://www.edsko.net/2013/06/11/throwTo/ [9] https://ghc.haskell.org/trac/ghc/ticket/2558
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Hi Carter! Interesting! This thread, right? https://mail.haskell.org/pipermail/libraries/2014-December/024429.html I haven't tried this as a patch to base, but I'm certain that the core of the proposal has no extra dependencies. Note that the proposal isn't about stack traces in particular - that's just one application of being able to throw exceptions with extra information. Even if `throwTo` isn't modified to throw exceptions with stack traces, this functionality could be provided outside of `Control.Exception` (though, that does seem like the right place to put it). I'm surprised that the circularity was so problematic, though. Why isn't it sufficient to have an hs-boot file for `GHC.Stack`, which exports `currentCallStack`? -Michael On Tue, Apr 14, 2015 at 7:55 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
Hey Michael, I actually proposed something along these lines that got OK'd by libraries early this past fall, the main challenge we hit was actually doing the enginering to add the stack traces to exceptions! theres some nasty module cycles in base that happen when you try to weave things around so that the standard error "message here" call includes some stack trace info. Have you tried to do that simple starter patch to base?
Chris Allen and I spent like 2 days trying to get it to work and just gave up because of the cycles. We (and others) would probably love some headway on that front.
Theres also some in progress work to use the dwarf debugging info data in
7.10 to provide useful stack traces in the default builds for GHC afaik, 'cause the stack trace functionality you're pointing at currenlty only work on profiled builds
cheers -Carter
On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan
wrote: Control.Exception currently lacks a good way to supply extra information along with exceptions. For example, exceptions could be thrown along with their callstack[1] or implicit stack[2], but we have no generic way to include this information with exceptions.
Proposed Solution =================
The proposed solution is to add a list of `SomeExceptionInfo` to the `SomeException` datatype. This list stores additional information about the exception. These `ExceptionInfo` instances use a mechanism which is pretty much identical to the dynamic way the `Exception` type works:
data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
class Typeable a => ExceptionInfo a where displayExceptionInfo :: a -> String
addExceptionInfo :: (ExceptionInfo a, Exception e) => a -> e -> SomeException addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = SomeExceptionWithInfo e (SomeExceptionInfo x : xs)
`ExceptionInfo` lacks the to / from functions that `Exception` has, because I don't see much point in supporting a hierarchy for exception info. The `Typeable` superclass constraint supplies the necessary casting.
`SomeExceptionInfo` could validly instead just use the constraint `(Typeable a, Show a)`. However, I believe it's good to have a new class for this so that:
* The user can specify a custom `displayExceptionInfo` implementation, for when this extra info is presented to the user. This function would be invoked by the `show` implementation for `SomeException`.
* Types need to opt-in to be usable with `SomeExceptionInfo`. Similarly to exceptions, I imagine that a type with a `ExceptionInfo` instance won't be used for anything but acting as such an annotation. Having a class for this allows you to ask GHCI about all in-scope exception info types via `:info ExceptionInfo`.
Backwards Compatibility =======================
GHC 7.10 adds support for bidirectional pattern synonyms. This means that this change could be made without breaking code:
pattern SomeException x <- SomeExceptionWithInfo x _ where SomeException x = SomeExceptionWithInfo x []
Note that consumers of this do not need to enable `-XPatternSynonyms`.
Applications ============
Callstacks ----------
As mentioned at the beginning, this can be used to add callstacks to exceptions:
newtype ExceptionCallStack = ExceptionCallStack { unExceptionCallStack :: [String] } deriving Typeable
instance ExceptionInfo ExceptionCallStack where displayExceptionInfo = unlines . unExceptionCallStack
throwIOWithStack :: Exception e => e -> IO a throwIOWithStack e = do stack <- currentCallStack if null stack then throwIO e else throwIO (addExceptionInfo (ExceptionCallStack stack) e)
I see little downside for making something like this the default implementation `throwIO`. Each rethrowing of the `SomeException` would add an additional stacktrace to its annotation, much like the output of `+RTS -xc`. Unlike this debug output, though, the stacktraces would be associated with the exception, rather than just listing locations that exceptions were thrown. This makes it tractable to debug exceptions that occur in concurrent programs, or in programs which frequently throw exceptions during normal functioning.
Throwing Exceptions in Handlers -------------------------------
Example:
main = throwIO InformativeErrorMessage `finally` throwIO ObscureCleanupIssue
While `InformativeErrorMessage` got thrown, the user doesn't see it, since `ObscureCleanupIssue` is thrown instead. This causes a few issues:
1. If the exception is handled by the default handler and yielded to the user, then the more informative error is lost.
2. Callers who expect to catch the "Informative error message" won't run their handlers for this exception type.
Problem 1 can now easily be resolved by adding some info to the exception:
data ExceptionCause = ExceptionCause { unExceptionCause :: SomeException } deriving Typeable
instance ExceptionInfo ExceptionCause where displayExceptionInfo fe = "thrown while handling " ++ displayException (unExceptionCause fe)
catch :: Exception e => IO a -> (e -> IO a) -> IO a catch f g = f `oldCatch` handler where handler ex = g ex `oldCatch` \(ex' :: SomeException) -> throwIO (addExceptionInfo info ex') where info = ExceptionCause (toException ex)
This implementation of `catch` is written in a backwards-compatible way, such that the exception thrown during finalization is still the one that gets rethrown. The "original" exception is recorded in the added info. This is the same approach used by Python 3's `__context__` attribute[3]. This was brought to my attention in a post by Mike Meyer[4], in a thread about having bracket not suppress the original exception[5].
This doesn't directly resolve issue #2, due to this backwards compatibility. With the earlier example, a `catch` handler for `InformativeErrorMessage` won't be invoked, because it isn't the exception being rethrown. This can be resolved by having a variant of catch which instead throws the original exception. This might be a good default for finalization handlers like `bracket` and `finally`.
Asynchronous Exceptions -----------------------
Currently, the only reliable way to catch exceptions, ignoring async exceptions, is to fork a new thread. This is the approach used by the enclosed-exceptions[6] package. I think it's quite ugly that we need to go to such lengths due to the lack of one bit of information about the exception! This would resolve ghc trac #5902[7].
base-4.7 added the `SomeAsyncException` type, but this doesn't enforce anything. Any exception can be thrown as a sync or async exception. Instead, we ought to have a reliable way to know if an exception is synchronous or asynchronous. Here's what this would look like:
data IsAsync = IsAsync deriving (Typeable, Show)
instance ExceptionInfo IsAsync where displayExceptionInfo IsAsync = "thrown asynchronously"
throwTo :: Exception e => ThreadId -> e -> IO () throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync
The details of this get a bit tricky: What happens if `throwIO` is used to rethrow a `SomeException` which has this `IsAsync` flag set? I'm going to leave out my thoughts on this for now as the interactions between unsafePerformIO and the concept of "rethrowing" async exceptions. Such details are explained in a post by Edsko de Vries[8] and ghc trac #2558[9].
Issue: fromException loses info ===============================
I can think of one main non-ideal aspect of this proposal:
Currently, the `toException` and `fromException` methods usually form a prism. In other words, when `fromException` yields a `Just`, you should get the same `SomeException` when using `toException` on that value.
For example,
fail "testing 1 2 3" `catch` \(ex :: SomeException) -> throwIO ex
is equivalent to
fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex
However, with exception info added to just `SomeException`, and no changes to existing `Exception` instances, this doesn't hold. Exceptions caught as a specific exception type get rethrown with less information.
One resolution to this is be to add `[SomeExceptionInfo]` as a field to existing `Exception` instances. This would require the use of non-default implementations of the `toException` and `fromException` instances.
Another approach is to have variants of `catch` and `throw` which also pass around the `[SomeExceptionInfo]`.
[1] https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... [2] https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations [3] https://www.python.org/dev/peps/pep-3134/ [4] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html [5] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html [6] https://hackage.haskell.org/package/enclosed-exceptions [7] https://ghc.haskell.org/trac/ghc/ticket/5902 [8] http://www.edsko.net/2013/06/11/throwTo/ [9] https://ghc.haskell.org/trac/ghc/ticket/2558
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

if you can patch prelude error to include stack traces, i will owe you a
=1 beer each at the next two icfps. Thats all i want for christmas. :)
i can't speak for how a different patch might work out, because thats not
what I'd tried at the time. If you have a go, please share the results!
-Carter
On Wed, Apr 15, 2015 at 12:22 AM, Michael Sloan
Hi Carter!
Interesting! This thread, right? https://mail.haskell.org/pipermail/libraries/2014-December/024429.html
I haven't tried this as a patch to base, but I'm certain that the core of the proposal has no extra dependencies. Note that the proposal isn't about stack traces in particular - that's just one application of being able to throw exceptions with extra information.
Even if `throwTo` isn't modified to throw exceptions with stack traces, this functionality could be provided outside of `Control.Exception` (though, that does seem like the right place to put it). I'm surprised that the circularity was so problematic, though. Why isn't it sufficient to have an hs-boot file for `GHC.Stack`, which exports `currentCallStack`?
-Michael
On Tue, Apr 14, 2015 at 7:55 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
Hey Michael, I actually proposed something along these lines that got OK'd by libraries early this past fall, the main challenge we hit was actually doing the enginering to add the stack traces to exceptions! theres some nasty module cycles in base that happen when you try to weave things around so that the standard error "message here" call includes some stack trace info. Have you tried to do that simple starter patch to base?
Chris Allen and I spent like 2 days trying to get it to work and just gave up because of the cycles. We (and others) would probably love some headway on that front.
Theres also some in progress work to use the dwarf debugging info data in
7.10 to provide useful stack traces in the default builds for GHC afaik, 'cause the stack trace functionality you're pointing at currenlty only work on profiled builds
cheers -Carter
On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan
wrote: Control.Exception currently lacks a good way to supply extra information along with exceptions. For example, exceptions could be thrown along with their callstack[1] or implicit stack[2], but we have no generic way to include this information with exceptions.
Proposed Solution =================
The proposed solution is to add a list of `SomeExceptionInfo` to the `SomeException` datatype. This list stores additional information about the exception. These `ExceptionInfo` instances use a mechanism which is pretty much identical to the dynamic way the `Exception` type works:
data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
class Typeable a => ExceptionInfo a where displayExceptionInfo :: a -> String
addExceptionInfo :: (ExceptionInfo a, Exception e) => a -> e -> SomeException addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = SomeExceptionWithInfo e (SomeExceptionInfo x : xs)
`ExceptionInfo` lacks the to / from functions that `Exception` has, because I don't see much point in supporting a hierarchy for exception info. The `Typeable` superclass constraint supplies the necessary casting.
`SomeExceptionInfo` could validly instead just use the constraint `(Typeable a, Show a)`. However, I believe it's good to have a new class for this so that:
* The user can specify a custom `displayExceptionInfo` implementation, for when this extra info is presented to the user. This function would be invoked by the `show` implementation for `SomeException`.
* Types need to opt-in to be usable with `SomeExceptionInfo`. Similarly to exceptions, I imagine that a type with a `ExceptionInfo` instance won't be used for anything but acting as such an annotation. Having a class for this allows you to ask GHCI about all in-scope exception info types via `:info ExceptionInfo`.
Backwards Compatibility =======================
GHC 7.10 adds support for bidirectional pattern synonyms. This means that this change could be made without breaking code:
pattern SomeException x <- SomeExceptionWithInfo x _ where SomeException x = SomeExceptionWithInfo x []
Note that consumers of this do not need to enable `-XPatternSynonyms`.
Applications ============
Callstacks ----------
As mentioned at the beginning, this can be used to add callstacks to exceptions:
newtype ExceptionCallStack = ExceptionCallStack { unExceptionCallStack :: [String] } deriving Typeable
instance ExceptionInfo ExceptionCallStack where displayExceptionInfo = unlines . unExceptionCallStack
throwIOWithStack :: Exception e => e -> IO a throwIOWithStack e = do stack <- currentCallStack if null stack then throwIO e else throwIO (addExceptionInfo (ExceptionCallStack stack) e)
I see little downside for making something like this the default implementation `throwIO`. Each rethrowing of the `SomeException` would add an additional stacktrace to its annotation, much like the output of `+RTS -xc`. Unlike this debug output, though, the stacktraces would be associated with the exception, rather than just listing locations that exceptions were thrown. This makes it tractable to debug exceptions that occur in concurrent programs, or in programs which frequently throw exceptions during normal functioning.
Throwing Exceptions in Handlers -------------------------------
Example:
main = throwIO InformativeErrorMessage `finally` throwIO ObscureCleanupIssue
While `InformativeErrorMessage` got thrown, the user doesn't see it, since `ObscureCleanupIssue` is thrown instead. This causes a few issues:
1. If the exception is handled by the default handler and yielded to the user, then the more informative error is lost.
2. Callers who expect to catch the "Informative error message" won't run their handlers for this exception type.
Problem 1 can now easily be resolved by adding some info to the exception:
data ExceptionCause = ExceptionCause { unExceptionCause :: SomeException } deriving Typeable
instance ExceptionInfo ExceptionCause where displayExceptionInfo fe = "thrown while handling " ++ displayException (unExceptionCause fe)
catch :: Exception e => IO a -> (e -> IO a) -> IO a catch f g = f `oldCatch` handler where handler ex = g ex `oldCatch` \(ex' :: SomeException) -> throwIO (addExceptionInfo info ex') where info = ExceptionCause (toException ex)
This implementation of `catch` is written in a backwards-compatible way, such that the exception thrown during finalization is still the one that gets rethrown. The "original" exception is recorded in the added info. This is the same approach used by Python 3's `__context__` attribute[3]. This was brought to my attention in a post by Mike Meyer[4], in a thread about having bracket not suppress the original exception[5].
This doesn't directly resolve issue #2, due to this backwards compatibility. With the earlier example, a `catch` handler for `InformativeErrorMessage` won't be invoked, because it isn't the exception being rethrown. This can be resolved by having a variant of catch which instead throws the original exception. This might be a good default for finalization handlers like `bracket` and `finally`.
Asynchronous Exceptions -----------------------
Currently, the only reliable way to catch exceptions, ignoring async exceptions, is to fork a new thread. This is the approach used by the enclosed-exceptions[6] package. I think it's quite ugly that we need to go to such lengths due to the lack of one bit of information about the exception! This would resolve ghc trac #5902[7].
base-4.7 added the `SomeAsyncException` type, but this doesn't enforce anything. Any exception can be thrown as a sync or async exception. Instead, we ought to have a reliable way to know if an exception is synchronous or asynchronous. Here's what this would look like:
data IsAsync = IsAsync deriving (Typeable, Show)
instance ExceptionInfo IsAsync where displayExceptionInfo IsAsync = "thrown asynchronously"
throwTo :: Exception e => ThreadId -> e -> IO () throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync
The details of this get a bit tricky: What happens if `throwIO` is used to rethrow a `SomeException` which has this `IsAsync` flag set? I'm going to leave out my thoughts on this for now as the interactions between unsafePerformIO and the concept of "rethrowing" async exceptions. Such details are explained in a post by Edsko de Vries[8] and ghc trac #2558[9].
Issue: fromException loses info ===============================
I can think of one main non-ideal aspect of this proposal:
Currently, the `toException` and `fromException` methods usually form a prism. In other words, when `fromException` yields a `Just`, you should get the same `SomeException` when using `toException` on that value.
For example,
fail "testing 1 2 3" `catch` \(ex :: SomeException) -> throwIO ex
is equivalent to
fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex
However, with exception info added to just `SomeException`, and no changes to existing `Exception` instances, this doesn't hold. Exceptions caught as a specific exception type get rethrown with less information.
One resolution to this is be to add `[SomeExceptionInfo]` as a field to existing `Exception` instances. This would require the use of non-default implementations of the `toException` and `fromException` instances.
Another approach is to have variants of `catch` and `throw` which also pass around the `[SomeExceptionInfo]`.
[1] https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... [2] https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations [3] https://www.python.org/dev/peps/pep-3134/ [4] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html [5] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html [6] https://hackage.haskell.org/package/enclosed-exceptions [7] https://ghc.haskell.org/trac/ghc/ticket/5902 [8] http://www.edsko.net/2013/06/11/throwTo/ [9] https://ghc.haskell.org/trac/ghc/ticket/2558
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I don't have a strong opinion towards this proposal. It definitely seems
useful, but I think most of the uses would be either somewhat niche in
practice, or better addressed by other mechanisms (the call stack stuff).
However I am opposed to adding IsAsync, because I do not think it is
useful. In every case I know where a user wants to differentiate async
exceptions, what they actually want is to differentiate RTS control
exceptions from everything else. I think the proposal would easily
accommodate that, and you could have IsAsync too if there is a use case for
it.
On Thu, Apr 16, 2015, 8:08 PM Carter Schonwald
if you can patch prelude error to include stack traces, i will owe you a
=1 beer each at the next two icfps. Thats all i want for christmas. :)
i can't speak for how a different patch might work out, because thats not what I'd tried at the time. If you have a go, please share the results! -Carter
On Wed, Apr 15, 2015 at 12:22 AM, Michael Sloan
wrote: Hi Carter!
Interesting! This thread, right? https://mail.haskell.org/pipermail/libraries/2014-December/024429.html
I haven't tried this as a patch to base, but I'm certain that the core of the proposal has no extra dependencies. Note that the proposal isn't about stack traces in particular - that's just one application of being able to throw exceptions with extra information.
Even if `throwTo` isn't modified to throw exceptions with stack traces, this functionality could be provided outside of `Control.Exception` (though, that does seem like the right place to put it). I'm surprised that the circularity was so problematic, though. Why isn't it sufficient to have an hs-boot file for `GHC.Stack`, which exports `currentCallStack`?
-Michael
On Tue, Apr 14, 2015 at 7:55 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
Hey Michael, I actually proposed something along these lines that got OK'd by libraries early this past fall, the main challenge we hit was actually doing the enginering to add the stack traces to exceptions! theres some nasty module cycles in base that happen when you try to weave things around so that the standard error "message here" call includes some stack trace info. Have you tried to do that simple starter patch to base?
Chris Allen and I spent like 2 days trying to get it to work and just gave up because of the cycles. We (and others) would probably love some headway on that front.
Theres also some in progress work to use the dwarf debugging info data in >7.10 to provide useful stack traces in the default builds for GHC afaik, 'cause the stack trace functionality you're pointing at currenlty only work on profiled builds
cheers -Carter
On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan
wrote: Control.Exception currently lacks a good way to supply extra information along with exceptions. For example, exceptions could be thrown along with their callstack[1] or implicit stack[2], but we have no generic way to include this information with exceptions.
Proposed Solution =================
The proposed solution is to add a list of `SomeExceptionInfo` to the `SomeException` datatype. This list stores additional information about the exception. These `ExceptionInfo` instances use a mechanism which is pretty much identical to the dynamic way the `Exception` type works:
data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
class Typeable a => ExceptionInfo a where displayExceptionInfo :: a -> String
addExceptionInfo :: (ExceptionInfo a, Exception e) => a -> e -> SomeException addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = SomeExceptionWithInfo e (SomeExceptionInfo x : xs)
`ExceptionInfo` lacks the to / from functions that `Exception` has, because I don't see much point in supporting a hierarchy for exception info. The `Typeable` superclass constraint supplies the necessary casting.
`SomeExceptionInfo` could validly instead just use the constraint `(Typeable a, Show a)`. However, I believe it's good to have a new class for this so that:
* The user can specify a custom `displayExceptionInfo` implementation, for when this extra info is presented to the user. This function would be invoked by the `show` implementation for `SomeException`.
* Types need to opt-in to be usable with `SomeExceptionInfo`. Similarly to exceptions, I imagine that a type with a `ExceptionInfo` instance won't be used for anything but acting as such an annotation. Having a class for this allows you to ask GHCI about all in-scope exception info types via `:info ExceptionInfo`.
Backwards Compatibility =======================
GHC 7.10 adds support for bidirectional pattern synonyms. This means that this change could be made without breaking code:
pattern SomeException x <- SomeExceptionWithInfo x _ where SomeException x = SomeExceptionWithInfo x []
Note that consumers of this do not need to enable `-XPatternSynonyms`.
Applications ============
Callstacks ----------
As mentioned at the beginning, this can be used to add callstacks to exceptions:
newtype ExceptionCallStack = ExceptionCallStack { unExceptionCallStack :: [String] } deriving Typeable
instance ExceptionInfo ExceptionCallStack where displayExceptionInfo = unlines . unExceptionCallStack
throwIOWithStack :: Exception e => e -> IO a throwIOWithStack e = do stack <- currentCallStack if null stack then throwIO e else throwIO (addExceptionInfo (ExceptionCallStack stack) e)
I see little downside for making something like this the default implementation `throwIO`. Each rethrowing of the `SomeException` would add an additional stacktrace to its annotation, much like the output of `+RTS -xc`. Unlike this debug output, though, the stacktraces would be associated with the exception, rather than just listing locations that exceptions were thrown. This makes it tractable to debug exceptions that occur in concurrent programs, or in programs which frequently throw exceptions during normal functioning.
Throwing Exceptions in Handlers -------------------------------
Example:
main = throwIO InformativeErrorMessage `finally` throwIO ObscureCleanupIssue
While `InformativeErrorMessage` got thrown, the user doesn't see it, since `ObscureCleanupIssue` is thrown instead. This causes a few issues:
1. If the exception is handled by the default handler and yielded to the user, then the more informative error is lost.
2. Callers who expect to catch the "Informative error message" won't run their handlers for this exception type.
Problem 1 can now easily be resolved by adding some info to the exception:
data ExceptionCause = ExceptionCause { unExceptionCause :: SomeException } deriving Typeable
instance ExceptionInfo ExceptionCause where displayExceptionInfo fe = "thrown while handling " ++ displayException (unExceptionCause fe)
catch :: Exception e => IO a -> (e -> IO a) -> IO a catch f g = f `oldCatch` handler where handler ex = g ex `oldCatch` \(ex' :: SomeException) -> throwIO (addExceptionInfo info ex') where info = ExceptionCause (toException ex)
This implementation of `catch` is written in a backwards-compatible way, such that the exception thrown during finalization is still the one that gets rethrown. The "original" exception is recorded in the added info. This is the same approach used by Python 3's `__context__` attribute[3]. This was brought to my attention in a post by Mike Meyer[4], in a thread about having bracket not suppress the original exception[5].
This doesn't directly resolve issue #2, due to this backwards compatibility. With the earlier example, a `catch` handler for `InformativeErrorMessage` won't be invoked, because it isn't the exception being rethrown. This can be resolved by having a variant of catch which instead throws the original exception. This might be a good default for finalization handlers like `bracket` and `finally`.
Asynchronous Exceptions -----------------------
Currently, the only reliable way to catch exceptions, ignoring async exceptions, is to fork a new thread. This is the approach used by the enclosed-exceptions[6] package. I think it's quite ugly that we need to go to such lengths due to the lack of one bit of information about the exception! This would resolve ghc trac #5902[7].
base-4.7 added the `SomeAsyncException` type, but this doesn't enforce anything. Any exception can be thrown as a sync or async exception. Instead, we ought to have a reliable way to know if an exception is synchronous or asynchronous. Here's what this would look like:
data IsAsync = IsAsync deriving (Typeable, Show)
instance ExceptionInfo IsAsync where displayExceptionInfo IsAsync = "thrown asynchronously"
throwTo :: Exception e => ThreadId -> e -> IO () throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync
The details of this get a bit tricky: What happens if `throwIO` is used to rethrow a `SomeException` which has this `IsAsync` flag set? I'm going to leave out my thoughts on this for now as the interactions between unsafePerformIO and the concept of "rethrowing" async exceptions. Such details are explained in a post by Edsko de Vries[8] and ghc trac #2558[9].
Issue: fromException loses info ===============================
I can think of one main non-ideal aspect of this proposal:
Currently, the `toException` and `fromException` methods usually form a prism. In other words, when `fromException` yields a `Just`, you should get the same `SomeException` when using `toException` on that value.
For example,
fail "testing 1 2 3" `catch` \(ex :: SomeException) -> throwIO ex
is equivalent to
fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex
However, with exception info added to just `SomeException`, and no changes to existing `Exception` instances, this doesn't hold. Exceptions caught as a specific exception type get rethrown with less information.
One resolution to this is be to add `[SomeExceptionInfo]` as a field to existing `Exception` instances. This would require the use of non-default implementations of the `toException` and `fromException` instances.
Another approach is to have variants of `catch` and `throw` which also pass around the `[SomeExceptionInfo]`.
[1] https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... [2] https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations [3] https://www.python.org/dev/peps/pep-3134/ [4] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html [5] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html [6] https://hackage.haskell.org/package/enclosed-exceptions [7] https://ghc.haskell.org/trac/ghc/ticket/5902 [8] http://www.edsko.net/2013/06/11/throwTo/ [9] https://ghc.haskell.org/trac/ghc/ticket/2558
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

The typical case for wanting to distinguish sync from async exceptions that
I'm aware of is using timeout, e.g.:
timeout (try someAction :: IO (Either SomeException SomeActionResult)
A more concrete example is available in the second code snippet at [1].
[1]
https://www.fpcomplete.com/user/snoyberg/general-haskell/exceptions/catching...
On Tue, Apr 21, 2015 at 8:27 AM John Lato
I don't have a strong opinion towards this proposal. It definitely seems useful, but I think most of the uses would be either somewhat niche in practice, or better addressed by other mechanisms (the call stack stuff).
However I am opposed to adding IsAsync, because I do not think it is useful. In every case I know where a user wants to differentiate async exceptions, what they actually want is to differentiate RTS control exceptions from everything else. I think the proposal would easily accommodate that, and you could have IsAsync too if there is a use case for it.
On Thu, Apr 16, 2015, 8:08 PM Carter Schonwald
wrote: if you can patch prelude error to include stack traces, i will owe you a
=1 beer each at the next two icfps. Thats all i want for christmas. :)
i can't speak for how a different patch might work out, because thats not what I'd tried at the time. If you have a go, please share the results! -Carter
On Wed, Apr 15, 2015 at 12:22 AM, Michael Sloan
wrote: Hi Carter!
Interesting! This thread, right? https://mail.haskell.org/pipermail/libraries/2014-December/024429.html
I haven't tried this as a patch to base, but I'm certain that the core of the proposal has no extra dependencies. Note that the proposal isn't about stack traces in particular - that's just one application of being able to throw exceptions with extra information.
Even if `throwTo` isn't modified to throw exceptions with stack traces, this functionality could be provided outside of `Control.Exception` (though, that does seem like the right place to put it). I'm surprised that the circularity was so problematic, though. Why isn't it sufficient to have an hs-boot file for `GHC.Stack`, which exports `currentCallStack`?
-Michael
On Tue, Apr 14, 2015 at 7:55 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
Hey Michael, I actually proposed something along these lines that got OK'd by libraries early this past fall, the main challenge we hit was actually doing the enginering to add the stack traces to exceptions! theres some nasty module cycles in base that happen when you try to weave things around so that the standard error "message here" call includes some stack trace info. Have you tried to do that simple starter patch to base?
Chris Allen and I spent like 2 days trying to get it to work and just gave up because of the cycles. We (and others) would probably love some headway on that front.
Theres also some in progress work to use the dwarf debugging info data in >7.10 to provide useful stack traces in the default builds for GHC afaik, 'cause the stack trace functionality you're pointing at currenlty only work on profiled builds
cheers -Carter
On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan
wrote: Control.Exception currently lacks a good way to supply extra information along with exceptions. For example, exceptions could be thrown along with their callstack[1] or implicit stack[2], but we have no generic way to include this information with exceptions.
Proposed Solution =================
The proposed solution is to add a list of `SomeExceptionInfo` to the `SomeException` datatype. This list stores additional information about the exception. These `ExceptionInfo` instances use a mechanism which is pretty much identical to the dynamic way the `Exception` type works:
data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
class Typeable a => ExceptionInfo a where displayExceptionInfo :: a -> String
addExceptionInfo :: (ExceptionInfo a, Exception e) => a -> e -> SomeException addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = SomeExceptionWithInfo e (SomeExceptionInfo x : xs)
`ExceptionInfo` lacks the to / from functions that `Exception` has, because I don't see much point in supporting a hierarchy for exception info. The `Typeable` superclass constraint supplies the necessary casting.
`SomeExceptionInfo` could validly instead just use the constraint `(Typeable a, Show a)`. However, I believe it's good to have a new class for this so that:
* The user can specify a custom `displayExceptionInfo` implementation, for when this extra info is presented to the user. This function would be invoked by the `show` implementation for `SomeException`.
* Types need to opt-in to be usable with `SomeExceptionInfo`. Similarly to exceptions, I imagine that a type with a `ExceptionInfo` instance won't be used for anything but acting as such an annotation. Having a class for this allows you to ask GHCI about all in-scope exception info types via `:info ExceptionInfo`.
Backwards Compatibility =======================
GHC 7.10 adds support for bidirectional pattern synonyms. This means that this change could be made without breaking code:
pattern SomeException x <- SomeExceptionWithInfo x _ where SomeException x = SomeExceptionWithInfo x []
Note that consumers of this do not need to enable `-XPatternSynonyms`.
Applications ============
Callstacks ----------
As mentioned at the beginning, this can be used to add callstacks to exceptions:
newtype ExceptionCallStack = ExceptionCallStack { unExceptionCallStack :: [String] } deriving Typeable
instance ExceptionInfo ExceptionCallStack where displayExceptionInfo = unlines . unExceptionCallStack
throwIOWithStack :: Exception e => e -> IO a throwIOWithStack e = do stack <- currentCallStack if null stack then throwIO e else throwIO (addExceptionInfo (ExceptionCallStack stack) e)
I see little downside for making something like this the default implementation `throwIO`. Each rethrowing of the `SomeException` would add an additional stacktrace to its annotation, much like the output of `+RTS -xc`. Unlike this debug output, though, the stacktraces would be associated with the exception, rather than just listing locations that exceptions were thrown. This makes it tractable to debug exceptions that occur in concurrent programs, or in programs which frequently throw exceptions during normal functioning.
Throwing Exceptions in Handlers -------------------------------
Example:
main = throwIO InformativeErrorMessage `finally` throwIO ObscureCleanupIssue
While `InformativeErrorMessage` got thrown, the user doesn't see it, since `ObscureCleanupIssue` is thrown instead. This causes a few issues:
1. If the exception is handled by the default handler and yielded to the user, then the more informative error is lost.
2. Callers who expect to catch the "Informative error message" won't run their handlers for this exception type.
Problem 1 can now easily be resolved by adding some info to the exception:
data ExceptionCause = ExceptionCause { unExceptionCause :: SomeException } deriving Typeable
instance ExceptionInfo ExceptionCause where displayExceptionInfo fe = "thrown while handling " ++ displayException (unExceptionCause fe)
catch :: Exception e => IO a -> (e -> IO a) -> IO a catch f g = f `oldCatch` handler where handler ex = g ex `oldCatch` \(ex' :: SomeException) -> throwIO (addExceptionInfo info ex') where info = ExceptionCause (toException ex)
This implementation of `catch` is written in a backwards-compatible way, such that the exception thrown during finalization is still the one that gets rethrown. The "original" exception is recorded in the added info. This is the same approach used by Python 3's `__context__` attribute[3]. This was brought to my attention in a post by Mike Meyer[4], in a thread about having bracket not suppress the original exception[5].
This doesn't directly resolve issue #2, due to this backwards compatibility. With the earlier example, a `catch` handler for `InformativeErrorMessage` won't be invoked, because it isn't the exception being rethrown. This can be resolved by having a variant of catch which instead throws the original exception. This might be a good default for finalization handlers like `bracket` and `finally`.
Asynchronous Exceptions -----------------------
Currently, the only reliable way to catch exceptions, ignoring async exceptions, is to fork a new thread. This is the approach used by the enclosed-exceptions[6] package. I think it's quite ugly that we need to go to such lengths due to the lack of one bit of information about the exception! This would resolve ghc trac #5902[7].
base-4.7 added the `SomeAsyncException` type, but this doesn't enforce anything. Any exception can be thrown as a sync or async exception. Instead, we ought to have a reliable way to know if an exception is synchronous or asynchronous. Here's what this would look like:
data IsAsync = IsAsync deriving (Typeable, Show)
instance ExceptionInfo IsAsync where displayExceptionInfo IsAsync = "thrown asynchronously"
throwTo :: Exception e => ThreadId -> e -> IO () throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync
The details of this get a bit tricky: What happens if `throwIO` is used to rethrow a `SomeException` which has this `IsAsync` flag set? I'm going to leave out my thoughts on this for now as the interactions between unsafePerformIO and the concept of "rethrowing" async exceptions. Such details are explained in a post by Edsko de Vries[8] and ghc trac #2558[9].
Issue: fromException loses info ===============================
I can think of one main non-ideal aspect of this proposal:
Currently, the `toException` and `fromException` methods usually form a prism. In other words, when `fromException` yields a `Just`, you should get the same `SomeException` when using `toException` on that value.
For example,
fail "testing 1 2 3" `catch` \(ex :: SomeException) -> throwIO ex
is equivalent to
fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex
However, with exception info added to just `SomeException`, and no changes to existing `Exception` instances, this doesn't hold. Exceptions caught as a specific exception type get rethrown with less information.
One resolution to this is be to add `[SomeExceptionInfo]` as a field to existing `Exception` instances. This would require the use of non-default implementations of the `toException` and `fromException` instances.
Another approach is to have variants of `catch` and `throw` which also pass around the `[SomeExceptionInfo]`.
[1] https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... [2] https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations [3] https://www.python.org/dev/peps/pep-3134/ [4] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html [5] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html [6] https://hackage.haskell.org/package/enclosed-exceptions [7] https://ghc.haskell.org/trac/ghc/ticket/5902 [8] http://www.edsko.net/2013/06/11/throwTo/ [9] https://ghc.haskell.org/trac/ghc/ticket/2558
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

That seems reasonable. Objection withdrawn, which makes me neutral overall.
On Mon, Apr 20, 2015, 10:40 PM Michael Snoyman
The typical case for wanting to distinguish sync from async exceptions that I'm aware of is using timeout, e.g.:
timeout (try someAction :: IO (Either SomeException SomeActionResult)
A more concrete example is available in the second code snippet at [1].
[1] https://www.fpcomplete.com/user/snoyberg/general-haskell/exceptions/catching...
On Tue, Apr 21, 2015 at 8:27 AM John Lato
wrote: I don't have a strong opinion towards this proposal. It definitely seems useful, but I think most of the uses would be either somewhat niche in practice, or better addressed by other mechanisms (the call stack stuff).
However I am opposed to adding IsAsync, because I do not think it is useful. In every case I know where a user wants to differentiate async exceptions, what they actually want is to differentiate RTS control exceptions from everything else. I think the proposal would easily accommodate that, and you could have IsAsync too if there is a use case for it.
On Thu, Apr 16, 2015, 8:08 PM Carter Schonwald < carter.schonwald@gmail.com> wrote:
if you can patch prelude error to include stack traces, i will owe you a
=1 beer each at the next two icfps. Thats all i want for christmas. :)
i can't speak for how a different patch might work out, because thats not what I'd tried at the time. If you have a go, please share the results! -Carter
On Wed, Apr 15, 2015 at 12:22 AM, Michael Sloan
wrote: Hi Carter!
Interesting! This thread, right? https://mail.haskell.org/pipermail/libraries/2014-December/024429.html
I haven't tried this as a patch to base, but I'm certain that the core of the proposal has no extra dependencies. Note that the proposal isn't about stack traces in particular - that's just one application of being able to throw exceptions with extra information.
Even if `throwTo` isn't modified to throw exceptions with stack traces, this functionality could be provided outside of `Control.Exception` (though, that does seem like the right place to put it). I'm surprised that the circularity was so problematic, though. Why isn't it sufficient to have an hs-boot file for `GHC.Stack`, which exports `currentCallStack`?
-Michael
On Tue, Apr 14, 2015 at 7:55 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
Hey Michael, I actually proposed something along these lines that got OK'd by libraries early this past fall, the main challenge we hit was actually doing the enginering to add the stack traces to exceptions! theres some nasty module cycles in base that happen when you try to weave things around so that the standard error "message here" call includes some stack trace info. Have you tried to do that simple starter patch to base?
Chris Allen and I spent like 2 days trying to get it to work and just gave up because of the cycles. We (and others) would probably love some headway on that front.
Theres also some in progress work to use the dwarf debugging info data in >7.10 to provide useful stack traces in the default builds for GHC afaik, 'cause the stack trace functionality you're pointing at currenlty only work on profiled builds
cheers -Carter
On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan
wrote: Control.Exception currently lacks a good way to supply extra information along with exceptions. For example, exceptions could be thrown along with their callstack[1] or implicit stack[2], but we have no generic way to include this information with exceptions.
Proposed Solution =================
The proposed solution is to add a list of `SomeExceptionInfo` to the `SomeException` datatype. This list stores additional information about the exception. These `ExceptionInfo` instances use a mechanism which is pretty much identical to the dynamic way the `Exception` type works:
data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
class Typeable a => ExceptionInfo a where displayExceptionInfo :: a -> String
addExceptionInfo :: (ExceptionInfo a, Exception e) => a -> e -> SomeException addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = SomeExceptionWithInfo e (SomeExceptionInfo x : xs)
`ExceptionInfo` lacks the to / from functions that `Exception` has, because I don't see much point in supporting a hierarchy for exception info. The `Typeable` superclass constraint supplies the necessary casting.
`SomeExceptionInfo` could validly instead just use the constraint `(Typeable a, Show a)`. However, I believe it's good to have a new class for this so that:
* The user can specify a custom `displayExceptionInfo` implementation, for when this extra info is presented to the user. This function would be invoked by the `show` implementation for `SomeException`.
* Types need to opt-in to be usable with `SomeExceptionInfo`. Similarly to exceptions, I imagine that a type with a `ExceptionInfo` instance won't be used for anything but acting as such an annotation. Having a class for this allows you to ask GHCI about all in-scope exception info types via `:info ExceptionInfo`.
Backwards Compatibility =======================
GHC 7.10 adds support for bidirectional pattern synonyms. This means that this change could be made without breaking code:
pattern SomeException x <- SomeExceptionWithInfo x _ where SomeException x = SomeExceptionWithInfo x []
Note that consumers of this do not need to enable `-XPatternSynonyms`.
Applications ============
Callstacks ----------
As mentioned at the beginning, this can be used to add callstacks to exceptions:
newtype ExceptionCallStack = ExceptionCallStack { unExceptionCallStack :: [String] } deriving Typeable
instance ExceptionInfo ExceptionCallStack where displayExceptionInfo = unlines . unExceptionCallStack
throwIOWithStack :: Exception e => e -> IO a throwIOWithStack e = do stack <- currentCallStack if null stack then throwIO e else throwIO (addExceptionInfo (ExceptionCallStack stack) e)
I see little downside for making something like this the default implementation `throwIO`. Each rethrowing of the `SomeException` would add an additional stacktrace to its annotation, much like the output of `+RTS -xc`. Unlike this debug output, though, the stacktraces would be associated with the exception, rather than just listing locations that exceptions were thrown. This makes it tractable to debug exceptions that occur in concurrent programs, or in programs which frequently throw exceptions during normal functioning.
Throwing Exceptions in Handlers -------------------------------
Example:
main = throwIO InformativeErrorMessage `finally` throwIO ObscureCleanupIssue
While `InformativeErrorMessage` got thrown, the user doesn't see it, since `ObscureCleanupIssue` is thrown instead. This causes a few issues:
1. If the exception is handled by the default handler and yielded to the user, then the more informative error is lost.
2. Callers who expect to catch the "Informative error message" won't run their handlers for this exception type.
Problem 1 can now easily be resolved by adding some info to the exception:
data ExceptionCause = ExceptionCause { unExceptionCause :: SomeException } deriving Typeable
instance ExceptionInfo ExceptionCause where displayExceptionInfo fe = "thrown while handling " ++ displayException (unExceptionCause fe)
catch :: Exception e => IO a -> (e -> IO a) -> IO a catch f g = f `oldCatch` handler where handler ex = g ex `oldCatch` \(ex' :: SomeException) -> throwIO (addExceptionInfo info ex') where info = ExceptionCause (toException ex)
This implementation of `catch` is written in a backwards-compatible way, such that the exception thrown during finalization is still the one that gets rethrown. The "original" exception is recorded in the added info. This is the same approach used by Python 3's `__context__` attribute[3]. This was brought to my attention in a post by Mike Meyer[4], in a thread about having bracket not suppress the original exception[5].
This doesn't directly resolve issue #2, due to this backwards compatibility. With the earlier example, a `catch` handler for `InformativeErrorMessage` won't be invoked, because it isn't the exception being rethrown. This can be resolved by having a variant of catch which instead throws the original exception. This might be a good default for finalization handlers like `bracket` and `finally`.
Asynchronous Exceptions -----------------------
Currently, the only reliable way to catch exceptions, ignoring async exceptions, is to fork a new thread. This is the approach used by the enclosed-exceptions[6] package. I think it's quite ugly that we need to go to such lengths due to the lack of one bit of information about the exception! This would resolve ghc trac #5902[7].
base-4.7 added the `SomeAsyncException` type, but this doesn't enforce anything. Any exception can be thrown as a sync or async exception. Instead, we ought to have a reliable way to know if an exception is synchronous or asynchronous. Here's what this would look like:
data IsAsync = IsAsync deriving (Typeable, Show)
instance ExceptionInfo IsAsync where displayExceptionInfo IsAsync = "thrown asynchronously"
throwTo :: Exception e => ThreadId -> e -> IO () throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync
The details of this get a bit tricky: What happens if `throwIO` is used to rethrow a `SomeException` which has this `IsAsync` flag set? I'm going to leave out my thoughts on this for now as the interactions between unsafePerformIO and the concept of "rethrowing" async exceptions. Such details are explained in a post by Edsko de Vries[8] and ghc trac #2558[9].
Issue: fromException loses info ===============================
I can think of one main non-ideal aspect of this proposal:
Currently, the `toException` and `fromException` methods usually form a prism. In other words, when `fromException` yields a `Just`, you should get the same `SomeException` when using `toException` on that value.
For example,
fail "testing 1 2 3" `catch` \(ex :: SomeException) -> throwIO ex
is equivalent to
fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex
However, with exception info added to just `SomeException`, and no changes to existing `Exception` instances, this doesn't hold. Exceptions caught as a specific exception type get rethrown with less information.
One resolution to this is be to add `[SomeExceptionInfo]` as a field to existing `Exception` instances. This would require the use of non-default implementations of the `toException` and `fromException` instances.
Another approach is to have variants of `catch` and `throw` which also pass around the `[SomeExceptionInfo]`.
[1] https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... [2] https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations [3] https://www.python.org/dev/peps/pep-3134/ [4] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html [5] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html [6] https://hackage.haskell.org/package/enclosed-exceptions [7] https://ghc.haskell.org/trac/ghc/ticket/5902 [8] http://www.edsko.net/2013/06/11/throwTo/ [9] https://ghc.haskell.org/trac/ghc/ticket/2558
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Thu, Apr 16, 2015 at 8:08 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
if you can patch prelude error to include stack traces, i will owe you a
=1 beer each at the next two icfps. Thats all i want for christmas. :)
Sounds good! No promises, but I'll be giving this a try soon. Looking forward to ICFP beers either way :D i can't speak for how a different patch might work out, because thats not
what I'd tried at the time. If you have a go, please share the results! -Carter
On Wed, Apr 15, 2015 at 12:22 AM, Michael Sloan
wrote: Hi Carter!
Interesting! This thread, right? https://mail.haskell.org/pipermail/libraries/2014-December/024429.html
I haven't tried this as a patch to base, but I'm certain that the core of the proposal has no extra dependencies. Note that the proposal isn't about stack traces in particular - that's just one application of being able to throw exceptions with extra information.
Even if `throwTo` isn't modified to throw exceptions with stack traces, this functionality could be provided outside of `Control.Exception` (though, that does seem like the right place to put it). I'm surprised that the circularity was so problematic, though. Why isn't it sufficient to have an hs-boot file for `GHC.Stack`, which exports `currentCallStack`?
-Michael
On Tue, Apr 14, 2015 at 7:55 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
Hey Michael, I actually proposed something along these lines that got OK'd by libraries early this past fall, the main challenge we hit was actually doing the enginering to add the stack traces to exceptions! theres some nasty module cycles in base that happen when you try to weave things around so that the standard error "message here" call includes some stack trace info. Have you tried to do that simple starter patch to base?
Chris Allen and I spent like 2 days trying to get it to work and just gave up because of the cycles. We (and others) would probably love some headway on that front.
Theres also some in progress work to use the dwarf debugging info data in >7.10 to provide useful stack traces in the default builds for GHC afaik, 'cause the stack trace functionality you're pointing at currenlty only work on profiled builds
cheers -Carter
On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan
wrote: Control.Exception currently lacks a good way to supply extra information along with exceptions. For example, exceptions could be thrown along with their callstack[1] or implicit stack[2], but we have no generic way to include this information with exceptions.
Proposed Solution =================
The proposed solution is to add a list of `SomeExceptionInfo` to the `SomeException` datatype. This list stores additional information about the exception. These `ExceptionInfo` instances use a mechanism which is pretty much identical to the dynamic way the `Exception` type works:
data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
class Typeable a => ExceptionInfo a where displayExceptionInfo :: a -> String
addExceptionInfo :: (ExceptionInfo a, Exception e) => a -> e -> SomeException addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = SomeExceptionWithInfo e (SomeExceptionInfo x : xs)
`ExceptionInfo` lacks the to / from functions that `Exception` has, because I don't see much point in supporting a hierarchy for exception info. The `Typeable` superclass constraint supplies the necessary casting.
`SomeExceptionInfo` could validly instead just use the constraint `(Typeable a, Show a)`. However, I believe it's good to have a new class for this so that:
* The user can specify a custom `displayExceptionInfo` implementation, for when this extra info is presented to the user. This function would be invoked by the `show` implementation for `SomeException`.
* Types need to opt-in to be usable with `SomeExceptionInfo`. Similarly to exceptions, I imagine that a type with a `ExceptionInfo` instance won't be used for anything but acting as such an annotation. Having a class for this allows you to ask GHCI about all in-scope exception info types via `:info ExceptionInfo`.
Backwards Compatibility =======================
GHC 7.10 adds support for bidirectional pattern synonyms. This means that this change could be made without breaking code:
pattern SomeException x <- SomeExceptionWithInfo x _ where SomeException x = SomeExceptionWithInfo x []
Note that consumers of this do not need to enable `-XPatternSynonyms`.
Applications ============
Callstacks ----------
As mentioned at the beginning, this can be used to add callstacks to exceptions:
newtype ExceptionCallStack = ExceptionCallStack { unExceptionCallStack :: [String] } deriving Typeable
instance ExceptionInfo ExceptionCallStack where displayExceptionInfo = unlines . unExceptionCallStack
throwIOWithStack :: Exception e => e -> IO a throwIOWithStack e = do stack <- currentCallStack if null stack then throwIO e else throwIO (addExceptionInfo (ExceptionCallStack stack) e)
I see little downside for making something like this the default implementation `throwIO`. Each rethrowing of the `SomeException` would add an additional stacktrace to its annotation, much like the output of `+RTS -xc`. Unlike this debug output, though, the stacktraces would be associated with the exception, rather than just listing locations that exceptions were thrown. This makes it tractable to debug exceptions that occur in concurrent programs, or in programs which frequently throw exceptions during normal functioning.
Throwing Exceptions in Handlers -------------------------------
Example:
main = throwIO InformativeErrorMessage `finally` throwIO ObscureCleanupIssue
While `InformativeErrorMessage` got thrown, the user doesn't see it, since `ObscureCleanupIssue` is thrown instead. This causes a few issues:
1. If the exception is handled by the default handler and yielded to the user, then the more informative error is lost.
2. Callers who expect to catch the "Informative error message" won't run their handlers for this exception type.
Problem 1 can now easily be resolved by adding some info to the exception:
data ExceptionCause = ExceptionCause { unExceptionCause :: SomeException } deriving Typeable
instance ExceptionInfo ExceptionCause where displayExceptionInfo fe = "thrown while handling " ++ displayException (unExceptionCause fe)
catch :: Exception e => IO a -> (e -> IO a) -> IO a catch f g = f `oldCatch` handler where handler ex = g ex `oldCatch` \(ex' :: SomeException) -> throwIO (addExceptionInfo info ex') where info = ExceptionCause (toException ex)
This implementation of `catch` is written in a backwards-compatible way, such that the exception thrown during finalization is still the one that gets rethrown. The "original" exception is recorded in the added info. This is the same approach used by Python 3's `__context__` attribute[3]. This was brought to my attention in a post by Mike Meyer[4], in a thread about having bracket not suppress the original exception[5].
This doesn't directly resolve issue #2, due to this backwards compatibility. With the earlier example, a `catch` handler for `InformativeErrorMessage` won't be invoked, because it isn't the exception being rethrown. This can be resolved by having a variant of catch which instead throws the original exception. This might be a good default for finalization handlers like `bracket` and `finally`.
Asynchronous Exceptions -----------------------
Currently, the only reliable way to catch exceptions, ignoring async exceptions, is to fork a new thread. This is the approach used by the enclosed-exceptions[6] package. I think it's quite ugly that we need to go to such lengths due to the lack of one bit of information about the exception! This would resolve ghc trac #5902[7].
base-4.7 added the `SomeAsyncException` type, but this doesn't enforce anything. Any exception can be thrown as a sync or async exception. Instead, we ought to have a reliable way to know if an exception is synchronous or asynchronous. Here's what this would look like:
data IsAsync = IsAsync deriving (Typeable, Show)
instance ExceptionInfo IsAsync where displayExceptionInfo IsAsync = "thrown asynchronously"
throwTo :: Exception e => ThreadId -> e -> IO () throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync
The details of this get a bit tricky: What happens if `throwIO` is used to rethrow a `SomeException` which has this `IsAsync` flag set? I'm going to leave out my thoughts on this for now as the interactions between unsafePerformIO and the concept of "rethrowing" async exceptions. Such details are explained in a post by Edsko de Vries[8] and ghc trac #2558[9].
Issue: fromException loses info ===============================
I can think of one main non-ideal aspect of this proposal:
Currently, the `toException` and `fromException` methods usually form a prism. In other words, when `fromException` yields a `Just`, you should get the same `SomeException` when using `toException` on that value.
For example,
fail "testing 1 2 3" `catch` \(ex :: SomeException) -> throwIO ex
is equivalent to
fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex
However, with exception info added to just `SomeException`, and no changes to existing `Exception` instances, this doesn't hold. Exceptions caught as a specific exception type get rethrown with less information.
One resolution to this is be to add `[SomeExceptionInfo]` as a field to existing `Exception` instances. This would require the use of non-default implementations of the `toException` and `fromException` instances.
Another approach is to have variants of `catch` and `throw` which also pass around the `[SomeExceptionInfo]`.
[1] https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... [2] https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations [3] https://www.python.org/dev/peps/pep-3134/ [4] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html [5] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html [6] https://hackage.haskell.org/package/enclosed-exceptions [7] https://ghc.haskell.org/trac/ghc/ticket/5902 [8] http://www.edsko.net/2013/06/11/throwTo/ [9] https://ghc.haskell.org/trac/ghc/ticket/2558
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Maybe I'm missing something, but isn't this already implemented?
https://phabricator.haskell.org/D578
On Tue, Apr 21, 2015 at 1:37 PM, Michael Sloan
On Thu, Apr 16, 2015 at 8:08 PM, Carter Schonwald
wrote: if you can patch prelude error to include stack traces, i will owe you a
=1 beer each at the next two icfps. Thats all i want for christmas. :)
Sounds good! No promises, but I'll be giving this a try soon. Looking forward to ICFP beers either way :D
i can't speak for how a different patch might work out, because thats not what I'd tried at the time. If you have a go, please share the results! -Carter
On Wed, Apr 15, 2015 at 12:22 AM, Michael Sloan
wrote: Hi Carter!
Interesting! This thread, right? https://mail.haskell.org/pipermail/libraries/2014-December/024429.html
I haven't tried this as a patch to base, but I'm certain that the core of the proposal has no extra dependencies. Note that the proposal isn't about stack traces in particular - that's just one application of being able to throw exceptions with extra information.
Even if `throwTo` isn't modified to throw exceptions with stack traces, this functionality could be provided outside of `Control.Exception` (though, that does seem like the right place to put it). I'm surprised that the circularity was so problematic, though. Why isn't it sufficient to have an hs-boot file for `GHC.Stack`, which exports `currentCallStack`?
-Michael
On Tue, Apr 14, 2015 at 7:55 PM, Carter Schonwald
wrote: Hey Michael, I actually proposed something along these lines that got OK'd by libraries early this past fall, the main challenge we hit was actually doing the enginering to add the stack traces to exceptions! theres some nasty module cycles in base that happen when you try to weave things around so that the standard error "message here" call includes some stack trace info. Have you tried to do that simple starter patch to base?
Chris Allen and I spent like 2 days trying to get it to work and just gave up because of the cycles. We (and others) would probably love some headway on that front.
Theres also some in progress work to use the dwarf debugging info data in >7.10 to provide useful stack traces in the default builds for GHC afaik, 'cause the stack trace functionality you're pointing at currenlty only work on profiled builds
cheers -Carter
On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan
wrote: Control.Exception currently lacks a good way to supply extra information along with exceptions. For example, exceptions could be thrown along with their callstack[1] or implicit stack[2], but we have no generic way to include this information with exceptions.
Proposed Solution =================
The proposed solution is to add a list of `SomeExceptionInfo` to the `SomeException` datatype. This list stores additional information about the exception. These `ExceptionInfo` instances use a mechanism which is pretty much identical to the dynamic way the `Exception` type works:
data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
class Typeable a => ExceptionInfo a where displayExceptionInfo :: a -> String
addExceptionInfo :: (ExceptionInfo a, Exception e) => a -> e -> SomeException addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = SomeExceptionWithInfo e (SomeExceptionInfo x : xs)
`ExceptionInfo` lacks the to / from functions that `Exception` has, because I don't see much point in supporting a hierarchy for exception info. The `Typeable` superclass constraint supplies the necessary casting.
`SomeExceptionInfo` could validly instead just use the constraint `(Typeable a, Show a)`. However, I believe it's good to have a new class for this so that:
* The user can specify a custom `displayExceptionInfo` implementation, for when this extra info is presented to the user. This function would be invoked by the `show` implementation for `SomeException`.
* Types need to opt-in to be usable with `SomeExceptionInfo`. Similarly to exceptions, I imagine that a type with a `ExceptionInfo` instance won't be used for anything but acting as such an annotation. Having a class for this allows you to ask GHCI about all in-scope exception info types via `:info ExceptionInfo`.
Backwards Compatibility =======================
GHC 7.10 adds support for bidirectional pattern synonyms. This means that this change could be made without breaking code:
pattern SomeException x <- SomeExceptionWithInfo x _ where SomeException x = SomeExceptionWithInfo x []
Note that consumers of this do not need to enable `-XPatternSynonyms`.
Applications ============
Callstacks ----------
As mentioned at the beginning, this can be used to add callstacks to exceptions:
newtype ExceptionCallStack = ExceptionCallStack { unExceptionCallStack :: [String] } deriving Typeable
instance ExceptionInfo ExceptionCallStack where displayExceptionInfo = unlines . unExceptionCallStack
throwIOWithStack :: Exception e => e -> IO a throwIOWithStack e = do stack <- currentCallStack if null stack then throwIO e else throwIO (addExceptionInfo (ExceptionCallStack stack) e)
I see little downside for making something like this the default implementation `throwIO`. Each rethrowing of the `SomeException` would add an additional stacktrace to its annotation, much like the output of `+RTS -xc`. Unlike this debug output, though, the stacktraces would be associated with the exception, rather than just listing locations that exceptions were thrown. This makes it tractable to debug exceptions that occur in concurrent programs, or in programs which frequently throw exceptions during normal functioning.
Throwing Exceptions in Handlers -------------------------------
Example:
main = throwIO InformativeErrorMessage `finally` throwIO ObscureCleanupIssue
While `InformativeErrorMessage` got thrown, the user doesn't see it, since `ObscureCleanupIssue` is thrown instead. This causes a few issues:
1. If the exception is handled by the default handler and yielded to the user, then the more informative error is lost.
2. Callers who expect to catch the "Informative error message" won't run their handlers for this exception type.
Problem 1 can now easily be resolved by adding some info to the exception:
data ExceptionCause = ExceptionCause { unExceptionCause :: SomeException } deriving Typeable
instance ExceptionInfo ExceptionCause where displayExceptionInfo fe = "thrown while handling " ++ displayException (unExceptionCause fe)
catch :: Exception e => IO a -> (e -> IO a) -> IO a catch f g = f `oldCatch` handler where handler ex = g ex `oldCatch` \(ex' :: SomeException) -> throwIO (addExceptionInfo info ex') where info = ExceptionCause (toException ex)
This implementation of `catch` is written in a backwards-compatible way, such that the exception thrown during finalization is still the one that gets rethrown. The "original" exception is recorded in the added info. This is the same approach used by Python 3's `__context__` attribute[3]. This was brought to my attention in a post by Mike Meyer[4], in a thread about having bracket not suppress the original exception[5].
This doesn't directly resolve issue #2, due to this backwards compatibility. With the earlier example, a `catch` handler for `InformativeErrorMessage` won't be invoked, because it isn't the exception being rethrown. This can be resolved by having a variant of catch which instead throws the original exception. This might be a good default for finalization handlers like `bracket` and `finally`.
Asynchronous Exceptions -----------------------
Currently, the only reliable way to catch exceptions, ignoring async exceptions, is to fork a new thread. This is the approach used by the enclosed-exceptions[6] package. I think it's quite ugly that we need to go to such lengths due to the lack of one bit of information about the exception! This would resolve ghc trac #5902[7].
base-4.7 added the `SomeAsyncException` type, but this doesn't enforce anything. Any exception can be thrown as a sync or async exception. Instead, we ought to have a reliable way to know if an exception is synchronous or asynchronous. Here's what this would look like:
data IsAsync = IsAsync deriving (Typeable, Show)
instance ExceptionInfo IsAsync where displayExceptionInfo IsAsync = "thrown asynchronously"
throwTo :: Exception e => ThreadId -> e -> IO () throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync
The details of this get a bit tricky: What happens if `throwIO` is used to rethrow a `SomeException` which has this `IsAsync` flag set? I'm going to leave out my thoughts on this for now as the interactions between unsafePerformIO and the concept of "rethrowing" async exceptions. Such details are explained in a post by Edsko de Vries[8] and ghc trac #2558[9].
Issue: fromException loses info ===============================
I can think of one main non-ideal aspect of this proposal:
Currently, the `toException` and `fromException` methods usually form a prism. In other words, when `fromException` yields a `Just`, you should get the same `SomeException` when using `toException` on that value.
For example,
fail "testing 1 2 3" `catch` \(ex :: SomeException) -> throwIO ex
is equivalent to
fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex
However, with exception info added to just `SomeException`, and no changes to existing `Exception` instances, this doesn't hold. Exceptions caught as a specific exception type get rethrown with less information.
One resolution to this is be to add `[SomeExceptionInfo]` as a field to existing `Exception` instances. This would require the use of non-default implementations of the `toException` and `fromException` instances.
Another approach is to have variants of `catch` and `throw` which also pass around the `[SomeExceptionInfo]`.
[1] https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... [2] https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations [3] https://www.python.org/dev/peps/pep-3134/ [4] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html [5] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html [6] https://hackage.haskell.org/package/enclosed-exceptions [7] https://ghc.haskell.org/trac/ghc/ticket/5902 [8] http://www.edsko.net/2013/06/11/throwTo/ [9] https://ghc.haskell.org/trac/ghc/ticket/2558
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Hmm, that patch doesn't appear to add stack traces to 'Prelude.error',
which is what Carter wants here. Also, I think it would be done with
profiling callstacks rather than implicit callstacks. But it's certainly
also useful to have functions which do the same with implicit callstacks!
On Tue, Apr 21, 2015 at 1:55 PM, Evan Laforge
Maybe I'm missing something, but isn't this already implemented?
https://phabricator.haskell.org/D578
On Thu, Apr 16, 2015 at 8:08 PM, Carter Schonwald
wrote: if you can patch prelude error to include stack traces, i will owe you a
=1 beer each at the next two icfps. Thats all i want for christmas. :)
Sounds good! No promises, but I'll be giving this a try soon. Looking forward to ICFP beers either way :D
i can't speak for how a different patch might work out, because thats not what I'd tried at the time. If you have a go, please share the results! -Carter
On Wed, Apr 15, 2015 at 12:22 AM, Michael Sloan
wrote: Hi Carter!
Interesting! This thread, right? https://mail.haskell.org/pipermail/libraries/2014-December/024429.html
I haven't tried this as a patch to base, but I'm certain that the core
of
the proposal has no extra dependencies. Note that the proposal isn't about stack traces in particular - that's just one application of being able to throw exceptions with extra information.
Even if `throwTo` isn't modified to throw exceptions with stack traces, this functionality could be provided outside of `Control.Exception` (though, that does seem like the right place to put it). I'm surprised that the circularity was so problematic, though. Why isn't it sufficient to have an hs-boot file for `GHC.Stack`, which exports `currentCallStack`?
-Michael
On Tue, Apr 14, 2015 at 7:55 PM, Carter Schonwald
wrote: Hey Michael, I actually proposed something along these lines that got OK'd by libraries early this past fall, the main challenge we hit was
actually doing
the enginering to add the stack traces to exceptions! theres some nasty module cycles in base that happen when you try to weave things around so that the standard error "message here" call includes some stack trace info. Have you tried to do that simple starter patch to base?
Chris Allen and I spent like 2 days trying to get it to work and just gave up because of the cycles. We (and others) would probably love some headway on that front.
Theres also some in progress work to use the dwarf debugging info data in >7.10 to provide useful stack traces in the default builds for GHC afaik, 'cause the stack trace functionality you're pointing at currenlty only work on profiled builds
cheers -Carter
On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan
wrote: Control.Exception currently lacks a good way to supply extra information along with exceptions. For example, exceptions could be thrown along with their callstack[1] or implicit stack[2], but we
have
no generic way to include this information with exceptions.
Proposed Solution =================
The proposed solution is to add a list of `SomeExceptionInfo` to the `SomeException` datatype. This list stores additional information about the exception. These `ExceptionInfo` instances use a mechanism which is pretty much identical to the dynamic way the `Exception` type works:
data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
class Typeable a => ExceptionInfo a where displayExceptionInfo :: a -> String
addExceptionInfo :: (ExceptionInfo a, Exception e) => a -> e -> SomeException addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = SomeExceptionWithInfo e (SomeExceptionInfo x : xs)
`ExceptionInfo` lacks the to / from functions that `Exception` has, because I don't see much point in supporting a hierarchy for exception info. The `Typeable` superclass constraint supplies the necessary casting.
`SomeExceptionInfo` could validly instead just use the constraint `(Typeable a, Show a)`. However, I believe it's good to have a new class for this so that:
* The user can specify a custom `displayExceptionInfo` implementation, for when this extra info is presented to the user. This function would be invoked by the `show` implementation for `SomeException`.
* Types need to opt-in to be usable with `SomeExceptionInfo`. Similarly to exceptions, I imagine that a type with a `ExceptionInfo` instance won't be used for anything but acting as such an annotation. Having a class for this allows you to ask GHCI about all in-scope exception info types via `:info ExceptionInfo`.
Backwards Compatibility =======================
GHC 7.10 adds support for bidirectional pattern synonyms. This means that this change could be made without breaking code:
pattern SomeException x <- SomeExceptionWithInfo x _ where SomeException x = SomeExceptionWithInfo x []
Note that consumers of this do not need to enable `-XPatternSynonyms`.
Applications ============
Callstacks ----------
As mentioned at the beginning, this can be used to add callstacks to exceptions:
newtype ExceptionCallStack = ExceptionCallStack { unExceptionCallStack :: [String] } deriving Typeable
instance ExceptionInfo ExceptionCallStack where displayExceptionInfo = unlines . unExceptionCallStack
throwIOWithStack :: Exception e => e -> IO a throwIOWithStack e = do stack <- currentCallStack if null stack then throwIO e else throwIO (addExceptionInfo (ExceptionCallStack stack) e)
I see little downside for making something like this the default implementation `throwIO`. Each rethrowing of the `SomeException` would add an additional stacktrace to its annotation, much like the output of `+RTS -xc`. Unlike this debug output, though, the stacktraces would be associated with the exception, rather than just listing locations that exceptions were thrown. This makes it tractable to debug exceptions that occur in concurrent programs, or in programs which frequently throw exceptions during normal functioning.
Throwing Exceptions in Handlers -------------------------------
Example:
main = throwIO InformativeErrorMessage `finally` throwIO ObscureCleanupIssue
While `InformativeErrorMessage` got thrown, the user doesn't see it, since `ObscureCleanupIssue` is thrown instead. This causes a few issues:
1. If the exception is handled by the default handler and yielded to the user, then the more informative error is lost.
2. Callers who expect to catch the "Informative error message" won't run their handlers for this exception type.
Problem 1 can now easily be resolved by adding some info to the exception:
data ExceptionCause = ExceptionCause { unExceptionCause :: SomeException } deriving Typeable
instance ExceptionInfo ExceptionCause where displayExceptionInfo fe = "thrown while handling " ++ displayException (unExceptionCause fe)
catch :: Exception e => IO a -> (e -> IO a) -> IO a catch f g = f `oldCatch` handler where handler ex = g ex `oldCatch` \(ex' :: SomeException) -> throwIO (addExceptionInfo info ex') where info = ExceptionCause (toException ex)
This implementation of `catch` is written in a backwards-compatible way, such that the exception thrown during finalization is still the one that gets rethrown. The "original" exception is recorded in the added info. This is the same approach used by Python 3's `__context__` attribute[3]. This was brought to my attention in a post by Mike Meyer[4], in a thread about having bracket not suppress the original exception[5].
This doesn't directly resolve issue #2, due to this backwards compatibility. With the earlier example, a `catch` handler for `InformativeErrorMessage` won't be invoked, because it isn't the exception being rethrown. This can be resolved by having a variant of catch which instead throws the original exception. This might be a good default for finalization handlers like `bracket` and `finally`.
Asynchronous Exceptions -----------------------
Currently, the only reliable way to catch exceptions, ignoring async exceptions, is to fork a new thread. This is the approach used by
On Tue, Apr 21, 2015 at 1:37 PM, Michael Sloan
wrote: the enclosed-exceptions[6] package. I think it's quite ugly that we need to go to such lengths due to the lack of one bit of information about the exception! This would resolve ghc trac #5902[7].
base-4.7 added the `SomeAsyncException` type, but this doesn't enforce anything. Any exception can be thrown as a sync or async exception. Instead, we ought to have a reliable way to know if an exception is synchronous or asynchronous. Here's what this would look like:
data IsAsync = IsAsync deriving (Typeable, Show)
instance ExceptionInfo IsAsync where displayExceptionInfo IsAsync = "thrown asynchronously"
throwTo :: Exception e => ThreadId -> e -> IO () throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync
The details of this get a bit tricky: What happens if `throwIO` is used to rethrow a `SomeException` which has this `IsAsync` flag set? I'm going to leave out my thoughts on this for now as the interactions between unsafePerformIO and the concept of "rethrowing" async exceptions. Such details are explained in a post by Edsko de Vries[8] and ghc trac #2558[9].
Issue: fromException loses info ===============================
I can think of one main non-ideal aspect of this proposal:
Currently, the `toException` and `fromException` methods usually form a prism. In other words, when `fromException` yields a `Just`, you should get the same `SomeException` when using `toException` on that value.
For example,
fail "testing 1 2 3" `catch` \(ex :: SomeException) -> throwIO ex
is equivalent to
fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex
However, with exception info added to just `SomeException`, and no changes to existing `Exception` instances, this doesn't hold. Exceptions caught as a specific exception type get rethrown with less information.
One resolution to this is be to add `[SomeExceptionInfo]` as a field to existing `Exception` instances. This would require the use of non-default implementations of the `toException` and `fromException` instances.
Another approach is to have variants of `catch` and `throw` which also pass around the `[SomeExceptionInfo]`.
[1]
https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current...
[2]
https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations
https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html
[5]
https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html
[6] https://hackage.haskell.org/package/enclosed-exceptions [7] https://ghc.haskell.org/trac/ghc/ticket/5902 [8] http://www.edsko.net/2013/06/11/throwTo/ [9] https://ghc.haskell.org/trac/ghc/ticket/2558
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Ah, but it looks like Niklas does have a patch which adds implicit
locations to such functions: https://phabricator.haskell.org/D861
However, there are some issues with changing the API of these functions:
https://phabricator.haskell.org/D861#23250
(as mentioned in the "Backporting srcLoc to the GHC 7.10 branch" thread)
On Tue, Apr 21, 2015 at 2:04 PM, Michael Sloan
Hmm, that patch doesn't appear to add stack traces to 'Prelude.error', which is what Carter wants here. Also, I think it would be done with profiling callstacks rather than implicit callstacks. But it's certainly also useful to have functions which do the same with implicit callstacks!
On Tue, Apr 21, 2015 at 1:55 PM, Evan Laforge
wrote: Maybe I'm missing something, but isn't this already implemented?
https://phabricator.haskell.org/D578
On Thu, Apr 16, 2015 at 8:08 PM, Carter Schonwald
wrote: if you can patch prelude error to include stack traces, i will owe you
a
=1 beer each at the next two icfps. Thats all i want for christmas. :)
Sounds good! No promises, but I'll be giving this a try soon. Looking forward to ICFP beers either way :D
i can't speak for how a different patch might work out, because thats not what I'd tried at the time. If you have a go, please share the results! -Carter
On Wed, Apr 15, 2015 at 12:22 AM, Michael Sloan
wrote: Hi Carter!
Interesting! This thread, right?
https://mail.haskell.org/pipermail/libraries/2014-December/024429.html
I haven't tried this as a patch to base, but I'm certain that the
core of
the proposal has no extra dependencies. Note that the proposal isn't about stack traces in particular - that's just one application of being able to throw exceptions with extra information.
Even if `throwTo` isn't modified to throw exceptions with stack
this functionality could be provided outside of `Control.Exception` (though, that does seem like the right place to put it). I'm surprised that
circularity was so problematic, though. Why isn't it sufficient to have an hs-boot file for `GHC.Stack`, which exports `currentCallStack`?
-Michael
On Tue, Apr 14, 2015 at 7:55 PM, Carter Schonwald
wrote: Hey Michael, I actually proposed something along these lines that got OK'd by libraries early this past fall, the main challenge we hit was
actually doing
the enginering to add the stack traces to exceptions! theres some nasty module cycles in base that happen when you try to weave things around so that the standard error "message here" call includes some stack
Have you tried to do that simple starter patch to base?
Chris Allen and I spent like 2 days trying to get it to work and just gave up because of the cycles. We (and others) would probably love some headway on that front.
Theres also some in progress work to use the dwarf debugging info data in >7.10 to provide useful stack traces in the default builds for GHC afaik, 'cause the stack trace functionality you're pointing at currenlty only work on profiled builds
cheers -Carter
On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan
wrote: > > Control.Exception currently lacks a good way to supply extra > information along with exceptions. For example, exceptions could be > thrown along with their callstack[1] or implicit stack[2], but we have > no generic way to include this information with exceptions. > > Proposed Solution > ================= > > The proposed solution is to add a list of `SomeExceptionInfo` to the > `SomeException` datatype. This list stores additional information > about the exception. These `ExceptionInfo` instances use a mechanism > which is pretty much identical to the dynamic way the `Exception` type > works: > > data SomeException = forall e . Exception e => > SomeExceptionWithInfo e [SomeExceptionInfo] > > data SomeExceptionInfo = forall a . ExceptionInfo a => > SomeExceptionInfo a > > class Typeable a => ExceptionInfo a where > displayExceptionInfo :: a -> String > > addExceptionInfo > :: (ExceptionInfo a, Exception e) > => a -> e -> SomeException > addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = > SomeExceptionWithInfo e (SomeExceptionInfo x : xs) > > `ExceptionInfo` lacks the to / from functions that `Exception` has, > because I don't see much point in supporting a hierarchy for exception > info. The `Typeable` superclass constraint supplies the necessary > casting. > > `SomeExceptionInfo` could validly instead just use the constraint > `(Typeable a, Show a)`. However, I believe it's good to have a new > class for this so that: > > * The user can specify a custom `displayExceptionInfo` > implementation, for when this extra info is presented to the user. > This function would be invoked by the `show` implementation for > `SomeException`. > > * Types need to opt-in to be usable with `SomeExceptionInfo`. > Similarly to exceptions, I imagine that a type with a > `ExceptionInfo` instance won't be used for anything but acting as > such an annotation. Having a class for this allows you to ask GHCI > about all in-scope exception info types via `:info ExceptionInfo`. > > Backwards Compatibility > ======================= > > GHC 7.10 adds support for bidirectional pattern synonyms. This means > that this change could be made without breaking code: > > pattern SomeException x <- SomeExceptionWithInfo x _ where > SomeException x = SomeExceptionWithInfo x [] > > Note that consumers of this do not need to enable `-XPatternSynonyms`. > > Applications > ============ > > Callstacks > ---------- > > As mentioned at the beginning, this can be used to add callstacks to > exceptions: > > newtype ExceptionCallStack = > ExceptionCallStack { unExceptionCallStack :: [String] } > deriving Typeable > > instance ExceptionInfo ExceptionCallStack where > displayExceptionInfo = unlines . unExceptionCallStack > > throwIOWithStack :: Exception e => e -> IO a > throwIOWithStack e = do > stack <- currentCallStack > if null stack > then throwIO e > else throwIO (addExceptionInfo (ExceptionCallStack stack) > e) > > I see little downside for making something like this the default > implementation `throwIO`. Each rethrowing of the `SomeException` > would add an additional stacktrace to its annotation, much like the > output of `+RTS -xc`. Unlike this debug output, though, the > stacktraces would be associated with the exception, rather than just > listing locations that exceptions were thrown. This makes it > tractable to debug exceptions that occur in concurrent programs, or in > programs which frequently throw exceptions during normal functioning. > > Throwing Exceptions in Handlers > ------------------------------- > > Example: > > main = > throwIO InformativeErrorMessage `finally` > throwIO ObscureCleanupIssue > > While `InformativeErrorMessage` got thrown, the user doesn't see it, > since `ObscureCleanupIssue` is thrown instead. This causes a few > issues: > > 1. If the exception is handled by the default handler and yielded to > the user, then the more informative error is lost. > > 2. Callers who expect to catch the "Informative error message" won't > run their handlers for this exception type. > > Problem 1 can now easily be resolved by adding some info to the > exception: > > data ExceptionCause = ExceptionCause > { unExceptionCause :: SomeException } > deriving Typeable > > instance ExceptionInfo ExceptionCause where > displayExceptionInfo fe = > "thrown while handling " ++ > displayException (unExceptionCause fe) > > catch :: Exception e => IO a -> (e -> IO a) -> IO a > catch f g = f `oldCatch` handler > where > handler ex = g ex `oldCatch` \(ex' :: SomeException) -> > throwIO (addExceptionInfo info ex') > where > info = ExceptionCause (toException ex) > > This implementation of `catch` is written in a backwards-compatible > way, such that the exception thrown during finalization is still the > one that gets rethrown. The "original" exception is recorded in the > added info. This is the same approach used by Python 3's > `__context__` attribute[3]. This was brought to my attention in a > post by Mike Meyer[4], in a thread about having bracket not suppress > the original exception[5]. > > This doesn't directly resolve issue #2, due to this backwards > compatibility. With the earlier example, a `catch` handler for > `InformativeErrorMessage` won't be invoked, because it isn't the > exception being rethrown. This can be resolved by having a variant of > catch which instead throws the original exception. This might be a > good default for finalization handlers like `bracket` and `finally`. > > Asynchronous Exceptions > ----------------------- > > Currently, the only reliable way to catch exceptions, ignoring async > exceptions, is to fork a new thread. This is the approach used by > enclosed-exceptions[6] package. I think it's quite ugly that we need > to go to such lengths due to the lack of one bit of information about > the exception! This would resolve ghc trac #5902[7]. > > base-4.7 added the `SomeAsyncException` type, but this doesn't enforce > anything. Any exception can be thrown as a sync or async exception. > Instead, we ought to have a reliable way to know if an exception is > synchronous or asynchronous. Here's what this would look like: > > data IsAsync = IsAsync > deriving (Typeable, Show) > > instance ExceptionInfo IsAsync where > displayExceptionInfo IsAsync = "thrown asynchronously" > > throwTo :: Exception e => ThreadId -> e -> IO () > throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync > > The details of this get a bit tricky: What happens if `throwIO` is > used to rethrow a `SomeException` which has this `IsAsync` flag set? > I'm going to leave out my thoughts on this for now as the interactions > between unsafePerformIO and the concept of "rethrowing" async > exceptions. Such details are explained in a post by Edsko de Vries[8] > and ghc trac #2558[9]. > > Issue: fromException loses info > =============================== > > I can think of one main non-ideal aspect of this proposal: > > Currently, the `toException` and `fromException` methods usually
On Tue, Apr 21, 2015 at 1:37 PM, Michael Sloan
wrote: traces, the trace info. the form > a prism. In other words, when `fromException` yields a `Just`, you > should get the same `SomeException` when using `toException` on that > value. > > For example, > > fail "testing 1 2 3" `catch` \(ex :: SomeException) -> throwIO ex > > is equivalent to > > fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex > > However, with exception info added to just `SomeException`, and no > changes to existing `Exception` instances, this > doesn't hold. Exceptions caught as a specific exception type get > rethrown with less information. > > One resolution to this is be to add `[SomeExceptionInfo]` as a field > to existing `Exception` instances. This would require the use of > non-default implementations of the `toException` and `fromException` > instances. > > Another approach is to have variants of `catch` and `throw` which also > pass around the `[SomeExceptionInfo]`. > > [1] > https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... > [2] > https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations > [3] https://www.python.org/dev/peps/pep-3134/ > [4] > https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html > [5] > https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html > [6] https://hackage.haskell.org/package/enclosed-exceptions > [7] https://ghc.haskell.org/trac/ghc/ticket/5902 > [8] http://www.edsko.net/2013/06/11/throwTo/ > [9] https://ghc.haskell.org/trac/ghc/ticket/2558 > > _______________________________________________ > Libraries mailing list > Libraries@haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On a more important note: assuming ghc 7.12 has support for informative
stack traces via dwarf by default, wouldn't that eliminate the need for
this proposal? Namely : there perhaps should be some reasonable way to talk
about concatting stack traces perhaps?
Phrased differently: how is the info that should perhaps be in informative
stack traces not subsuming the info of this proposal?
On Tuesday, April 21, 2015, Michael Sloan
Ah, but it looks like Niklas does have a patch which adds implicit locations to such functions: https://phabricator.haskell.org/D861
However, there are some issues with changing the API of these functions: https://phabricator.haskell.org/D861#23250
(as mentioned in the "Backporting srcLoc to the GHC 7.10 branch" thread)
On Tue, Apr 21, 2015 at 2:04 PM, Michael Sloan
javascript:_e(%7B%7D,'cvml','mgsloan@gmail.com');> wrote: Hmm, that patch doesn't appear to add stack traces to 'Prelude.error', which is what Carter wants here. Also, I think it would be done with profiling callstacks rather than implicit callstacks. But it's certainly also useful to have functions which do the same with implicit callstacks!
On Tue, Apr 21, 2015 at 1:55 PM, Evan Laforge
javascript:_e(%7B%7D,'cvml','qdunkan@gmail.com');> wrote: Maybe I'm missing something, but isn't this already implemented?
https://phabricator.haskell.org/D578
On Thu, Apr 16, 2015 at 8:08 PM, Carter Schonwald
javascript:_e(%7B%7D,'cvml','carter.schonwald@gmail.com');> wrote: if you can patch prelude error to include stack traces, i will owe
you a
=1 beer each at the next two icfps. Thats all i want for christmas. :)
Sounds good! No promises, but I'll be giving this a try soon. Looking forward to ICFP beers either way :D
i can't speak for how a different patch might work out, because thats not what I'd tried at the time. If you have a go, please share the results! -Carter
On Wed, Apr 15, 2015 at 12:22 AM, Michael Sloan
javascript:_e(%7B%7D,'cvml','mgsloan@gmail.com');> wrote: Hi Carter!
Interesting! This thread, right?
https://mail.haskell.org/pipermail/libraries/2014-December/024429.html
I haven't tried this as a patch to base, but I'm certain that the
core of
the proposal has no extra dependencies. Note that the proposal isn't about stack traces in particular - that's just one application of being able to throw exceptions with extra information.
Even if `throwTo` isn't modified to throw exceptions with stack
this functionality could be provided outside of `Control.Exception` (though, that does seem like the right place to put it). I'm surprised that
circularity was so problematic, though. Why isn't it sufficient to have an hs-boot file for `GHC.Stack`, which exports `currentCallStack`?
-Michael
On Tue, Apr 14, 2015 at 7:55 PM, Carter Schonwald
javascript:_e(%7B%7D,'cvml','carter.schonwald@gmail.com');> wrote: > > Hey Michael, > I actually proposed something along these lines that got OK'd by > libraries early this past fall, the main challenge we hit was actually doing > the enginering to add the stack traces to exceptions! theres some nasty > module cycles in base that happen when you try to weave things around so > that the standard error "message here" call includes some stack > Have you tried to do that simple starter patch to base? > > Chris Allen and I spent like 2 days trying to get it to work and just > gave up because of the cycles. We (and others) would probably love some > headway on that front. > > Theres also some in progress work to use the dwarf debugging info data > in >7.10 to provide useful stack traces in the default builds for GHC afaik, > 'cause the stack trace functionality you're pointing at currenlty only work > on profiled builds > > cheers > -Carter > > On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan
javascript:_e(%7B%7D,'cvml','mgsloan@gmail.com');> > wrote: >> >> Control.Exception currently lacks a good way to supply extra >> information along with exceptions. For example, exceptions could be >> thrown along with their callstack[1] or implicit stack[2], but we have >> no generic way to include this information with exceptions. >> >> Proposed Solution >> ================= >> >> The proposed solution is to add a list of `SomeExceptionInfo` to >> `SomeException` datatype. This list stores additional information >> about the exception. These `ExceptionInfo` instances use a mechanism >> which is pretty much identical to the dynamic way the `Exception` type >> works: >> >> data SomeException = forall e . Exception e => >> SomeExceptionWithInfo e [SomeExceptionInfo] >> >> data SomeExceptionInfo = forall a . ExceptionInfo a => >> SomeExceptionInfo a >> >> class Typeable a => ExceptionInfo a where >> displayExceptionInfo :: a -> String >> >> addExceptionInfo >> :: (ExceptionInfo a, Exception e) >> => a -> e -> SomeException >> addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = >> SomeExceptionWithInfo e (SomeExceptionInfo x : xs) >> >> `ExceptionInfo` lacks the to / from functions that `Exception` has, >> because I don't see much point in supporting a hierarchy for exception >> info. The `Typeable` superclass constraint supplies the necessary >> casting. >> >> `SomeExceptionInfo` could validly instead just use the constraint >> `(Typeable a, Show a)`. However, I believe it's good to have a new >> class for this so that: >> >> * The user can specify a custom `displayExceptionInfo` >> implementation, for when this extra info is presented to the user. >> This function would be invoked by the `show` implementation for >> `SomeException`. >> >> * Types need to opt-in to be usable with `SomeExceptionInfo`. >> Similarly to exceptions, I imagine that a type with a >> `ExceptionInfo` instance won't be used for anything but acting as >> such an annotation. Having a class for this allows you to ask GHCI >> about all in-scope exception info types via `:info ExceptionInfo`. >> >> Backwards Compatibility >> ======================= >> >> GHC 7.10 adds support for bidirectional pattern synonyms. This means >> that this change could be made without breaking code: >> >> pattern SomeException x <- SomeExceptionWithInfo x _ where >> SomeException x = SomeExceptionWithInfo x [] >> >> Note that consumers of this do not need to enable `-XPatternSynonyms`. >> >> Applications >> ============ >> >> Callstacks >> ---------- >> >> As mentioned at the beginning, this can be used to add callstacks to >> exceptions: >> >> newtype ExceptionCallStack = >> ExceptionCallStack { unExceptionCallStack :: [String] } >> deriving Typeable >> >> instance ExceptionInfo ExceptionCallStack where >> displayExceptionInfo = unlines . unExceptionCallStack >> >> throwIOWithStack :: Exception e => e -> IO a >> throwIOWithStack e = do >> stack <- currentCallStack >> if null stack >> then throwIO e >> else throwIO (addExceptionInfo (ExceptionCallStack stack) >> e) >> >> I see little downside for making something like this the default >> implementation `throwIO`. Each rethrowing of the `SomeException` >> would add an additional stacktrace to its annotation, much like the >> output of `+RTS -xc`. Unlike this debug output, though, the >> stacktraces would be associated with the exception, rather than just >> listing locations that exceptions were thrown. This makes it >> tractable to debug exceptions that occur in concurrent programs, or in >> programs which frequently throw exceptions during normal functioning. >> >> Throwing Exceptions in Handlers >> ------------------------------- >> >> Example: >> >> main = >> throwIO InformativeErrorMessage `finally` >> throwIO ObscureCleanupIssue >> >> While `InformativeErrorMessage` got thrown, the user doesn't see it, >> since `ObscureCleanupIssue` is thrown instead. This causes a few >> issues: >> >> 1. If the exception is handled by the default handler and yielded to >> the user, then the more informative error is lost. >> >> 2. Callers who expect to catch the "Informative error message" won't >> run their handlers for this exception type. >> >> Problem 1 can now easily be resolved by adding some info to the >> exception: >> >> data ExceptionCause = ExceptionCause >> { unExceptionCause :: SomeException } >> deriving Typeable >> >> instance ExceptionInfo ExceptionCause where >> displayExceptionInfo fe = >> "thrown while handling " ++ >> displayException (unExceptionCause fe) >> >> catch :: Exception e => IO a -> (e -> IO a) -> IO a >> catch f g = f `oldCatch` handler >> where >> handler ex = g ex `oldCatch` \(ex' :: SomeException) -> >> throwIO (addExceptionInfo info ex') >> where >> info = ExceptionCause (toException ex) >> >> This implementation of `catch` is written in a backwards-compatible >> way, such that the exception thrown during finalization is still
>> one that gets rethrown. The "original" exception is recorded in
>> added info. This is the same approach used by Python 3's >> `__context__` attribute[3]. This was brought to my attention in a >> post by Mike Meyer[4], in a thread about having bracket not suppress >> the original exception[5]. >> >> This doesn't directly resolve issue #2, due to this backwards >> compatibility. With the earlier example, a `catch` handler for >> `InformativeErrorMessage` won't be invoked, because it isn't the >> exception being rethrown. This can be resolved by having a variant of >> catch which instead throws the original exception. This might be a >> good default for finalization handlers like `bracket` and `finally`. >> >> Asynchronous Exceptions >> ----------------------- >> >> Currently, the only reliable way to catch exceptions, ignoring async >> exceptions, is to fork a new thread. This is the approach used by
>> enclosed-exceptions[6] package. I think it's quite ugly that we need >> to go to such lengths due to the lack of one bit of information about >> the exception! This would resolve ghc trac #5902[7]. >> >> base-4.7 added the `SomeAsyncException` type, but this doesn't enforce >> anything. Any exception can be thrown as a sync or async exception. >> Instead, we ought to have a reliable way to know if an exception is >> synchronous or asynchronous. Here's what this would look like: >> >> data IsAsync = IsAsync >> deriving (Typeable, Show) >> >> instance ExceptionInfo IsAsync where >> displayExceptionInfo IsAsync = "thrown asynchronously" >> >> throwTo :: Exception e => ThreadId -> e -> IO () >> throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync >> >> The details of this get a bit tricky: What happens if `throwIO` is >> used to rethrow a `SomeException` which has this `IsAsync` flag set? >> I'm going to leave out my thoughts on this for now as the interactions >> between unsafePerformIO and the concept of "rethrowing" async >> exceptions. Such details are explained in a post by Edsko de Vries[8] >> and ghc trac #2558[9]. >> >> Issue: fromException loses info >> =============================== >> >> I can think of one main non-ideal aspect of this proposal: >> >> Currently, the `toException` and `fromException` methods usually
>> a prism. In other words, when `fromException` yields a `Just`, you >> should get the same `SomeException` when using `toException` on
On Tue, Apr 21, 2015 at 1:37 PM, Michael Sloan
javascript:_e(%7B%7D,'cvml','mgsloan@gmail.com');> wrote: traces, the trace info. the the the the form that >> value. >> >> For example, >> >> fail "testing 1 2 3" `catch` \(ex :: SomeException) -> throwIO ex >> >> is equivalent to >> >> fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex >> >> However, with exception info added to just `SomeException`, and no >> changes to existing `Exception` instances, this >> doesn't hold. Exceptions caught as a specific exception type get >> rethrown with less information. >> >> One resolution to this is be to add `[SomeExceptionInfo]` as a field >> to existing `Exception` instances. This would require the use of >> non-default implementations of the `toException` and `fromException` >> instances. >> >> Another approach is to have variants of `catch` and `throw` which also >> pass around the `[SomeExceptionInfo]`. >> >> [1] >> https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... >> [2] >> https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations >> [3] https://www.python.org/dev/peps/pep-3134/ >> [4] >> https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html >> [5] >> https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html >> [6] https://hackage.haskell.org/package/enclosed-exceptions >> [7] https://ghc.haskell.org/trac/ghc/ticket/5902 >> [8] http://www.edsko.net/2013/06/11/throwTo/ >> [9] https://ghc.haskell.org/trac/ghc/ticket/2558 >> >> _______________________________________________ >> Libraries mailing list >> Libraries@haskell.org javascript:_e(%7B%7D,'cvml','Libraries@haskell.org'); >> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >
_______________________________________________ Libraries mailing list Libraries@haskell.org javascript:_e(%7B%7D,'cvml','Libraries@haskell.org'); http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

No, this proposal is not specifically about stack traces, that is just one of the usecases. Instead, this is about a general mechanism for including extra information with exceptions. The core of this proposal is still relevant even if the behavior of error / throw / throwTo / etc remain unchanged. I'm not familiar with how the new dwarf stuff will interact with throwing / displaying exceptions. It seems like this would require having the debugger break at the throw site, and exceptions would still lack stack traces. Having informative stack traces is quite orthogonal to having a good place to store them. Note that in my original proposal text I mentioned that this is agnostic of the particular source of the stack trace. In particular, this could be used with a profiling stack trace, implicit callstack, or, indeed, these traces via dwarf. -Michael On Tue, Apr 21, 2015 at 3:06 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
On a more important note: assuming ghc 7.12 has support for informative stack traces via dwarf by default, wouldn't that eliminate the need for this proposal? Namely : there perhaps should be some reasonable way to talk about concatting stack traces perhaps?
Phrased differently: how is the info that should perhaps be in informative stack traces not subsuming the info of this proposal?
On Tuesday, April 21, 2015, Michael Sloan
wrote: Ah, but it looks like Niklas does have a patch which adds implicit locations to such functions: https://phabricator.haskell.org/D861
However, there are some issues with changing the API of these functions: https://phabricator.haskell.org/D861#23250
(as mentioned in the "Backporting srcLoc to the GHC 7.10 branch" thread)
On Tue, Apr 21, 2015 at 2:04 PM, Michael Sloan
wrote: Hmm, that patch doesn't appear to add stack traces to 'Prelude.error', which is what Carter wants here. Also, I think it would be done with profiling callstacks rather than implicit callstacks. But it's certainly also useful to have functions which do the same with implicit callstacks!
On Tue, Apr 21, 2015 at 1:55 PM, Evan Laforge
wrote: Maybe I'm missing something, but isn't this already implemented?
https://phabricator.haskell.org/D578
On Thu, Apr 16, 2015 at 8:08 PM, Carter Schonwald
wrote: if you can patch prelude error to include stack traces, i will owe
you a
>=1 beer each at the next two icfps. Thats all i want for christmas. :)
Sounds good! No promises, but I'll be giving this a try soon. Looking forward to ICFP beers either way :D
i can't speak for how a different patch might work out, because
what I'd tried at the time. If you have a go, please share the results! -Carter
On Wed, Apr 15, 2015 at 12:22 AM, Michael Sloan
wrote: > > Hi Carter! > > Interesting! This thread, right? > https://mail.haskell.org/pipermail/libraries/2014-December/024429.html > > I haven't tried this as a patch to base, but I'm certain that the core of > the proposal has no extra dependencies. Note that the proposal isn't about > stack traces in particular - that's just one application of being able to > throw exceptions with extra information. > > Even if `throwTo` isn't modified to throw exceptions with stack > this functionality could be provided outside of `Control.Exception` (though, > that does seem like the right place to put it). I'm surprised that
> circularity was so problematic, though. Why isn't it sufficient to have an > hs-boot file for `GHC.Stack`, which exports `currentCallStack`? > > -Michael > > On Tue, Apr 14, 2015 at 7:55 PM, Carter Schonwald >
wrote: >> >> Hey Michael, >> I actually proposed something along these lines that got OK'd by >> libraries early this past fall, the main challenge we hit was actually doing >> the enginering to add the stack traces to exceptions! theres some nasty >> module cycles in base that happen when you try to weave things around so >> that the standard error "message here" call includes some stack >> Have you tried to do that simple starter patch to base? >> >> Chris Allen and I spent like 2 days trying to get it to work and just >> gave up because of the cycles. We (and others) would probably love some >> headway on that front. >> >> Theres also some in progress work to use the dwarf debugging info data >> in >7.10 to provide useful stack traces in the default builds for GHC afaik, >> 'cause the stack trace functionality you're pointing at currenlty only work >> on profiled builds >> >> cheers >> -Carter >> >> On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan
>> wrote: >>> >>> Control.Exception currently lacks a good way to supply extra >>> information along with exceptions. For example, exceptions could be >>> thrown along with their callstack[1] or implicit stack[2], but we have >>> no generic way to include this information with exceptions. >>> >>> Proposed Solution >>> ================= >>> >>> The proposed solution is to add a list of `SomeExceptionInfo` to >>> `SomeException` datatype. This list stores additional information >>> about the exception. These `ExceptionInfo` instances use a mechanism >>> which is pretty much identical to the dynamic way the `Exception` type >>> works: >>> >>> data SomeException = forall e . Exception e => >>> SomeExceptionWithInfo e [SomeExceptionInfo] >>> >>> data SomeExceptionInfo = forall a . ExceptionInfo a => >>> SomeExceptionInfo a >>> >>> class Typeable a => ExceptionInfo a where >>> displayExceptionInfo :: a -> String >>> >>> addExceptionInfo >>> :: (ExceptionInfo a, Exception e) >>> => a -> e -> SomeException >>> addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = >>> SomeExceptionWithInfo e (SomeExceptionInfo x : xs) >>> >>> `ExceptionInfo` lacks the to / from functions that `Exception` has, >>> because I don't see much point in supporting a hierarchy for exception >>> info. The `Typeable` superclass constraint supplies the necessary >>> casting. >>> >>> `SomeExceptionInfo` could validly instead just use the constraint >>> `(Typeable a, Show a)`. However, I believe it's good to have a new >>> class for this so that: >>> >>> * The user can specify a custom `displayExceptionInfo` >>> implementation, for when this extra info is presented to the user. >>> This function would be invoked by the `show` implementation for >>> `SomeException`. >>> >>> * Types need to opt-in to be usable with `SomeExceptionInfo`. >>> Similarly to exceptions, I imagine that a type with a >>> `ExceptionInfo` instance won't be used for anything but acting as >>> such an annotation. Having a class for this allows you to ask GHCI >>> about all in-scope exception info types via `:info ExceptionInfo`. >>> >>> Backwards Compatibility >>> ======================= >>> >>> GHC 7.10 adds support for bidirectional pattern synonyms. This means >>> that this change could be made without breaking code: >>> >>> pattern SomeException x <- SomeExceptionWithInfo x _ where >>> SomeException x = SomeExceptionWithInfo x [] >>> >>> Note that consumers of this do not need to enable `-XPatternSynonyms`. >>> >>> Applications >>> ============ >>> >>> Callstacks >>> ---------- >>> >>> As mentioned at the beginning, this can be used to add callstacks to >>> exceptions: >>> >>> newtype ExceptionCallStack = >>> ExceptionCallStack { unExceptionCallStack :: [String] } >>> deriving Typeable >>> >>> instance ExceptionInfo ExceptionCallStack where >>> displayExceptionInfo = unlines . unExceptionCallStack >>> >>> throwIOWithStack :: Exception e => e -> IO a >>> throwIOWithStack e = do >>> stack <- currentCallStack >>> if null stack >>> then throwIO e >>> else throwIO (addExceptionInfo (ExceptionCallStack stack) >>> e) >>> >>> I see little downside for making something like this the default >>> implementation `throwIO`. Each rethrowing of the `SomeException` >>> would add an additional stacktrace to its annotation, much like
>>> output of `+RTS -xc`. Unlike this debug output, though, the >>> stacktraces would be associated with the exception, rather than just >>> listing locations that exceptions were thrown. This makes it >>> tractable to debug exceptions that occur in concurrent programs, or in >>> programs which frequently throw exceptions during normal functioning. >>> >>> Throwing Exceptions in Handlers >>> ------------------------------- >>> >>> Example: >>> >>> main = >>> throwIO InformativeErrorMessage `finally` >>> throwIO ObscureCleanupIssue >>> >>> While `InformativeErrorMessage` got thrown, the user doesn't see it, >>> since `ObscureCleanupIssue` is thrown instead. This causes a few >>> issues: >>> >>> 1. If the exception is handled by the default handler and yielded to >>> the user, then the more informative error is lost. >>> >>> 2. Callers who expect to catch the "Informative error message" won't >>> run their handlers for this exception type. >>> >>> Problem 1 can now easily be resolved by adding some info to the >>> exception: >>> >>> data ExceptionCause = ExceptionCause >>> { unExceptionCause :: SomeException } >>> deriving Typeable >>> >>> instance ExceptionInfo ExceptionCause where >>> displayExceptionInfo fe = >>> "thrown while handling " ++ >>> displayException (unExceptionCause fe) >>> >>> catch :: Exception e => IO a -> (e -> IO a) -> IO a >>> catch f g = f `oldCatch` handler >>> where >>> handler ex = g ex `oldCatch` \(ex' :: SomeException) -> >>> throwIO (addExceptionInfo info ex') >>> where >>> info = ExceptionCause (toException ex) >>> >>> This implementation of `catch` is written in a backwards-compatible >>> way, such that the exception thrown during finalization is still
>>> one that gets rethrown. The "original" exception is recorded in
>>> added info. This is the same approach used by Python 3's >>> `__context__` attribute[3]. This was brought to my attention in a >>> post by Mike Meyer[4], in a thread about having bracket not suppress >>> the original exception[5]. >>> >>> This doesn't directly resolve issue #2, due to this backwards >>> compatibility. With the earlier example, a `catch` handler for >>> `InformativeErrorMessage` won't be invoked, because it isn't the >>> exception being rethrown. This can be resolved by having a variant of >>> catch which instead throws the original exception. This might be a >>> good default for finalization handlers like `bracket` and `finally`. >>> >>> Asynchronous Exceptions >>> ----------------------- >>> >>> Currently, the only reliable way to catch exceptions, ignoring async >>> exceptions, is to fork a new thread. This is the approach used by the >>> enclosed-exceptions[6] package. I think it's quite ugly that we need >>> to go to such lengths due to the lack of one bit of information about >>> the exception! This would resolve ghc trac #5902[7]. >>> >>> base-4.7 added the `SomeAsyncException` type, but this doesn't enforce >>> anything. Any exception can be thrown as a sync or async exception. >>> Instead, we ought to have a reliable way to know if an exception is >>> synchronous or asynchronous. Here's what this would look like: >>> >>> data IsAsync = IsAsync >>> deriving (Typeable, Show) >>> >>> instance ExceptionInfo IsAsync where >>> displayExceptionInfo IsAsync = "thrown asynchronously" >>> >>> throwTo :: Exception e => ThreadId -> e -> IO () >>> throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync >>> >>> The details of this get a bit tricky: What happens if `throwIO` is >>> used to rethrow a `SomeException` which has this `IsAsync` flag set? >>> I'm going to leave out my thoughts on this for now as the interactions >>> between unsafePerformIO and the concept of "rethrowing" async >>> exceptions. Such details are explained in a post by Edsko de Vries[8] >>> and ghc trac #2558[9]. >>> >>> Issue: fromException loses info >>> =============================== >>> >>> I can think of one main non-ideal aspect of this proposal: >>> >>> Currently, the `toException` and `fromException` methods usually
>>> a prism. In other words, when `fromException` yields a `Just`, you >>> should get the same `SomeException` when using `toException` on
>>> value. >>> >>> For example, >>> >>> fail "testing 1 2 3" `catch` \(ex :: SomeException) ->
On Tue, Apr 21, 2015 at 1:37 PM, Michael Sloan
wrote: thats not traces, the trace info. the the the the form that throwIO ex >>> >>> is equivalent to >>> >>> fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex >>> >>> However, with exception info added to just `SomeException`, and no >>> changes to existing `Exception` instances, this >>> doesn't hold. Exceptions caught as a specific exception type get >>> rethrown with less information. >>> >>> One resolution to this is be to add `[SomeExceptionInfo]` as a field >>> to existing `Exception` instances. This would require the use of >>> non-default implementations of the `toException` and `fromException` >>> instances. >>> >>> Another approach is to have variants of `catch` and `throw` which also >>> pass around the `[SomeExceptionInfo]`. >>> >>> [1] >>> https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... >>> [2] >>> https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations >>> [3] https://www.python.org/dev/peps/pep-3134/ >>> [4] >>> https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html >>> [5] >>> https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html >>> [6] https://hackage.haskell.org/package/enclosed-exceptions >>> [7] https://ghc.haskell.org/trac/ghc/ticket/5902 >>> [8] http://www.edsko.net/2013/06/11/throwTo/ >>> [9] https://ghc.haskell.org/trac/ghc/ticket/2558 >>> >>> _______________________________________________ >>> Libraries mailing list >>> Libraries@haskell.org >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>> >> >
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

So, I've had a number of issues with exceptions. This has been one of them.
I don't really like this proposal as it stands though as it seems to make
catch a specific exception with said extra info more difficult.
This is data Control.Exception can move around on its own though, right?
The problem really isn't passing it internal, we could just make a (Stack,
SomeException) tuple just fine, in theory I think (I'll admit I've not
actually reviewed the code, and this isn't meant as a complete proposal but
more a thought experiment). The problem is code handling the data and
working with old code while not losing any of the power of the current
system.
So we start with: catch :: Exception e => IO a -> (e -> IO a) -> IO a
Now this proposal allows: catch :: IO a -> (SomeException -> IO a) -> IO a
If we want access to the new information, but that's not really
satisfactory.
Real code regularly wants to (picking an arbitrary instance of Exception)
do: catch :: IO a -> (IOError -> IO a) -> IO a
only we still want new data.
Now one could do something like: catch :: IO a -> (Stack -> IOError -> IO a)
-> IO a
but that is not very upgradable and it breaks existing code.
But this is just a matter of requesting information, so one could do
something like: catch :: IO a -> (WithStack IOError -> IO a) -> IO a
where: data WithStack e = WithStack Stack e
Or maybe one just addes: catchWithContext :: Exception e => IO a ->
(Context -> e -> IO a) -> IO a
Or: catchWithContext :: Exception => IO a -> (Context e -> IO a) -> IO a
Now existing code continues to run and we can feed our exception handlers
the data they want, even when we want some specific exception instead of
just any exception.
Now that still leave a hole in what I want out of exceptions. We're still
short of programmatic interrogating them, or even telling what the
exception was if we didn't expect it!
Consider AssertionFailed
https://hackage.haskell.org/package/base-4.8.0.0/docs/src/GHC-IO-Exception.h....
Its show instance is "showsPrec _ (AssertionFailed err) = showString err",
so if we print out the SomeException, we get whatever string is in
AssertionFailed. Which is great if that string makes sense. But you see
that on your console and its a bit baffling if it doesn't. It could even be
a lie, I can make that say something that looks like its a different
exception. We can use the Typeable instance so the program can tell them
apart at least though. Which works as long as the exception is
single-constructor, or has a well-behaved show instance. What if we come
across a monstrosity like
http://hackage.haskell.org/package/http-conduit-2.1.5/docs/Network-HTTP-Cond...
and it doesn't have a nice show instance that says which on it is? If
Exception added a Data constraint we could actually pull apart these
exceptions and start to make proper sense of them reliably.
Once you have that there are quite a few useful things you can do with the
exceptions you didn't expect. Currently you could only do them by
enumerating every possible exception which of course doesn't work for the
unexpected.
On Tue, Apr 21, 2015 at 6:24 PM, Michael Sloan
No, this proposal is not specifically about stack traces, that is just one of the usecases. Instead, this is about a general mechanism for including extra information with exceptions. The core of this proposal is still relevant even if the behavior of error / throw / throwTo / etc remain unchanged.
I'm not familiar with how the new dwarf stuff will interact with throwing / displaying exceptions. It seems like this would require having the debugger break at the throw site, and exceptions would still lack stack traces. Having informative stack traces is quite orthogonal to having a good place to store them.
Note that in my original proposal text I mentioned that this is agnostic of the particular source of the stack trace. In particular, this could be used with a profiling stack trace, implicit callstack, or, indeed, these traces via dwarf.
-Michael
On Tue, Apr 21, 2015 at 3:06 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
On a more important note: assuming ghc 7.12 has support for informative stack traces via dwarf by default, wouldn't that eliminate the need for this proposal? Namely : there perhaps should be some reasonable way to talk about concatting stack traces perhaps?
Phrased differently: how is the info that should perhaps be in informative stack traces not subsuming the info of this proposal?
On Tuesday, April 21, 2015, Michael Sloan
wrote: Ah, but it looks like Niklas does have a patch which adds implicit locations to such functions: https://phabricator.haskell.org/D861
However, there are some issues with changing the API of these functions: https://phabricator.haskell.org/D861#23250
(as mentioned in the "Backporting srcLoc to the GHC 7.10 branch" thread)
On Tue, Apr 21, 2015 at 2:04 PM, Michael Sloan
wrote: Hmm, that patch doesn't appear to add stack traces to 'Prelude.error', which is what Carter wants here. Also, I think it would be done with profiling callstacks rather than implicit callstacks. But it's certainly also useful to have functions which do the same with implicit callstacks!
On Tue, Apr 21, 2015 at 1:55 PM, Evan Laforge
wrote: Maybe I'm missing something, but isn't this already implemented?
https://phabricator.haskell.org/D578
On Thu, Apr 16, 2015 at 8:08 PM, Carter Schonwald
wrote: > > if you can patch prelude error to include stack traces, i will owe you a > >=1 beer each at the next two icfps. Thats all i want for christmas. :) Sounds good! No promises, but I'll be giving this a try soon. Looking forward to ICFP beers either way :D
> i can't speak for how a different patch might work out, because
> what I'd tried at the time. If you have a go, please share the results! > -Carter > > On Wed, Apr 15, 2015 at 12:22 AM, Michael Sloan
wrote: >> >> Hi Carter! >> >> Interesting! This thread, right? >> https://mail.haskell.org/pipermail/libraries/2014-December/024429.html >> >> I haven't tried this as a patch to base, but I'm certain that the core of >> the proposal has no extra dependencies. Note that the proposal isn't about >> stack traces in particular - that's just one application of being able to >> throw exceptions with extra information. >> >> Even if `throwTo` isn't modified to throw exceptions with stack >> this functionality could be provided outside of `Control.Exception` (though, >> that does seem like the right place to put it). I'm surprised
>> circularity was so problematic, though. Why isn't it sufficient to have an >> hs-boot file for `GHC.Stack`, which exports `currentCallStack`? >> >> -Michael >> >> On Tue, Apr 14, 2015 at 7:55 PM, Carter Schonwald >>
wrote: >>> >>> Hey Michael, >>> I actually proposed something along these lines that got OK'd by >>> libraries early this past fall, the main challenge we hit was actually doing >>> the enginering to add the stack traces to exceptions! theres some nasty >>> module cycles in base that happen when you try to weave things around so >>> that the standard error "message here" call includes some stack >>> Have you tried to do that simple starter patch to base? >>> >>> Chris Allen and I spent like 2 days trying to get it to work and just >>> gave up because of the cycles. We (and others) would probably love some >>> headway on that front. >>> >>> Theres also some in progress work to use the dwarf debugging info data >>> in >7.10 to provide useful stack traces in the default builds for GHC afaik, >>> 'cause the stack trace functionality you're pointing at currenlty only work >>> on profiled builds >>> >>> cheers >>> -Carter >>> >>> On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan
>>> wrote: >>>> >>>> Control.Exception currently lacks a good way to supply extra >>>> information along with exceptions. For example, exceptions could be >>>> thrown along with their callstack[1] or implicit stack[2], but we have >>>> no generic way to include this information with exceptions. >>>> >>>> Proposed Solution >>>> ================= >>>> >>>> The proposed solution is to add a list of `SomeExceptionInfo` to
>>>> `SomeException` datatype. This list stores additional information >>>> about the exception. These `ExceptionInfo` instances use a mechanism >>>> which is pretty much identical to the dynamic way the `Exception` type >>>> works: >>>> >>>> data SomeException = forall e . Exception e => >>>> SomeExceptionWithInfo e [SomeExceptionInfo] >>>> >>>> data SomeExceptionInfo = forall a . ExceptionInfo a => >>>> SomeExceptionInfo a >>>> >>>> class Typeable a => ExceptionInfo a where >>>> displayExceptionInfo :: a -> String >>>> >>>> addExceptionInfo >>>> :: (ExceptionInfo a, Exception e) >>>> => a -> e -> SomeException >>>> addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = >>>> SomeExceptionWithInfo e (SomeExceptionInfo x : xs) >>>> >>>> `ExceptionInfo` lacks the to / from functions that `Exception` has, >>>> because I don't see much point in supporting a hierarchy for exception >>>> info. The `Typeable` superclass constraint supplies the necessary >>>> casting. >>>> >>>> `SomeExceptionInfo` could validly instead just use the constraint >>>> `(Typeable a, Show a)`. However, I believe it's good to have a new >>>> class for this so that: >>>> >>>> * The user can specify a custom `displayExceptionInfo` >>>> implementation, for when this extra info is presented to the user. >>>> This function would be invoked by the `show` implementation for >>>> `SomeException`. >>>> >>>> * Types need to opt-in to be usable with `SomeExceptionInfo`. >>>> Similarly to exceptions, I imagine that a type with a >>>> `ExceptionInfo` instance won't be used for anything but acting as >>>> such an annotation. Having a class for this allows you to ask GHCI >>>> about all in-scope exception info types via `:info ExceptionInfo`. >>>> >>>> Backwards Compatibility >>>> ======================= >>>> >>>> GHC 7.10 adds support for bidirectional pattern synonyms. This means >>>> that this change could be made without breaking code: >>>> >>>> pattern SomeException x <- SomeExceptionWithInfo x _ where >>>> SomeException x = SomeExceptionWithInfo x [] >>>> >>>> Note that consumers of this do not need to enable `-XPatternSynonyms`. >>>> >>>> Applications >>>> ============ >>>> >>>> Callstacks >>>> ---------- >>>> >>>> As mentioned at the beginning, this can be used to add callstacks to >>>> exceptions: >>>> >>>> newtype ExceptionCallStack = >>>> ExceptionCallStack { unExceptionCallStack :: [String] } >>>> deriving Typeable >>>> >>>> instance ExceptionInfo ExceptionCallStack where >>>> displayExceptionInfo = unlines . unExceptionCallStack >>>> >>>> throwIOWithStack :: Exception e => e -> IO a >>>> throwIOWithStack e = do >>>> stack <- currentCallStack >>>> if null stack >>>> then throwIO e >>>> else throwIO (addExceptionInfo (ExceptionCallStack stack) >>>> e) >>>> >>>> I see little downside for making something like this the default >>>> implementation `throwIO`. Each rethrowing of the `SomeException` >>>> would add an additional stacktrace to its annotation, much like
>>>> output of `+RTS -xc`. Unlike this debug output, though, the >>>> stacktraces would be associated with the exception, rather than just >>>> listing locations that exceptions were thrown. This makes it >>>> tractable to debug exceptions that occur in concurrent programs, or in >>>> programs which frequently throw exceptions during normal functioning. >>>> >>>> Throwing Exceptions in Handlers >>>> ------------------------------- >>>> >>>> Example: >>>> >>>> main = >>>> throwIO InformativeErrorMessage `finally` >>>> throwIO ObscureCleanupIssue >>>> >>>> While `InformativeErrorMessage` got thrown, the user doesn't see it, >>>> since `ObscureCleanupIssue` is thrown instead. This causes a few >>>> issues: >>>> >>>> 1. If the exception is handled by the default handler and yielded to >>>> the user, then the more informative error is lost. >>>> >>>> 2. Callers who expect to catch the "Informative error message" won't >>>> run their handlers for this exception type. >>>> >>>> Problem 1 can now easily be resolved by adding some info to the >>>> exception: >>>> >>>> data ExceptionCause = ExceptionCause >>>> { unExceptionCause :: SomeException } >>>> deriving Typeable >>>> >>>> instance ExceptionInfo ExceptionCause where >>>> displayExceptionInfo fe = >>>> "thrown while handling " ++ >>>> displayException (unExceptionCause fe) >>>> >>>> catch :: Exception e => IO a -> (e -> IO a) -> IO a >>>> catch f g = f `oldCatch` handler >>>> where >>>> handler ex = g ex `oldCatch` \(ex' :: SomeException) -> >>>> throwIO (addExceptionInfo info ex') >>>> where >>>> info = ExceptionCause (toException ex) >>>> >>>> This implementation of `catch` is written in a backwards-compatible >>>> way, such that the exception thrown during finalization is still
>>>> one that gets rethrown. The "original" exception is recorded in
>>>> added info. This is the same approach used by Python 3's >>>> `__context__` attribute[3]. This was brought to my attention in a >>>> post by Mike Meyer[4], in a thread about having bracket not suppress >>>> the original exception[5]. >>>> >>>> This doesn't directly resolve issue #2, due to this backwards >>>> compatibility. With the earlier example, a `catch` handler for >>>> `InformativeErrorMessage` won't be invoked, because it isn't the >>>> exception being rethrown. This can be resolved by having a variant of >>>> catch which instead throws the original exception. This might be a >>>> good default for finalization handlers like `bracket` and `finally`. >>>> >>>> Asynchronous Exceptions >>>> ----------------------- >>>> >>>> Currently, the only reliable way to catch exceptions, ignoring async >>>> exceptions, is to fork a new thread. This is the approach used by the >>>> enclosed-exceptions[6] package. I think it's quite ugly that we need >>>> to go to such lengths due to the lack of one bit of information about >>>> the exception! This would resolve ghc trac #5902[7]. >>>> >>>> base-4.7 added the `SomeAsyncException` type, but this doesn't enforce >>>> anything. Any exception can be thrown as a sync or async exception. >>>> Instead, we ought to have a reliable way to know if an exception is >>>> synchronous or asynchronous. Here's what this would look like: >>>> >>>> data IsAsync = IsAsync >>>> deriving (Typeable, Show) >>>> >>>> instance ExceptionInfo IsAsync where >>>> displayExceptionInfo IsAsync = "thrown asynchronously" >>>> >>>> throwTo :: Exception e => ThreadId -> e -> IO () >>>> throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync >>>> >>>> The details of this get a bit tricky: What happens if `throwIO` is >>>> used to rethrow a `SomeException` which has this `IsAsync` flag set? >>>> I'm going to leave out my thoughts on this for now as the interactions >>>> between unsafePerformIO and the concept of "rethrowing" async >>>> exceptions. Such details are explained in a post by Edsko de Vries[8] >>>> and ghc trac #2558[9]. >>>> >>>> Issue: fromException loses info >>>> =============================== >>>> >>>> I can think of one main non-ideal aspect of this proposal: >>>> >>>> Currently, the `toException` and `fromException` methods usually
>>>> a prism. In other words, when `fromException` yields a `Just`, you >>>> should get the same `SomeException` when using `toException` on
>>>> value. >>>> >>>> For example, >>>> >>>> fail "testing 1 2 3" `catch` \(ex :: SomeException) ->
On Tue, Apr 21, 2015 at 1:37 PM, Michael Sloan
wrote: thats not traces, that the trace info. the the the the form that throwIO ex >>>> >>>> is equivalent to >>>> >>>> fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex >>>> >>>> However, with exception info added to just `SomeException`, and no >>>> changes to existing `Exception` instances, this >>>> doesn't hold. Exceptions caught as a specific exception type get >>>> rethrown with less information. >>>> >>>> One resolution to this is be to add `[SomeExceptionInfo]` as a field >>>> to existing `Exception` instances. This would require the use of >>>> non-default implementations of the `toException` and `fromException` >>>> instances. >>>> >>>> Another approach is to have variants of `catch` and `throw` which also >>>> pass around the `[SomeExceptionInfo]`. >>>> >>>> [1] >>>> https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... >>>> [2] >>>> https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations >>>> [3] https://www.python.org/dev/peps/pep-3134/ >>>> [4] >>>> https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html >>>> [5] >>>> https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html >>>> [6] https://hackage.haskell.org/package/enclosed-exceptions >>>> [7] https://ghc.haskell.org/trac/ghc/ticket/5902 >>>> [8] http://www.edsko.net/2013/06/11/throwTo/ >>>> [9] https://ghc.haskell.org/trac/ghc/ticket/2558 >>>> >>>> _______________________________________________ >>>> Libraries mailing list >>>> Libraries@haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>> >>> >> >
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Tue, Apr 21, 2015 at 6:40 PM, davean
So, I've had a number of issues with exceptions. This has been one of them. I don't really like this proposal as it stands though as it seems to make catch a specific exception with said extra info more difficult.
This is data Control.Exception can move around on its own though, right? The problem really isn't passing it internal, we could just make a (Stack, SomeException) tuple just fine, in theory I think (I'll admit I've not actually reviewed the code, and this isn't meant as a complete proposal but more a thought experiment). The problem is code handling the data and working with old code while not losing any of the power of the current system.
So we start with: catch :: Exception e => IO a -> (e -> IO a) -> IO a
Now this proposal allows: catch :: IO a -> (SomeException -> IO a) -> IO a If we want access to the new information, but that's not really satisfactory.
Real code regularly wants to (picking an arbitrary instance of Exception) do: catch :: IO a -> (IOError -> IO a) -> IO a only we still want new data.
There is no way to always pass around the new data without breaking the Control.Exception API or having users add extra fields to their data types. This is a fundamental issue, and one that my proposal does not seek to address. Infact, I acknowledge it at the end - fromException now loses data. To me it is quite acceptable because: * This is a fundamental limitation of the existing Control.Exception API. This proposal allows us to gracefully update to a new API which does preserve the new info when catching / rethrowing. * These extra annotations are primarily for debugging purposes. It shouldn't be a correctness issue for them to be lost due to rethrowing something other than SomeException. Now one could do something like: catch :: IO a -> (Stack -> IOError -> IO a)
-> IO a but that is not very upgradable and it breaks existing code.
But this is just a matter of requesting information, so one could do something like: catch :: IO a -> (WithStack IOError -> IO a) -> IO a where: data WithStack e = WithStack Stack e Or maybe one just addes: catchWithContext :: Exception e => IO a -> (Context -> e -> IO a) -> IO a Or: catchWithContext :: Exception => IO a -> (Context e -> IO a) -> IO a
Now existing code continues to run and we can feed our exception handlers the data they want, even when we want some specific exception instead of just any exception.
This is a good idea, which is directly supported by this proposal. You would simply have the implementation of fromException populate the info in your With* datatype. Or, the definition I would prefer: data WithExceptionInfo e = WithExceptionInfo e [SomeExceptionInfo] deriving Typeable instance Exception e => Exception (WithExceptionInfo e) where fromException (SomeExceptionWithInfo e infos) = fmap (\e' -> WithExceptionInfo e' infos) (cast e) toException (WithExceptionInfo e infos) = SomeExceptionWithInfo e infos Does this help clarify my proposal? As far as I can tell there is no contradiction or difference between our proposals. I think you would end up with essentially the same thing I have (maybe with different names ;) ), if you tried implementing your ideas in the context of Control.Exception.

in the context of davean's proposal (which i'm still digesting), i'm gonna
go -1 on this one.
i'm really leery of commiting to any changes to our exception machinery
until the dwarf stack trace tooling and associated RTS/exception
interaction support is a bit more mature, because i think a lot of other
approaches / changes to ghc / base have been driven by the lack of cheap
stack traces. This proposal crosses that line, at least for me ;)
On Tue, Apr 21, 2015 at 6:24 PM, Michael Sloan
No, this proposal is not specifically about stack traces, that is just one of the usecases. Instead, this is about a general mechanism for including extra information with exceptions. The core of this proposal is still relevant even if the behavior of error / throw / throwTo / etc remain unchanged.
I'm not familiar with how the new dwarf stuff will interact with throwing / displaying exceptions. It seems like this would require having the debugger break at the throw site, and exceptions would still lack stack traces. Having informative stack traces is quite orthogonal to having a good place to store them.
Note that in my original proposal text I mentioned that this is agnostic of the particular source of the stack trace. In particular, this could be used with a profiling stack trace, implicit callstack, or, indeed, these traces via dwarf.
-Michael
On Tue, Apr 21, 2015 at 3:06 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
On a more important note: assuming ghc 7.12 has support for informative stack traces via dwarf by default, wouldn't that eliminate the need for this proposal? Namely : there perhaps should be some reasonable way to talk about concatting stack traces perhaps?
Phrased differently: how is the info that should perhaps be in informative stack traces not subsuming the info of this proposal?
On Tuesday, April 21, 2015, Michael Sloan
wrote: Ah, but it looks like Niklas does have a patch which adds implicit locations to such functions: https://phabricator.haskell.org/D861
However, there are some issues with changing the API of these functions: https://phabricator.haskell.org/D861#23250
(as mentioned in the "Backporting srcLoc to the GHC 7.10 branch" thread)
On Tue, Apr 21, 2015 at 2:04 PM, Michael Sloan
wrote: Hmm, that patch doesn't appear to add stack traces to 'Prelude.error', which is what Carter wants here. Also, I think it would be done with profiling callstacks rather than implicit callstacks. But it's certainly also useful to have functions which do the same with implicit callstacks!
On Tue, Apr 21, 2015 at 1:55 PM, Evan Laforge
wrote: Maybe I'm missing something, but isn't this already implemented?
https://phabricator.haskell.org/D578
On Thu, Apr 16, 2015 at 8:08 PM, Carter Schonwald
wrote: > > if you can patch prelude error to include stack traces, i will owe you a > >=1 beer each at the next two icfps. Thats all i want for christmas. :) Sounds good! No promises, but I'll be giving this a try soon. Looking forward to ICFP beers either way :D
> i can't speak for how a different patch might work out, because
> what I'd tried at the time. If you have a go, please share the results! > -Carter > > On Wed, Apr 15, 2015 at 12:22 AM, Michael Sloan
wrote: >> >> Hi Carter! >> >> Interesting! This thread, right? >> https://mail.haskell.org/pipermail/libraries/2014-December/024429.html >> >> I haven't tried this as a patch to base, but I'm certain that the core of >> the proposal has no extra dependencies. Note that the proposal isn't about >> stack traces in particular - that's just one application of being able to >> throw exceptions with extra information. >> >> Even if `throwTo` isn't modified to throw exceptions with stack >> this functionality could be provided outside of `Control.Exception` (though, >> that does seem like the right place to put it). I'm surprised
>> circularity was so problematic, though. Why isn't it sufficient to have an >> hs-boot file for `GHC.Stack`, which exports `currentCallStack`? >> >> -Michael >> >> On Tue, Apr 14, 2015 at 7:55 PM, Carter Schonwald >>
wrote: >>> >>> Hey Michael, >>> I actually proposed something along these lines that got OK'd by >>> libraries early this past fall, the main challenge we hit was actually doing >>> the enginering to add the stack traces to exceptions! theres some nasty >>> module cycles in base that happen when you try to weave things around so >>> that the standard error "message here" call includes some stack >>> Have you tried to do that simple starter patch to base? >>> >>> Chris Allen and I spent like 2 days trying to get it to work and just >>> gave up because of the cycles. We (and others) would probably love some >>> headway on that front. >>> >>> Theres also some in progress work to use the dwarf debugging info data >>> in >7.10 to provide useful stack traces in the default builds for GHC afaik, >>> 'cause the stack trace functionality you're pointing at currenlty only work >>> on profiled builds >>> >>> cheers >>> -Carter >>> >>> On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan
>>> wrote: >>>> >>>> Control.Exception currently lacks a good way to supply extra >>>> information along with exceptions. For example, exceptions could be >>>> thrown along with their callstack[1] or implicit stack[2], but we have >>>> no generic way to include this information with exceptions. >>>> >>>> Proposed Solution >>>> ================= >>>> >>>> The proposed solution is to add a list of `SomeExceptionInfo` to
>>>> `SomeException` datatype. This list stores additional information >>>> about the exception. These `ExceptionInfo` instances use a mechanism >>>> which is pretty much identical to the dynamic way the `Exception` type >>>> works: >>>> >>>> data SomeException = forall e . Exception e => >>>> SomeExceptionWithInfo e [SomeExceptionInfo] >>>> >>>> data SomeExceptionInfo = forall a . ExceptionInfo a => >>>> SomeExceptionInfo a >>>> >>>> class Typeable a => ExceptionInfo a where >>>> displayExceptionInfo :: a -> String >>>> >>>> addExceptionInfo >>>> :: (ExceptionInfo a, Exception e) >>>> => a -> e -> SomeException >>>> addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = >>>> SomeExceptionWithInfo e (SomeExceptionInfo x : xs) >>>> >>>> `ExceptionInfo` lacks the to / from functions that `Exception` has, >>>> because I don't see much point in supporting a hierarchy for exception >>>> info. The `Typeable` superclass constraint supplies the necessary >>>> casting. >>>> >>>> `SomeExceptionInfo` could validly instead just use the constraint >>>> `(Typeable a, Show a)`. However, I believe it's good to have a new >>>> class for this so that: >>>> >>>> * The user can specify a custom `displayExceptionInfo` >>>> implementation, for when this extra info is presented to the user. >>>> This function would be invoked by the `show` implementation for >>>> `SomeException`. >>>> >>>> * Types need to opt-in to be usable with `SomeExceptionInfo`. >>>> Similarly to exceptions, I imagine that a type with a >>>> `ExceptionInfo` instance won't be used for anything but acting as >>>> such an annotation. Having a class for this allows you to ask GHCI >>>> about all in-scope exception info types via `:info ExceptionInfo`. >>>> >>>> Backwards Compatibility >>>> ======================= >>>> >>>> GHC 7.10 adds support for bidirectional pattern synonyms. This means >>>> that this change could be made without breaking code: >>>> >>>> pattern SomeException x <- SomeExceptionWithInfo x _ where >>>> SomeException x = SomeExceptionWithInfo x [] >>>> >>>> Note that consumers of this do not need to enable `-XPatternSynonyms`. >>>> >>>> Applications >>>> ============ >>>> >>>> Callstacks >>>> ---------- >>>> >>>> As mentioned at the beginning, this can be used to add callstacks to >>>> exceptions: >>>> >>>> newtype ExceptionCallStack = >>>> ExceptionCallStack { unExceptionCallStack :: [String] } >>>> deriving Typeable >>>> >>>> instance ExceptionInfo ExceptionCallStack where >>>> displayExceptionInfo = unlines . unExceptionCallStack >>>> >>>> throwIOWithStack :: Exception e => e -> IO a >>>> throwIOWithStack e = do >>>> stack <- currentCallStack >>>> if null stack >>>> then throwIO e >>>> else throwIO (addExceptionInfo (ExceptionCallStack stack) >>>> e) >>>> >>>> I see little downside for making something like this the default >>>> implementation `throwIO`. Each rethrowing of the `SomeException` >>>> would add an additional stacktrace to its annotation, much like
>>>> output of `+RTS -xc`. Unlike this debug output, though, the >>>> stacktraces would be associated with the exception, rather than just >>>> listing locations that exceptions were thrown. This makes it >>>> tractable to debug exceptions that occur in concurrent programs, or in >>>> programs which frequently throw exceptions during normal functioning. >>>> >>>> Throwing Exceptions in Handlers >>>> ------------------------------- >>>> >>>> Example: >>>> >>>> main = >>>> throwIO InformativeErrorMessage `finally` >>>> throwIO ObscureCleanupIssue >>>> >>>> While `InformativeErrorMessage` got thrown, the user doesn't see it, >>>> since `ObscureCleanupIssue` is thrown instead. This causes a few >>>> issues: >>>> >>>> 1. If the exception is handled by the default handler and yielded to >>>> the user, then the more informative error is lost. >>>> >>>> 2. Callers who expect to catch the "Informative error message" won't >>>> run their handlers for this exception type. >>>> >>>> Problem 1 can now easily be resolved by adding some info to the >>>> exception: >>>> >>>> data ExceptionCause = ExceptionCause >>>> { unExceptionCause :: SomeException } >>>> deriving Typeable >>>> >>>> instance ExceptionInfo ExceptionCause where >>>> displayExceptionInfo fe = >>>> "thrown while handling " ++ >>>> displayException (unExceptionCause fe) >>>> >>>> catch :: Exception e => IO a -> (e -> IO a) -> IO a >>>> catch f g = f `oldCatch` handler >>>> where >>>> handler ex = g ex `oldCatch` \(ex' :: SomeException) -> >>>> throwIO (addExceptionInfo info ex') >>>> where >>>> info = ExceptionCause (toException ex) >>>> >>>> This implementation of `catch` is written in a backwards-compatible >>>> way, such that the exception thrown during finalization is still
>>>> one that gets rethrown. The "original" exception is recorded in
>>>> added info. This is the same approach used by Python 3's >>>> `__context__` attribute[3]. This was brought to my attention in a >>>> post by Mike Meyer[4], in a thread about having bracket not suppress >>>> the original exception[5]. >>>> >>>> This doesn't directly resolve issue #2, due to this backwards >>>> compatibility. With the earlier example, a `catch` handler for >>>> `InformativeErrorMessage` won't be invoked, because it isn't the >>>> exception being rethrown. This can be resolved by having a variant of >>>> catch which instead throws the original exception. This might be a >>>> good default for finalization handlers like `bracket` and `finally`. >>>> >>>> Asynchronous Exceptions >>>> ----------------------- >>>> >>>> Currently, the only reliable way to catch exceptions, ignoring async >>>> exceptions, is to fork a new thread. This is the approach used by the >>>> enclosed-exceptions[6] package. I think it's quite ugly that we need >>>> to go to such lengths due to the lack of one bit of information about >>>> the exception! This would resolve ghc trac #5902[7]. >>>> >>>> base-4.7 added the `SomeAsyncException` type, but this doesn't enforce >>>> anything. Any exception can be thrown as a sync or async exception. >>>> Instead, we ought to have a reliable way to know if an exception is >>>> synchronous or asynchronous. Here's what this would look like: >>>> >>>> data IsAsync = IsAsync >>>> deriving (Typeable, Show) >>>> >>>> instance ExceptionInfo IsAsync where >>>> displayExceptionInfo IsAsync = "thrown asynchronously" >>>> >>>> throwTo :: Exception e => ThreadId -> e -> IO () >>>> throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync >>>> >>>> The details of this get a bit tricky: What happens if `throwIO` is >>>> used to rethrow a `SomeException` which has this `IsAsync` flag set? >>>> I'm going to leave out my thoughts on this for now as the interactions >>>> between unsafePerformIO and the concept of "rethrowing" async >>>> exceptions. Such details are explained in a post by Edsko de Vries[8] >>>> and ghc trac #2558[9]. >>>> >>>> Issue: fromException loses info >>>> =============================== >>>> >>>> I can think of one main non-ideal aspect of this proposal: >>>> >>>> Currently, the `toException` and `fromException` methods usually
>>>> a prism. In other words, when `fromException` yields a `Just`, you >>>> should get the same `SomeException` when using `toException` on
>>>> value. >>>> >>>> For example, >>>> >>>> fail "testing 1 2 3" `catch` \(ex :: SomeException) ->
On Tue, Apr 21, 2015 at 1:37 PM, Michael Sloan
wrote: thats not traces, that the trace info. the the the the form that throwIO ex >>>> >>>> is equivalent to >>>> >>>> fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex >>>> >>>> However, with exception info added to just `SomeException`, and no >>>> changes to existing `Exception` instances, this >>>> doesn't hold. Exceptions caught as a specific exception type get >>>> rethrown with less information. >>>> >>>> One resolution to this is be to add `[SomeExceptionInfo]` as a field >>>> to existing `Exception` instances. This would require the use of >>>> non-default implementations of the `toException` and `fromException` >>>> instances. >>>> >>>> Another approach is to have variants of `catch` and `throw` which also >>>> pass around the `[SomeExceptionInfo]`. >>>> >>>> [1] >>>> https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... >>>> [2] >>>> https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations >>>> [3] https://www.python.org/dev/peps/pep-3134/ >>>> [4] >>>> https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html >>>> [5] >>>> https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html >>>> [6] https://hackage.haskell.org/package/enclosed-exceptions >>>> [7] https://ghc.haskell.org/trac/ghc/ticket/5902 >>>> [8] http://www.edsko.net/2013/06/11/throwTo/ >>>> [9] https://ghc.haskell.org/trac/ghc/ticket/2558 >>>> >>>> _______________________________________________ >>>> Libraries mailing list >>>> Libraries@haskell.org >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>> >>> >> >
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Davean's proposal is essentially the same as mine, restarted and specialized to callstacks. So, I'm not sure why it would make you vote against this. This does more than just stack traces, and is independent of the source of call stacks. What kind of mechanism are you envisioning that would make it redundant to include the callstack with the exception? I can imagine setting a thread local variable to the "last callstack of raise#". However, this does not allow us to accumulate callstacks when the exception is rethrown. Often you care more about the initial throw of the exception, rather than the most recent one. For example, with `+GHC -xc` output, when an exception is caught and rethrown, you'll see the callstacks of all the places it's thrown. This output is rather terrible for real world debugging, though, because it doesn't actually tell you what the exception is. When dealing with a concurrent system where some exceptions occur as part of normal operation, this becomes nightmareish. This proposal solves that problem. If you see even the rough possibility of another solution to this problem, please do tell. -Michael On Tue, Apr 21, 2015 at 7:26 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
in the context of davean's proposal (which i'm still digesting), i'm gonna go -1 on this one.
i'm really leery of commiting to any changes to our exception machinery until the dwarf stack trace tooling and associated RTS/exception interaction support is a bit more mature, because i think a lot of other approaches / changes to ghc / base have been driven by the lack of cheap stack traces. This proposal crosses that line, at least for me ;)
On Tue, Apr 21, 2015 at 6:24 PM, Michael Sloan
wrote: No, this proposal is not specifically about stack traces, that is just one of the usecases. Instead, this is about a general mechanism for including extra information with exceptions. The core of this proposal is still relevant even if the behavior of error / throw / throwTo / etc remain unchanged.
I'm not familiar with how the new dwarf stuff will interact with throwing / displaying exceptions. It seems like this would require having the debugger break at the throw site, and exceptions would still lack stack traces. Having informative stack traces is quite orthogonal to having a good place to store them.
Note that in my original proposal text I mentioned that this is agnostic of the particular source of the stack trace. In particular, this could be used with a profiling stack trace, implicit callstack, or, indeed, these traces via dwarf.
-Michael
On Tue, Apr 21, 2015 at 3:06 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
On a more important note: assuming ghc 7.12 has support for informative stack traces via dwarf by default, wouldn't that eliminate the need for this proposal? Namely : there perhaps should be some reasonable way to talk about concatting stack traces perhaps?
Phrased differently: how is the info that should perhaps be in informative stack traces not subsuming the info of this proposal?
On Tuesday, April 21, 2015, Michael Sloan
wrote: Ah, but it looks like Niklas does have a patch which adds implicit locations to such functions: https://phabricator.haskell.org/D861
However, there are some issues with changing the API of these functions: https://phabricator.haskell.org/D861#23250
(as mentioned in the "Backporting srcLoc to the GHC 7.10 branch" thread)
On Tue, Apr 21, 2015 at 2:04 PM, Michael Sloan
wrote: Hmm, that patch doesn't appear to add stack traces to 'Prelude.error', which is what Carter wants here. Also, I think it would be done with profiling callstacks rather than implicit callstacks. But it's certainly also useful to have functions which do the same with implicit callstacks!
On Tue, Apr 21, 2015 at 1:55 PM, Evan Laforge
wrote: Maybe I'm missing something, but isn't this already implemented?
https://phabricator.haskell.org/D578
On Tue, Apr 21, 2015 at 1:37 PM, Michael Sloan
wrote: > On Thu, Apr 16, 2015 at 8:08 PM, Carter Schonwald > wrote: >> >> if you can patch prelude error to include stack traces, i will owe you a >> >=1 beer each at the next two icfps. Thats all i want for christmas. :) > > > Sounds good! No promises, but I'll be giving this a try soon. Looking > forward to ICFP beers either way :D > >> i can't speak for how a different patch might work out, because thats not >> what I'd tried at the time. If you have a go, please share the results! >> -Carter >> >> On Wed, Apr 15, 2015 at 12:22 AM, Michael Sloan wrote: >>> >>> Hi Carter! >>> >>> Interesting! This thread, right? >>> https://mail.haskell.org/pipermail/libraries/2014-December/024429.html >>> >>> I haven't tried this as a patch to base, but I'm certain that the core of >>> the proposal has no extra dependencies. Note that the proposal isn't about >>> stack traces in particular - that's just one application of being able to >>> throw exceptions with extra information. >>> >>> Even if `throwTo` isn't modified to throw exceptions with stack traces, >>> this functionality could be provided outside of `Control.Exception` (though, >>> that does seem like the right place to put it). I'm surprised that the >>> circularity was so problematic, though. Why isn't it sufficient to have an >>> hs-boot file for `GHC.Stack`, which exports `currentCallStack`? >>> >>> -Michael >>> >>> On Tue, Apr 14, 2015 at 7:55 PM, Carter Schonwald >>> wrote: >>>> >>>> Hey Michael, >>>> I actually proposed something along these lines that got OK'd by >>>> libraries early this past fall, the main challenge we hit was actually doing >>>> the enginering to add the stack traces to exceptions! theres some nasty >>>> module cycles in base that happen when you try to weave things around so >>>> that the standard error "message here" call includes some stack trace info. >>>> Have you tried to do that simple starter patch to base? >>>> >>>> Chris Allen and I spent like 2 days trying to get it to work and just >>>> gave up because of the cycles. We (and others) would probably love some >>>> headway on that front. >>>> >>>> Theres also some in progress work to use the dwarf debugging info data >>>> in >7.10 to provide useful stack traces in the default builds for GHC afaik, >>>> 'cause the stack trace functionality you're pointing at currenlty only work >>>> on profiled builds >>>> >>>> cheers >>>> -Carter >>>> >>>> On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan < mgsloan@gmail.com> >>>> wrote: >>>>> >>>>> Control.Exception currently lacks a good way to supply extra >>>>> information along with exceptions. For example, exceptions could be >>>>> thrown along with their callstack[1] or implicit stack[2], but we have >>>>> no generic way to include this information with exceptions. >>>>> >>>>> Proposed Solution >>>>> ================= >>>>> >>>>> The proposed solution is to add a list of `SomeExceptionInfo` to the >>>>> `SomeException` datatype. This list stores additional information >>>>> about the exception. These `ExceptionInfo` instances use a mechanism >>>>> which is pretty much identical to the dynamic way the `Exception` type >>>>> works: >>>>> >>>>> data SomeException = forall e . Exception e => >>>>> SomeExceptionWithInfo e [SomeExceptionInfo] >>>>> >>>>> data SomeExceptionInfo = forall a . ExceptionInfo a => >>>>> SomeExceptionInfo a >>>>> >>>>> class Typeable a => ExceptionInfo a where >>>>> displayExceptionInfo :: a -> String >>>>> >>>>> addExceptionInfo >>>>> :: (ExceptionInfo a, Exception e) >>>>> => a -> e -> SomeException >>>>> addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = >>>>> SomeExceptionWithInfo e (SomeExceptionInfo x : xs) >>>>> >>>>> `ExceptionInfo` lacks the to / from functions that `Exception` has, >>>>> because I don't see much point in supporting a hierarchy for exception >>>>> info. The `Typeable` superclass constraint supplies the necessary >>>>> casting. >>>>> >>>>> `SomeExceptionInfo` could validly instead just use the constraint >>>>> `(Typeable a, Show a)`. However, I believe it's good to have a new >>>>> class for this so that: >>>>> >>>>> * The user can specify a custom `displayExceptionInfo` >>>>> implementation, for when this extra info is presented to the user. >>>>> This function would be invoked by the `show` implementation for >>>>> `SomeException`. >>>>> >>>>> * Types need to opt-in to be usable with `SomeExceptionInfo`. >>>>> Similarly to exceptions, I imagine that a type with a >>>>> `ExceptionInfo` instance won't be used for anything but acting as >>>>> such an annotation. Having a class for this allows you to ask GHCI >>>>> about all in-scope exception info types via `:info ExceptionInfo`. >>>>> >>>>> Backwards Compatibility >>>>> ======================= >>>>> >>>>> GHC 7.10 adds support for bidirectional pattern synonyms. This means >>>>> that this change could be made without breaking code: >>>>> >>>>> pattern SomeException x <- SomeExceptionWithInfo x _ where >>>>> SomeException x = SomeExceptionWithInfo x [] >>>>> >>>>> Note that consumers of this do not need to enable `-XPatternSynonyms`. >>>>> >>>>> Applications >>>>> ============ >>>>> >>>>> Callstacks >>>>> ---------- >>>>> >>>>> As mentioned at the beginning, this can be used to add callstacks to >>>>> exceptions: >>>>> >>>>> newtype ExceptionCallStack = >>>>> ExceptionCallStack { unExceptionCallStack :: [String] } >>>>> deriving Typeable >>>>> >>>>> instance ExceptionInfo ExceptionCallStack where >>>>> displayExceptionInfo = unlines . unExceptionCallStack >>>>> >>>>> throwIOWithStack :: Exception e => e -> IO a >>>>> throwIOWithStack e = do >>>>> stack <- currentCallStack >>>>> if null stack >>>>> then throwIO e >>>>> else throwIO (addExceptionInfo (ExceptionCallStack stack) >>>>> e) >>>>> >>>>> I see little downside for making something like this the default >>>>> implementation `throwIO`. Each rethrowing of the `SomeException` >>>>> would add an additional stacktrace to its annotation, much like the >>>>> output of `+RTS -xc`. Unlike this debug output, though, the >>>>> stacktraces would be associated with the exception, rather than just >>>>> listing locations that exceptions were thrown. This makes it >>>>> tractable to debug exceptions that occur in concurrent programs, or in >>>>> programs which frequently throw exceptions during normal functioning. >>>>> >>>>> Throwing Exceptions in Handlers >>>>> ------------------------------- >>>>> >>>>> Example: >>>>> >>>>> main = >>>>> throwIO InformativeErrorMessage `finally` >>>>> throwIO ObscureCleanupIssue >>>>> >>>>> While `InformativeErrorMessage` got thrown, the user doesn't see it, >>>>> since `ObscureCleanupIssue` is thrown instead. This causes a few >>>>> issues: >>>>> >>>>> 1. If the exception is handled by the default handler and yielded to >>>>> the user, then the more informative error is lost. >>>>> >>>>> 2. Callers who expect to catch the "Informative error message" won't >>>>> run their handlers for this exception type. >>>>> >>>>> Problem 1 can now easily be resolved by adding some info to the >>>>> exception: >>>>> >>>>> data ExceptionCause = ExceptionCause >>>>> { unExceptionCause :: SomeException } >>>>> deriving Typeable >>>>> >>>>> instance ExceptionInfo ExceptionCause where >>>>> displayExceptionInfo fe = >>>>> "thrown while handling " ++ >>>>> displayException (unExceptionCause fe) >>>>> >>>>> catch :: Exception e => IO a -> (e -> IO a) -> IO a >>>>> catch f g = f `oldCatch` handler >>>>> where >>>>> handler ex = g ex `oldCatch` \(ex' :: SomeException) -> >>>>> throwIO (addExceptionInfo info ex') >>>>> where >>>>> info = ExceptionCause (toException ex) >>>>> >>>>> This implementation of `catch` is written in a backwards-compatible >>>>> way, such that the exception thrown during finalization is still the >>>>> one that gets rethrown. The "original" exception is recorded in the >>>>> added info. This is the same approach used by Python 3's >>>>> `__context__` attribute[3]. This was brought to my attention in a >>>>> post by Mike Meyer[4], in a thread about having bracket not suppress >>>>> the original exception[5]. >>>>> >>>>> This doesn't directly resolve issue #2, due to this backwards >>>>> compatibility. With the earlier example, a `catch` handler for >>>>> `InformativeErrorMessage` won't be invoked, because it isn't the >>>>> exception being rethrown. This can be resolved by having a variant of >>>>> catch which instead throws the original exception. This might be a >>>>> good default for finalization handlers like `bracket` and `finally`. >>>>> >>>>> Asynchronous Exceptions >>>>> ----------------------- >>>>> >>>>> Currently, the only reliable way to catch exceptions, ignoring async >>>>> exceptions, is to fork a new thread. This is the approach used by the >>>>> enclosed-exceptions[6] package. I think it's quite ugly that we need >>>>> to go to such lengths due to the lack of one bit of information about >>>>> the exception! This would resolve ghc trac #5902[7]. >>>>> >>>>> base-4.7 added the `SomeAsyncException` type, but this doesn't enforce >>>>> anything. Any exception can be thrown as a sync or async exception. >>>>> Instead, we ought to have a reliable way to know if an exception is >>>>> synchronous or asynchronous. Here's what this would look like: >>>>> >>>>> data IsAsync = IsAsync >>>>> deriving (Typeable, Show) >>>>> >>>>> instance ExceptionInfo IsAsync where >>>>> displayExceptionInfo IsAsync = "thrown asynchronously" >>>>> >>>>> throwTo :: Exception e => ThreadId -> e -> IO () >>>>> throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync >>>>> >>>>> The details of this get a bit tricky: What happens if `throwIO` is >>>>> used to rethrow a `SomeException` which has this `IsAsync` flag set? >>>>> I'm going to leave out my thoughts on this for now as the interactions >>>>> between unsafePerformIO and the concept of "rethrowing" async >>>>> exceptions. Such details are explained in a post by Edsko de Vries[8] >>>>> and ghc trac #2558[9]. >>>>> >>>>> Issue: fromException loses info >>>>> =============================== >>>>> >>>>> I can think of one main non-ideal aspect of this proposal: >>>>> >>>>> Currently, the `toException` and `fromException` methods usually form >>>>> a prism. In other words, when `fromException` yields a `Just`, you >>>>> should get the same `SomeException` when using `toException` on that >>>>> value. >>>>> >>>>> For example, >>>>> >>>>> fail "testing 1 2 3" `catch` \(ex :: SomeException) -> throwIO ex >>>>> >>>>> is equivalent to >>>>> >>>>> fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex >>>>> >>>>> However, with exception info added to just `SomeException`, and no >>>>> changes to existing `Exception` instances, this >>>>> doesn't hold. Exceptions caught as a specific exception type get >>>>> rethrown with less information. >>>>> >>>>> One resolution to this is be to add `[SomeExceptionInfo]` as a field >>>>> to existing `Exception` instances. This would require the use of >>>>> non-default implementations of the `toException` and `fromException` >>>>> instances. >>>>> >>>>> Another approach is to have variants of `catch` and `throw` which also >>>>> pass around the `[SomeExceptionInfo]`. >>>>> >>>>> [1] >>>>> https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... >>>>> [2] >>>>> https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations >>>>> [3] https://www.python.org/dev/peps/pep-3134/ >>>>> [4] >>>>> https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html >>>>> [5] >>>>> https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html >>>>> [6] https://hackage.haskell.org/package/enclosed-exceptions >>>>> [7] https://ghc.haskell.org/trac/ghc/ticket/5902 >>>>> [8] http://www.edsko.net/2013/06/11/throwTo/ >>>>> [9] https://ghc.haskell.org/trac/ghc/ticket/2558 >>>>> >>>>> _______________________________________________ >>>>> Libraries mailing list >>>>> Libraries@haskell.org >>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >>>>> >>>> >>> >> > > > _______________________________________________ > Libraries mailing list > Libraries@haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >

..... why are you using exceptions are part of normal control flow for
actions that aren't some manner of thread timeout or otherwise exceptional?
on a more important note... its important to note that youre focusing on
the *profiling build* notion of call stack, rather than the (still
moderately in progress) dwarf stack trace work thats still on going. The
stack trace spamming issue you're alluding to that arises in the +RTS -xc
-RTS profiling stack traces should not ever happen with dwarf stack traces.
what precludes changing all exceptions in base/userland to having proper
stack traces associated with them as an alternative design that addresses
that same issues. I ask this because any changes to base are only going to
be happening in future GHCs, and thus any discussions about changing
exceptions in base really need to be forward looking with respect to
parallel materially ongoing work in GHC
for those who wanna read up on whats currently afoot in stack trace land
for GHC, let me share the following links
https://ghc.haskell.org/trac/ghc/ticket/3693#comment:75
https://ghc.haskell.org/trac/ghc/wiki/DWARF
http://arashrouhani.com/papers/master-thesis.pdf
On Tue, Apr 21, 2015 at 11:43 PM, Michael Sloan
Davean's proposal is essentially the same as mine, restarted and specialized to callstacks. So, I'm not sure why it would make you vote against this.
This does more than just stack traces, and is independent of the source of call stacks. What kind of mechanism are you envisioning that would make it redundant to include the callstack with the exception?
I can imagine setting a thread local variable to the "last callstack of raise#". However, this does not allow us to accumulate callstacks when the exception is rethrown. Often you care more about the initial throw of the exception, rather than the most recent one.
For example, with `+GHC -xc` output, when an exception is caught and rethrown, you'll see the callstacks of all the places it's thrown. This output is rather terrible for real world debugging, though, because it doesn't actually tell you what the exception is. When dealing with a concurrent system where some exceptions occur as part of normal operation, this becomes nightmareish. This proposal solves that problem. If you see even the rough possibility of another solution to this problem, please do tell.
-Michael
On Tue, Apr 21, 2015 at 7:26 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
in the context of davean's proposal (which i'm still digesting), i'm gonna go -1 on this one.
i'm really leery of commiting to any changes to our exception machinery until the dwarf stack trace tooling and associated RTS/exception interaction support is a bit more mature, because i think a lot of other approaches / changes to ghc / base have been driven by the lack of cheap stack traces. This proposal crosses that line, at least for me ;)
On Tue, Apr 21, 2015 at 6:24 PM, Michael Sloan
wrote: No, this proposal is not specifically about stack traces, that is just one of the usecases. Instead, this is about a general mechanism for including extra information with exceptions. The core of this proposal is still relevant even if the behavior of error / throw / throwTo / etc remain unchanged.
I'm not familiar with how the new dwarf stuff will interact with throwing / displaying exceptions. It seems like this would require having the debugger break at the throw site, and exceptions would still lack stack traces. Having informative stack traces is quite orthogonal to having a good place to store them.
Note that in my original proposal text I mentioned that this is agnostic of the particular source of the stack trace. In particular, this could be used with a profiling stack trace, implicit callstack, or, indeed, these traces via dwarf.
-Michael
On Tue, Apr 21, 2015 at 3:06 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
On a more important note: assuming ghc 7.12 has support for informative stack traces via dwarf by default, wouldn't that eliminate the need for this proposal? Namely : there perhaps should be some reasonable way to talk about concatting stack traces perhaps?
Phrased differently: how is the info that should perhaps be in informative stack traces not subsuming the info of this proposal?
On Tuesday, April 21, 2015, Michael Sloan
wrote: Ah, but it looks like Niklas does have a patch which adds implicit locations to such functions: https://phabricator.haskell.org/D861
However, there are some issues with changing the API of these functions: https://phabricator.haskell.org/D861#23250
(as mentioned in the "Backporting srcLoc to the GHC 7.10 branch" thread)
On Tue, Apr 21, 2015 at 2:04 PM, Michael Sloan
wrote: Hmm, that patch doesn't appear to add stack traces to 'Prelude.error', which is what Carter wants here. Also, I think it would be done with profiling callstacks rather than implicit callstacks. But it's certainly also useful to have functions which do the same with implicit callstacks!
On Tue, Apr 21, 2015 at 1:55 PM, Evan Laforge
wrote: > Maybe I'm missing something, but isn't this already implemented? > > https://phabricator.haskell.org/D578 > > On Tue, Apr 21, 2015 at 1:37 PM, Michael Sloan
> wrote: > > On Thu, Apr 16, 2015 at 8:08 PM, Carter Schonwald > > wrote: > >> > >> if you can patch prelude error to include stack traces, i will > owe you a > >> >=1 beer each at the next two icfps. Thats all i want for > christmas. :) > > > > > > Sounds good! No promises, but I'll be giving this a try soon. > Looking > > forward to ICFP beers either way :D > > > >> i can't speak for how a different patch might work out, because > thats not > >> what I'd tried at the time. If you have a go, please share the > results! > >> -Carter > >> > >> On Wed, Apr 15, 2015 at 12:22 AM, Michael Sloan < > mgsloan@gmail.com> wrote: > >>> > >>> Hi Carter! > >>> > >>> Interesting! This thread, right? > >>> > https://mail.haskell.org/pipermail/libraries/2014-December/024429.html > >>> > >>> I haven't tried this as a patch to base, but I'm certain that > the core of > >>> the proposal has no extra dependencies. Note that the proposal > isn't about > >>> stack traces in particular - that's just one application of > being able to > >>> throw exceptions with extra information. > >>> > >>> Even if `throwTo` isn't modified to throw exceptions with stack > traces, > >>> this functionality could be provided outside of > `Control.Exception` (though, > >>> that does seem like the right place to put it). I'm surprised > that the > >>> circularity was so problematic, though. Why isn't it sufficient > to have an > >>> hs-boot file for `GHC.Stack`, which exports `currentCallStack`? > >>> > >>> -Michael > >>> > >>> On Tue, Apr 14, 2015 at 7:55 PM, Carter Schonwald > >>> wrote: > >>>> > >>>> Hey Michael, > >>>> I actually proposed something along these lines that got OK'd by > >>>> libraries early this past fall, the main challenge we hit was > actually doing > >>>> the enginering to add the stack traces to exceptions! theres > some nasty > >>>> module cycles in base that happen when you try to weave things > around so > >>>> that the standard error "message here" call includes some stack > trace info. > >>>> Have you tried to do that simple starter patch to base? > >>>> > >>>> Chris Allen and I spent like 2 days trying to get it to work > and just > >>>> gave up because of the cycles. We (and others) would probably > love some > >>>> headway on that front. > >>>> > >>>> Theres also some in progress work to use the dwarf debugging > info data > >>>> in >7.10 to provide useful stack traces in the default builds > for GHC afaik, > >>>> 'cause the stack trace functionality you're pointing at > currenlty only work > >>>> on profiled builds > >>>> > >>>> cheers > >>>> -Carter > >>>> > >>>> On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan < > mgsloan@gmail.com> > >>>> wrote: > >>>>> > >>>>> Control.Exception currently lacks a good way to supply extra > >>>>> information along with exceptions. For example, exceptions > could be > >>>>> thrown along with their callstack[1] or implicit stack[2], but > we have > >>>>> no generic way to include this information with exceptions. > >>>>> > >>>>> Proposed Solution > >>>>> ================= > >>>>> > >>>>> The proposed solution is to add a list of `SomeExceptionInfo` > to the > >>>>> `SomeException` datatype. This list stores additional > information > >>>>> about the exception. These `ExceptionInfo` instances use a > mechanism > >>>>> which is pretty much identical to the dynamic way the > `Exception` type > >>>>> works: > >>>>> > >>>>> data SomeException = forall e . Exception e => > >>>>> SomeExceptionWithInfo e [SomeExceptionInfo] > >>>>> > >>>>> data SomeExceptionInfo = forall a . ExceptionInfo a => > >>>>> SomeExceptionInfo a > >>>>> > >>>>> class Typeable a => ExceptionInfo a where > >>>>> displayExceptionInfo :: a -> String > >>>>> > >>>>> addExceptionInfo > >>>>> :: (ExceptionInfo a, Exception e) > >>>>> => a -> e -> SomeException > >>>>> addExceptionInfo x (toException -> SomeExceptionWithInfo e > xs) = > >>>>> SomeExceptionWithInfo e (SomeExceptionInfo x : xs) > >>>>> > >>>>> `ExceptionInfo` lacks the to / from functions that `Exception` > has, > >>>>> because I don't see much point in supporting a hierarchy for > exception > >>>>> info. The `Typeable` superclass constraint supplies the > necessary > >>>>> casting. > >>>>> > >>>>> `SomeExceptionInfo` could validly instead just use the > constraint > >>>>> `(Typeable a, Show a)`. However, I believe it's good to have > a new > >>>>> class for this so that: > >>>>> > >>>>> * The user can specify a custom `displayExceptionInfo` > >>>>> implementation, for when this extra info is presented to the > user. > >>>>> This function would be invoked by the `show` implementation > for > >>>>> `SomeException`. > >>>>> > >>>>> * Types need to opt-in to be usable with `SomeExceptionInfo`. > >>>>> Similarly to exceptions, I imagine that a type with a > >>>>> `ExceptionInfo` instance won't be used for anything but > acting as > >>>>> such an annotation. Having a class for this allows you to > ask GHCI > >>>>> about all in-scope exception info types via `:info > ExceptionInfo`. > >>>>> > >>>>> Backwards Compatibility > >>>>> ======================= > >>>>> > >>>>> GHC 7.10 adds support for bidirectional pattern synonyms. > This means > >>>>> that this change could be made without breaking code: > >>>>> > >>>>> pattern SomeException x <- SomeExceptionWithInfo x _ where > >>>>> SomeException x = SomeExceptionWithInfo x [] > >>>>> > >>>>> Note that consumers of this do not need to enable > `-XPatternSynonyms`. > >>>>> > >>>>> Applications > >>>>> ============ > >>>>> > >>>>> Callstacks > >>>>> ---------- > >>>>> > >>>>> As mentioned at the beginning, this can be used to add > callstacks to > >>>>> exceptions: > >>>>> > >>>>> newtype ExceptionCallStack = > >>>>> ExceptionCallStack { unExceptionCallStack :: [String] } > >>>>> deriving Typeable > >>>>> > >>>>> instance ExceptionInfo ExceptionCallStack where > >>>>> displayExceptionInfo = unlines . unExceptionCallStack > >>>>> > >>>>> throwIOWithStack :: Exception e => e -> IO a > >>>>> throwIOWithStack e = do > >>>>> stack <- currentCallStack > >>>>> if null stack > >>>>> then throwIO e > >>>>> else throwIO (addExceptionInfo (ExceptionCallStack > stack) > >>>>> e) > >>>>> > >>>>> I see little downside for making something like this the > default > >>>>> implementation `throwIO`. Each rethrowing of the > `SomeException` > >>>>> would add an additional stacktrace to its annotation, much > like the > >>>>> output of `+RTS -xc`. Unlike this debug output, though, the > >>>>> stacktraces would be associated with the exception, rather > than just > >>>>> listing locations that exceptions were thrown. This makes it > >>>>> tractable to debug exceptions that occur in concurrent > programs, or in > >>>>> programs which frequently throw exceptions during normal > functioning. > >>>>> > >>>>> Throwing Exceptions in Handlers > >>>>> ------------------------------- > >>>>> > >>>>> Example: > >>>>> > >>>>> main = > >>>>> throwIO InformativeErrorMessage `finally` > >>>>> throwIO ObscureCleanupIssue > >>>>> > >>>>> While `InformativeErrorMessage` got thrown, the user doesn't > see it, > >>>>> since `ObscureCleanupIssue` is thrown instead. This causes a > few > >>>>> issues: > >>>>> > >>>>> 1. If the exception is handled by the default handler and > yielded to > >>>>> the user, then the more informative error is lost. > >>>>> > >>>>> 2. Callers who expect to catch the "Informative error message" > won't > >>>>> run their handlers for this exception type. > >>>>> > >>>>> Problem 1 can now easily be resolved by adding some info to the > >>>>> exception: > >>>>> > >>>>> data ExceptionCause = ExceptionCause > >>>>> { unExceptionCause :: SomeException } > >>>>> deriving Typeable > >>>>> > >>>>> instance ExceptionInfo ExceptionCause where > >>>>> displayExceptionInfo fe = > >>>>> "thrown while handling " ++ > >>>>> displayException (unExceptionCause fe) > >>>>> > >>>>> catch :: Exception e => IO a -> (e -> IO a) -> IO a > >>>>> catch f g = f `oldCatch` handler > >>>>> where > >>>>> handler ex = g ex `oldCatch` \(ex' :: SomeException) -> > >>>>> throwIO (addExceptionInfo info ex') > >>>>> where > >>>>> info = ExceptionCause (toException ex) > >>>>> > >>>>> This implementation of `catch` is written in a > backwards-compatible > >>>>> way, such that the exception thrown during finalization is > still the > >>>>> one that gets rethrown. The "original" exception is recorded > in the > >>>>> added info. This is the same approach used by Python 3's > >>>>> `__context__` attribute[3]. This was brought to my attention > in a > >>>>> post by Mike Meyer[4], in a thread about having bracket not > suppress > >>>>> the original exception[5]. > >>>>> > >>>>> This doesn't directly resolve issue #2, due to this backwards > >>>>> compatibility. With the earlier example, a `catch` handler for > >>>>> `InformativeErrorMessage` won't be invoked, because it isn't > the > >>>>> exception being rethrown. This can be resolved by having a > variant of > >>>>> catch which instead throws the original exception. This might > be a > >>>>> good default for finalization handlers like `bracket` and > `finally`. > >>>>> > >>>>> Asynchronous Exceptions > >>>>> ----------------------- > >>>>> > >>>>> Currently, the only reliable way to catch exceptions, ignoring > async > >>>>> exceptions, is to fork a new thread. This is the approach > used by the > >>>>> enclosed-exceptions[6] package. I think it's quite ugly that > we need > >>>>> to go to such lengths due to the lack of one bit of > information about > >>>>> the exception! This would resolve ghc trac #5902[7]. > >>>>> > >>>>> base-4.7 added the `SomeAsyncException` type, but this doesn't > enforce > >>>>> anything. Any exception can be thrown as a sync or async > exception. > >>>>> Instead, we ought to have a reliable way to know if an > exception is > >>>>> synchronous or asynchronous. Here's what this would look like: > >>>>> > >>>>> data IsAsync = IsAsync > >>>>> deriving (Typeable, Show) > >>>>> > >>>>> instance ExceptionInfo IsAsync where > >>>>> displayExceptionInfo IsAsync = "thrown asynchronously" > >>>>> > >>>>> throwTo :: Exception e => ThreadId -> e -> IO () > >>>>> throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync > >>>>> > >>>>> The details of this get a bit tricky: What happens if > `throwIO` is > >>>>> used to rethrow a `SomeException` which has this `IsAsync` > flag set? > >>>>> I'm going to leave out my thoughts on this for now as the > interactions > >>>>> between unsafePerformIO and the concept of "rethrowing" async > >>>>> exceptions. Such details are explained in a post by Edsko de > Vries[8] > >>>>> and ghc trac #2558[9]. > >>>>> > >>>>> Issue: fromException loses info > >>>>> =============================== > >>>>> > >>>>> I can think of one main non-ideal aspect of this proposal: > >>>>> > >>>>> Currently, the `toException` and `fromException` methods > usually form > >>>>> a prism. In other words, when `fromException` yields a > `Just`, you > >>>>> should get the same `SomeException` when using `toException` > on that > >>>>> value. > >>>>> > >>>>> For example, > >>>>> > >>>>> fail "testing 1 2 3" `catch` \(ex :: SomeException) -> > throwIO ex > >>>>> > >>>>> is equivalent to > >>>>> > >>>>> fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex > >>>>> > >>>>> However, with exception info added to just `SomeException`, > and no > >>>>> changes to existing `Exception` instances, this > >>>>> doesn't hold. Exceptions caught as a specific exception type > get > >>>>> rethrown with less information. > >>>>> > >>>>> One resolution to this is be to add `[SomeExceptionInfo]` as a > field > >>>>> to existing `Exception` instances. This would require the use > of > >>>>> non-default implementations of the `toException` and > `fromException` > >>>>> instances. > >>>>> > >>>>> Another approach is to have variants of `catch` and `throw` > which also > >>>>> pass around the `[SomeExceptionInfo]`. > >>>>> > >>>>> [1] > >>>>> > https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... > >>>>> [2] > >>>>> > https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations > >>>>> [3] https://www.python.org/dev/peps/pep-3134/ > >>>>> [4] > >>>>> > https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html > >>>>> [5] > >>>>> > https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html > >>>>> [6] https://hackage.haskell.org/package/enclosed-exceptions > >>>>> [7] https://ghc.haskell.org/trac/ghc/ticket/5902 > >>>>> [8] http://www.edsko.net/2013/06/11/throwTo/ > >>>>> [9] https://ghc.haskell.org/trac/ghc/ticket/2558 > >>>>> > >>>>> _______________________________________________ > >>>>> Libraries mailing list > >>>>> Libraries@haskell.org > >>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > >>>>> > >>>> > >>> > >> > > > > > > _______________________________________________ > > Libraries mailing list > > Libraries@haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > > >

Sorry for the response delay! I wanted to take some time to review your links. On Tue, Apr 21, 2015 at 9:16 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
..... why are you using exceptions are part of normal control flow for actions that aren't some manner of thread timeout or otherwise exceptional?
Fair point! Personally, I think it's fine to use exceptions for circumstances in which exceptions are expected to occur. In my case, a concrete example is a network library which throws exceptions when attempting to receive / send to a connection which has disconnected. So, we expect exceptions from that. The argument could be made that this is an API design flaw. on a more important note... its important to note that youre focusing on
the *profiling build* notion of call stack, rather than the (still moderately in progress) dwarf stack trace work thats still on going. The stack trace spamming issue you're alluding to that arises in the +RTS -xc -RTS profiling stack traces should not ever happen with dwarf stack traces.
I think the mechanism needs to be able to support different sources for stack traces. Since it should work for all thrown exceptions, this means adopting a global configuration of throwing with stack traces. This might look like having a function 'setRaiseFunction :: (SomeException -> IO ()) -> IO ()', which would work similarly to 'setUncaughtExceptionHandler' ( http://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Conc-Sync.html#v:se...). Instead of setting the default exception handler, it sets how exceptions are thrown. This will allow the user to use profiling stack traces, DWARF stack traces, or no stack traces at all. Sure, global state like this is gross and non Haskell-ey. It's quite sensible, though, as which source of callstack being viable is a global property of your program (whether it was built with -prof, with -g for dwarf stack traces). We cannot just settle on dwarf callstacks, because that won't work for windows. what precludes changing all exceptions in base/userland to having proper
stack traces associated with them as an alternative design that addresses that same issues. I ask this because any changes to base are only going to be happening in future GHCs, and thus any discussions about changing exceptions in base really need to be forward looking with respect to parallel materially ongoing work in GHC
for those who wanna read up on whats currently afoot in stack trace land for GHC, let me share the following links
https://ghc.haskell.org/trac/ghc/ticket/3693#comment:75 https://ghc.haskell.org/trac/ghc/wiki/DWARF http://arashrouhani.com/papers/master-thesis.pdf
I read chapter 6 of the thesis. Cool stuff, very pertinent! Our reasoning agrees a lot in section 6.3. The difference is that I'm willing to accept information being lost when catching more specific types. We could certainly pick a richer stack type than [String], such as his stack datatypes, but -prof based stack traces would also need to provide this richer type. He also explores some options involving RTS changes. These would make "execution inside a handler" into a special execution context. At the beginning of a handler, 'recoverExecutionStack' would get the stack. This alone is pretty reasonable, but there are problems with the scheme for rethrowing. The idea is essentially to modify the meaning of 'throw' within a handler to use the stack for the original exception. Section 6.3 covers a number of issues with this approach. In particular, to me the following make this seem quite undesirable: 1) Rethrowing outside the handler does not rethrow with the stack (e.g., after a try) 2) Any exception thrown in the handler gets rethrown with the original exception's callstack. This is bizarre and misleading. 3) We don't get additional stacks for the rethrows. So, unfortunately, that particular solution is also unsatisfying. It seems to me like we're pretty much trapped by the old API. So, if my proposal is distasteful, the only way forward is to break the backwards compatibility of Control.Exception, and endure propagating the API change through all the packages (leading to yucky CPP). -Michael
On Tue, Apr 21, 2015 at 11:43 PM, Michael Sloan
wrote: Davean's proposal is essentially the same as mine, restarted and specialized to callstacks. So, I'm not sure why it would make you vote against this.
This does more than just stack traces, and is independent of the source of call stacks. What kind of mechanism are you envisioning that would make it redundant to include the callstack with the exception?
I can imagine setting a thread local variable to the "last callstack of raise#". However, this does not allow us to accumulate callstacks when the exception is rethrown. Often you care more about the initial throw of the exception, rather than the most recent one.
For example, with `+GHC -xc` output, when an exception is caught and rethrown, you'll see the callstacks of all the places it's thrown. This output is rather terrible for real world debugging, though, because it doesn't actually tell you what the exception is. When dealing with a concurrent system where some exceptions occur as part of normal operation, this becomes nightmareish. This proposal solves that problem. If you see even the rough possibility of another solution to this problem, please do tell.
-Michael
On Tue, Apr 21, 2015 at 7:26 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
in the context of davean's proposal (which i'm still digesting), i'm gonna go -1 on this one.
i'm really leery of commiting to any changes to our exception machinery until the dwarf stack trace tooling and associated RTS/exception interaction support is a bit more mature, because i think a lot of other approaches / changes to ghc / base have been driven by the lack of cheap stack traces. This proposal crosses that line, at least for me ;)
On Tue, Apr 21, 2015 at 6:24 PM, Michael Sloan
wrote: No, this proposal is not specifically about stack traces, that is just one of the usecases. Instead, this is about a general mechanism for including extra information with exceptions. The core of this proposal is still relevant even if the behavior of error / throw / throwTo / etc remain unchanged.
I'm not familiar with how the new dwarf stuff will interact with throwing / displaying exceptions. It seems like this would require having the debugger break at the throw site, and exceptions would still lack stack traces. Having informative stack traces is quite orthogonal to having a good place to store them.
Note that in my original proposal text I mentioned that this is agnostic of the particular source of the stack trace. In particular, this could be used with a profiling stack trace, implicit callstack, or, indeed, these traces via dwarf.
-Michael
On Tue, Apr 21, 2015 at 3:06 PM, Carter Schonwald < carter.schonwald@gmail.com> wrote:
On a more important note: assuming ghc 7.12 has support for informative stack traces via dwarf by default, wouldn't that eliminate the need for this proposal? Namely : there perhaps should be some reasonable way to talk about concatting stack traces perhaps?
Phrased differently: how is the info that should perhaps be in informative stack traces not subsuming the info of this proposal?
On Tuesday, April 21, 2015, Michael Sloan
wrote: Ah, but it looks like Niklas does have a patch which adds implicit locations to such functions: https://phabricator.haskell.org/D861
However, there are some issues with changing the API of these functions: https://phabricator.haskell.org/D861#23250
(as mentioned in the "Backporting srcLoc to the GHC 7.10 branch" thread)
On Tue, Apr 21, 2015 at 2:04 PM, Michael Sloan
wrote: > Hmm, that patch doesn't appear to add stack traces to > 'Prelude.error', which is what Carter wants here. Also, I think it would > be done with profiling callstacks rather than implicit callstacks. But > it's certainly also useful to have functions which do the same with > implicit callstacks! > > > On Tue, Apr 21, 2015 at 1:55 PM, Evan Laforge
> wrote: > >> Maybe I'm missing something, but isn't this already implemented? >> >> https://phabricator.haskell.org/D578 >> >> On Tue, Apr 21, 2015 at 1:37 PM, Michael Sloan >> wrote: >> > On Thu, Apr 16, 2015 at 8:08 PM, Carter Schonwald >> > wrote: >> >> >> >> if you can patch prelude error to include stack traces, i will >> owe you a >> >> >=1 beer each at the next two icfps. Thats all i want for >> christmas. :) >> > >> > >> > Sounds good! No promises, but I'll be giving this a try soon. >> Looking >> > forward to ICFP beers either way :D >> > >> >> i can't speak for how a different patch might work out, because >> thats not >> >> what I'd tried at the time. If you have a go, please share the >> results! >> >> -Carter >> >> >> >> On Wed, Apr 15, 2015 at 12:22 AM, Michael Sloan < >> mgsloan@gmail.com> wrote: >> >>> >> >>> Hi Carter! >> >>> >> >>> Interesting! This thread, right? >> >>> >> https://mail.haskell.org/pipermail/libraries/2014-December/024429.html >> >>> >> >>> I haven't tried this as a patch to base, but I'm certain that >> the core of >> >>> the proposal has no extra dependencies. Note that the proposal >> isn't about >> >>> stack traces in particular - that's just one application of >> being able to >> >>> throw exceptions with extra information. >> >>> >> >>> Even if `throwTo` isn't modified to throw exceptions with stack >> traces, >> >>> this functionality could be provided outside of >> `Control.Exception` (though, >> >>> that does seem like the right place to put it). I'm surprised >> that the >> >>> circularity was so problematic, though. Why isn't it >> sufficient to have an >> >>> hs-boot file for `GHC.Stack`, which exports `currentCallStack`? >> >>> >> >>> -Michael >> >>> >> >>> On Tue, Apr 14, 2015 at 7:55 PM, Carter Schonwald >> >>> wrote: >> >>>> >> >>>> Hey Michael, >> >>>> I actually proposed something along these lines that got OK'd >> by >> >>>> libraries early this past fall, the main challenge we hit was >> actually doing >> >>>> the enginering to add the stack traces to exceptions! theres >> some nasty >> >>>> module cycles in base that happen when you try to weave things >> around so >> >>>> that the standard error "message here" call includes some >> stack trace info. >> >>>> Have you tried to do that simple starter patch to base? >> >>>> >> >>>> Chris Allen and I spent like 2 days trying to get it to work >> and just >> >>>> gave up because of the cycles. We (and others) would probably >> love some >> >>>> headway on that front. >> >>>> >> >>>> Theres also some in progress work to use the dwarf debugging >> info data >> >>>> in >7.10 to provide useful stack traces in the default builds >> for GHC afaik, >> >>>> 'cause the stack trace functionality you're pointing at >> currenlty only work >> >>>> on profiled builds >> >>>> >> >>>> cheers >> >>>> -Carter >> >>>> >> >>>> On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan < >> mgsloan@gmail.com> >> >>>> wrote: >> >>>>> >> >>>>> Control.Exception currently lacks a good way to supply extra >> >>>>> information along with exceptions. For example, exceptions >> could be >> >>>>> thrown along with their callstack[1] or implicit stack[2], >> but we have >> >>>>> no generic way to include this information with exceptions. >> >>>>> >> >>>>> Proposed Solution >> >>>>> ================= >> >>>>> >> >>>>> The proposed solution is to add a list of `SomeExceptionInfo` >> to the >> >>>>> `SomeException` datatype. This list stores additional >> information >> >>>>> about the exception. These `ExceptionInfo` instances use a >> mechanism >> >>>>> which is pretty much identical to the dynamic way the >> `Exception` type >> >>>>> works: >> >>>>> >> >>>>> data SomeException = forall e . Exception e => >> >>>>> SomeExceptionWithInfo e [SomeExceptionInfo] >> >>>>> >> >>>>> data SomeExceptionInfo = forall a . ExceptionInfo a => >> >>>>> SomeExceptionInfo a >> >>>>> >> >>>>> class Typeable a => ExceptionInfo a where >> >>>>> displayExceptionInfo :: a -> String >> >>>>> >> >>>>> addExceptionInfo >> >>>>> :: (ExceptionInfo a, Exception e) >> >>>>> => a -> e -> SomeException >> >>>>> addExceptionInfo x (toException -> SomeExceptionWithInfo >> e xs) = >> >>>>> SomeExceptionWithInfo e (SomeExceptionInfo x : xs) >> >>>>> >> >>>>> `ExceptionInfo` lacks the to / from functions that >> `Exception` has, >> >>>>> because I don't see much point in supporting a hierarchy for >> exception >> >>>>> info. The `Typeable` superclass constraint supplies the >> necessary >> >>>>> casting. >> >>>>> >> >>>>> `SomeExceptionInfo` could validly instead just use the >> constraint >> >>>>> `(Typeable a, Show a)`. However, I believe it's good to have >> a new >> >>>>> class for this so that: >> >>>>> >> >>>>> * The user can specify a custom `displayExceptionInfo` >> >>>>> implementation, for when this extra info is presented to >> the user. >> >>>>> This function would be invoked by the `show` implementation >> for >> >>>>> `SomeException`. >> >>>>> >> >>>>> * Types need to opt-in to be usable with >> `SomeExceptionInfo`. >> >>>>> Similarly to exceptions, I imagine that a type with a >> >>>>> `ExceptionInfo` instance won't be used for anything but >> acting as >> >>>>> such an annotation. Having a class for this allows you to >> ask GHCI >> >>>>> about all in-scope exception info types via `:info >> ExceptionInfo`. >> >>>>> >> >>>>> Backwards Compatibility >> >>>>> ======================= >> >>>>> >> >>>>> GHC 7.10 adds support for bidirectional pattern synonyms. >> This means >> >>>>> that this change could be made without breaking code: >> >>>>> >> >>>>> pattern SomeException x <- SomeExceptionWithInfo x _ where >> >>>>> SomeException x = SomeExceptionWithInfo x [] >> >>>>> >> >>>>> Note that consumers of this do not need to enable >> `-XPatternSynonyms`. >> >>>>> >> >>>>> Applications >> >>>>> ============ >> >>>>> >> >>>>> Callstacks >> >>>>> ---------- >> >>>>> >> >>>>> As mentioned at the beginning, this can be used to add >> callstacks to >> >>>>> exceptions: >> >>>>> >> >>>>> newtype ExceptionCallStack = >> >>>>> ExceptionCallStack { unExceptionCallStack :: [String] >> } >> >>>>> deriving Typeable >> >>>>> >> >>>>> instance ExceptionInfo ExceptionCallStack where >> >>>>> displayExceptionInfo = unlines . unExceptionCallStack >> >>>>> >> >>>>> throwIOWithStack :: Exception e => e -> IO a >> >>>>> throwIOWithStack e = do >> >>>>> stack <- currentCallStack >> >>>>> if null stack >> >>>>> then throwIO e >> >>>>> else throwIO (addExceptionInfo >> (ExceptionCallStack stack) >> >>>>> e) >> >>>>> >> >>>>> I see little downside for making something like this the >> default >> >>>>> implementation `throwIO`. Each rethrowing of the >> `SomeException` >> >>>>> would add an additional stacktrace to its annotation, much >> like the >> >>>>> output of `+RTS -xc`. Unlike this debug output, though, the >> >>>>> stacktraces would be associated with the exception, rather >> than just >> >>>>> listing locations that exceptions were thrown. This makes it >> >>>>> tractable to debug exceptions that occur in concurrent >> programs, or in >> >>>>> programs which frequently throw exceptions during normal >> functioning. >> >>>>> >> >>>>> Throwing Exceptions in Handlers >> >>>>> ------------------------------- >> >>>>> >> >>>>> Example: >> >>>>> >> >>>>> main = >> >>>>> throwIO InformativeErrorMessage `finally` >> >>>>> throwIO ObscureCleanupIssue >> >>>>> >> >>>>> While `InformativeErrorMessage` got thrown, the user doesn't >> see it, >> >>>>> since `ObscureCleanupIssue` is thrown instead. This causes a >> few >> >>>>> issues: >> >>>>> >> >>>>> 1. If the exception is handled by the default handler and >> yielded to >> >>>>> the user, then the more informative error is lost. >> >>>>> >> >>>>> 2. Callers who expect to catch the "Informative error >> message" won't >> >>>>> run their handlers for this exception type. >> >>>>> >> >>>>> Problem 1 can now easily be resolved by adding some info to >> the >> >>>>> exception: >> >>>>> >> >>>>> data ExceptionCause = ExceptionCause >> >>>>> { unExceptionCause :: SomeException } >> >>>>> deriving Typeable >> >>>>> >> >>>>> instance ExceptionInfo ExceptionCause where >> >>>>> displayExceptionInfo fe = >> >>>>> "thrown while handling " ++ >> >>>>> displayException (unExceptionCause fe) >> >>>>> >> >>>>> catch :: Exception e => IO a -> (e -> IO a) -> IO a >> >>>>> catch f g = f `oldCatch` handler >> >>>>> where >> >>>>> handler ex = g ex `oldCatch` \(ex' :: SomeException) >> -> >> >>>>> throwIO (addExceptionInfo info ex') >> >>>>> where >> >>>>> info = ExceptionCause (toException ex) >> >>>>> >> >>>>> This implementation of `catch` is written in a >> backwards-compatible >> >>>>> way, such that the exception thrown during finalization is >> still the >> >>>>> one that gets rethrown. The "original" exception is recorded >> in the >> >>>>> added info. This is the same approach used by Python 3's >> >>>>> `__context__` attribute[3]. This was brought to my attention >> in a >> >>>>> post by Mike Meyer[4], in a thread about having bracket not >> suppress >> >>>>> the original exception[5]. >> >>>>> >> >>>>> This doesn't directly resolve issue #2, due to this backwards >> >>>>> compatibility. With the earlier example, a `catch` handler >> for >> >>>>> `InformativeErrorMessage` won't be invoked, because it isn't >> the >> >>>>> exception being rethrown. This can be resolved by having a >> variant of >> >>>>> catch which instead throws the original exception. This >> might be a >> >>>>> good default for finalization handlers like `bracket` and >> `finally`. >> >>>>> >> >>>>> Asynchronous Exceptions >> >>>>> ----------------------- >> >>>>> >> >>>>> Currently, the only reliable way to catch exceptions, >> ignoring async >> >>>>> exceptions, is to fork a new thread. This is the approach >> used by the >> >>>>> enclosed-exceptions[6] package. I think it's quite ugly that >> we need >> >>>>> to go to such lengths due to the lack of one bit of >> information about >> >>>>> the exception! This would resolve ghc trac #5902[7]. >> >>>>> >> >>>>> base-4.7 added the `SomeAsyncException` type, but this >> doesn't enforce >> >>>>> anything. Any exception can be thrown as a sync or async >> exception. >> >>>>> Instead, we ought to have a reliable way to know if an >> exception is >> >>>>> synchronous or asynchronous. Here's what this would look >> like: >> >>>>> >> >>>>> data IsAsync = IsAsync >> >>>>> deriving (Typeable, Show) >> >>>>> >> >>>>> instance ExceptionInfo IsAsync where >> >>>>> displayExceptionInfo IsAsync = "thrown asynchronously" >> >>>>> >> >>>>> throwTo :: Exception e => ThreadId -> e -> IO () >> >>>>> throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync >> >>>>> >> >>>>> The details of this get a bit tricky: What happens if >> `throwIO` is >> >>>>> used to rethrow a `SomeException` which has this `IsAsync` >> flag set? >> >>>>> I'm going to leave out my thoughts on this for now as the >> interactions >> >>>>> between unsafePerformIO and the concept of "rethrowing" async >> >>>>> exceptions. Such details are explained in a post by Edsko de >> Vries[8] >> >>>>> and ghc trac #2558[9]. >> >>>>> >> >>>>> Issue: fromException loses info >> >>>>> =============================== >> >>>>> >> >>>>> I can think of one main non-ideal aspect of this proposal: >> >>>>> >> >>>>> Currently, the `toException` and `fromException` methods >> usually form >> >>>>> a prism. In other words, when `fromException` yields a >> `Just`, you >> >>>>> should get the same `SomeException` when using `toException` >> on that >> >>>>> value. >> >>>>> >> >>>>> For example, >> >>>>> >> >>>>> fail "testing 1 2 3" `catch` \(ex :: SomeException) -> >> throwIO ex >> >>>>> >> >>>>> is equivalent to >> >>>>> >> >>>>> fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO >> ex >> >>>>> >> >>>>> However, with exception info added to just `SomeException`, >> and no >> >>>>> changes to existing `Exception` instances, this >> >>>>> doesn't hold. Exceptions caught as a specific exception type >> get >> >>>>> rethrown with less information. >> >>>>> >> >>>>> One resolution to this is be to add `[SomeExceptionInfo]` as >> a field >> >>>>> to existing `Exception` instances. This would require the >> use of >> >>>>> non-default implementations of the `toException` and >> `fromException` >> >>>>> instances. >> >>>>> >> >>>>> Another approach is to have variants of `catch` and `throw` >> which also >> >>>>> pass around the `[SomeExceptionInfo]`. >> >>>>> >> >>>>> [1] >> >>>>> >> https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... >> >>>>> [2] >> >>>>> >> https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations >> >>>>> [3] https://www.python.org/dev/peps/pep-3134/ >> >>>>> [4] >> >>>>> >> https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html >> >>>>> [5] >> >>>>> >> https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html >> >>>>> [6] https://hackage.haskell.org/package/enclosed-exceptions >> >>>>> [7] https://ghc.haskell.org/trac/ghc/ticket/5902 >> >>>>> [8] http://www.edsko.net/2013/06/11/throwTo/ >> >>>>> [9] https://ghc.haskell.org/trac/ghc/ticket/2558 >> >>>>> >> >>>>> _______________________________________________ >> >>>>> Libraries mailing list >> >>>>> Libraries@haskell.org >> >>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> >>>>> >> >>>> >> >>> >> >> >> > >> > >> > _______________________________________________ >> > Libraries mailing list >> > Libraries@haskell.org >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries >> > >> > >

Sorry to confuse this thread with a second Michael.
I spoke with Michael Sloan about this proposal before he made it. I'm
usually very hesitant to introduce breaking changes to core APIs, but in
this case (1) there's a very good use case that's currently excluded by the
API, and (2) Michael Sloan figured out some great ways to minimize the
breakage. You could even argue that this proposal has *no* API breakage.
I'm +1 on including it. I'm also hopeful that we can address the `error =
errorWithStackTrace`, but that would really be a step 2 after the changes
to SomeException are made.
On Wed, Apr 15, 2015 at 5:56 AM Carter Schonwald
Hey Michael, I actually proposed something along these lines that got OK'd by libraries early this past fall, the main challenge we hit was actually doing the enginering to add the stack traces to exceptions! theres some nasty module cycles in base that happen when you try to weave things around so that the standard error "message here" call includes some stack trace info. Have you tried to do that simple starter patch to base?
Chris Allen and I spent like 2 days trying to get it to work and just gave up because of the cycles. We (and others) would probably love some headway on that front.
Theres also some in progress work to use the dwarf debugging info data in
7.10 to provide useful stack traces in the default builds for GHC afaik, 'cause the stack trace functionality you're pointing at currenlty only work on profiled builds
cheers -Carter
On Tue, Apr 14, 2015 at 2:38 PM, Michael Sloan
wrote: Control.Exception currently lacks a good way to supply extra information along with exceptions. For example, exceptions could be thrown along with their callstack[1] or implicit stack[2], but we have no generic way to include this information with exceptions.
Proposed Solution =================
The proposed solution is to add a list of `SomeExceptionInfo` to the `SomeException` datatype. This list stores additional information about the exception. These `ExceptionInfo` instances use a mechanism which is pretty much identical to the dynamic way the `Exception` type works:
data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
class Typeable a => ExceptionInfo a where displayExceptionInfo :: a -> String
addExceptionInfo :: (ExceptionInfo a, Exception e) => a -> e -> SomeException addExceptionInfo x (toException -> SomeExceptionWithInfo e xs) = SomeExceptionWithInfo e (SomeExceptionInfo x : xs)
`ExceptionInfo` lacks the to / from functions that `Exception` has, because I don't see much point in supporting a hierarchy for exception info. The `Typeable` superclass constraint supplies the necessary casting.
`SomeExceptionInfo` could validly instead just use the constraint `(Typeable a, Show a)`. However, I believe it's good to have a new class for this so that:
* The user can specify a custom `displayExceptionInfo` implementation, for when this extra info is presented to the user. This function would be invoked by the `show` implementation for `SomeException`.
* Types need to opt-in to be usable with `SomeExceptionInfo`. Similarly to exceptions, I imagine that a type with a `ExceptionInfo` instance won't be used for anything but acting as such an annotation. Having a class for this allows you to ask GHCI about all in-scope exception info types via `:info ExceptionInfo`.
Backwards Compatibility =======================
GHC 7.10 adds support for bidirectional pattern synonyms. This means that this change could be made without breaking code:
pattern SomeException x <- SomeExceptionWithInfo x _ where SomeException x = SomeExceptionWithInfo x []
Note that consumers of this do not need to enable `-XPatternSynonyms`.
Applications ============
Callstacks ----------
As mentioned at the beginning, this can be used to add callstacks to exceptions:
newtype ExceptionCallStack = ExceptionCallStack { unExceptionCallStack :: [String] } deriving Typeable
instance ExceptionInfo ExceptionCallStack where displayExceptionInfo = unlines . unExceptionCallStack
throwIOWithStack :: Exception e => e -> IO a throwIOWithStack e = do stack <- currentCallStack if null stack then throwIO e else throwIO (addExceptionInfo (ExceptionCallStack stack) e)
I see little downside for making something like this the default implementation `throwIO`. Each rethrowing of the `SomeException` would add an additional stacktrace to its annotation, much like the output of `+RTS -xc`. Unlike this debug output, though, the stacktraces would be associated with the exception, rather than just listing locations that exceptions were thrown. This makes it tractable to debug exceptions that occur in concurrent programs, or in programs which frequently throw exceptions during normal functioning.
Throwing Exceptions in Handlers -------------------------------
Example:
main = throwIO InformativeErrorMessage `finally` throwIO ObscureCleanupIssue
While `InformativeErrorMessage` got thrown, the user doesn't see it, since `ObscureCleanupIssue` is thrown instead. This causes a few issues:
1. If the exception is handled by the default handler and yielded to the user, then the more informative error is lost.
2. Callers who expect to catch the "Informative error message" won't run their handlers for this exception type.
Problem 1 can now easily be resolved by adding some info to the exception:
data ExceptionCause = ExceptionCause { unExceptionCause :: SomeException } deriving Typeable
instance ExceptionInfo ExceptionCause where displayExceptionInfo fe = "thrown while handling " ++ displayException (unExceptionCause fe)
catch :: Exception e => IO a -> (e -> IO a) -> IO a catch f g = f `oldCatch` handler where handler ex = g ex `oldCatch` \(ex' :: SomeException) -> throwIO (addExceptionInfo info ex') where info = ExceptionCause (toException ex)
This implementation of `catch` is written in a backwards-compatible way, such that the exception thrown during finalization is still the one that gets rethrown. The "original" exception is recorded in the added info. This is the same approach used by Python 3's `__context__` attribute[3]. This was brought to my attention in a post by Mike Meyer[4], in a thread about having bracket not suppress the original exception[5].
This doesn't directly resolve issue #2, due to this backwards compatibility. With the earlier example, a `catch` handler for `InformativeErrorMessage` won't be invoked, because it isn't the exception being rethrown. This can be resolved by having a variant of catch which instead throws the original exception. This might be a good default for finalization handlers like `bracket` and `finally`.
Asynchronous Exceptions -----------------------
Currently, the only reliable way to catch exceptions, ignoring async exceptions, is to fork a new thread. This is the approach used by the enclosed-exceptions[6] package. I think it's quite ugly that we need to go to such lengths due to the lack of one bit of information about the exception! This would resolve ghc trac #5902[7].
base-4.7 added the `SomeAsyncException` type, but this doesn't enforce anything. Any exception can be thrown as a sync or async exception. Instead, we ought to have a reliable way to know if an exception is synchronous or asynchronous. Here's what this would look like:
data IsAsync = IsAsync deriving (Typeable, Show)
instance ExceptionInfo IsAsync where displayExceptionInfo IsAsync = "thrown asynchronously"
throwTo :: Exception e => ThreadId -> e -> IO () throwTo tid = oldThrowTo tid . addExceptionInfo IsAsync
The details of this get a bit tricky: What happens if `throwIO` is used to rethrow a `SomeException` which has this `IsAsync` flag set? I'm going to leave out my thoughts on this for now as the interactions between unsafePerformIO and the concept of "rethrowing" async exceptions. Such details are explained in a post by Edsko de Vries[8] and ghc trac #2558[9].
Issue: fromException loses info ===============================
I can think of one main non-ideal aspect of this proposal:
Currently, the `toException` and `fromException` methods usually form a prism. In other words, when `fromException` yields a `Just`, you should get the same `SomeException` when using `toException` on that value.
For example,
fail "testing 1 2 3" `catch` \(ex :: SomeException) -> throwIO ex
is equivalent to
fail "testing 3 4 5" `catch` \(ex :: IOError) -> throwIO ex
However, with exception info added to just `SomeException`, and no changes to existing `Exception` instances, this doesn't hold. Exceptions caught as a specific exception type get rethrown with less information.
One resolution to this is be to add `[SomeExceptionInfo]` as a field to existing `Exception` instances. This would require the use of non-default implementations of the `toException` and `fromException` instances.
Another approach is to have variants of `catch` and `throw` which also pass around the `[SomeExceptionInfo]`.
[1] https://hackage.haskell.org/package/base-4.8.0.0/docs/GHC-Stack.html#current... [2] https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations [3] https://www.python.org/dev/peps/pep-3134/ [4] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114987.html [5] https://mail.haskell.org/pipermail/haskell-cafe/2014-July/114986.html [6] https://hackage.haskell.org/package/enclosed-exceptions [7] https://ghc.haskell.org/trac/ghc/ticket/5902 [8] http://www.edsko.net/2013/06/11/throwTo/ [9] https://ghc.haskell.org/trac/ghc/ticket/2558
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Michael Snoyman wrote:
Sorry to confuse this thread with a second Michael.
1) there's a very good use case that's currently excluded by the API, and (2) Michael Sloan figured out some great ways to minimize the breakage. You could even argue that this proposal has *no* API breakage.
Perhaps I missed it, but wouldn't this create major breakage across hackage for 7.8 and before? We will certainly be using 7.8 for years to come, at least for older versions of our products that we must continue to support. In fact, we are only now able to reduce our use of 7.6 to a fairly low (but non-zero) level. This cycle will likely be even longer than usual for the 7.10 upgrade due to the inclusion of the FTP breaking changes which make upgrading much more difficult. I certainly hope that most of the ecosystem will continue to support GHC versions going back at least one or two major versions, as it always has in the past. All that said, I am in favor of this change - it is a great design. But I would strongly oppose doing it immediately unless there is some plan to allow continued support of recent pre-7.10 GHC versions in the ecosystem. Thanks, Yitz ("you can call me Michael")

On Tue, Apr 21, 2015 at 12:05 PM Yitzchak Gale
Michael Snoyman wrote:
Sorry to confuse this thread with a second Michael.
1) there's a very good use case that's currently excluded by the API, and (2) Michael Sloan figured out some great ways to minimize the breakage. You could even argue that this proposal has *no* API breakage.
Perhaps I missed it, but wouldn't this create major breakage across hackage for 7.8 and before?
We will certainly be using 7.8 for years to come, at least for older versions of our products that we must continue to support. In fact, we are only now able to reduce our use of 7.6 to a fairly low (but non-zero) level.
This cycle will likely be even longer than usual for the 7.10 upgrade due to the inclusion of the FTP breaking changes which make upgrading much more difficult.
I certainly hope that most of the ecosystem will continue to support GHC versions going back at least one or two major versions, as it always has in the past.
All that said, I am in favor of this change - it is a great design. But I would strongly oppose doing it immediately unless there is some plan to allow continued support of recent pre-7.10 GHC versions in the ecosystem.
Thanks, Yitz ("you can call me Michael")
I may also be missing something here, but my read of Michael Sloan's proposal would mean that code written against the GHC 7.8/7.10 (and prior) API would continue to compile against GHC 7.12 and forward. It's true that code using the new functionality added in 7.12 would be unable to compile with 7.10 and earlier, but that's always the case when expanding the API (making this backwards compatible, or in PVP terms a minor version bump). The only catch here is that the proposal simulates the old API by using pattern synonyms. That means that the data types have in fact changed. But I'm so far unable to come up with an example that compiles with 7.8/7.10 but not with this new API (with the caveat that I'm no expert in pattern synonyms and therefore I may be misunderstanding something). I may also not be addressing what you're thinking of as the "major breakage." If so, can you clarify? Michael

Michael Snoyman wrote:
I may also be missing something here, but my read of Michael Sloan's proposal would mean that code written against the GHC 7.8/7.10 (and prior) API would continue to compile against GHC 7.12 and forward. It's true that code using the new functionality added in 7.12 would be unable to compile with 7.10 and earlier, but that's always the case when expanding the API (making this backwards compatible, or in PVP terms a minor version bump)...
I may also not be addressing what you're thinking of as the "major breakage." If so, can you clarify?
You're right, "major breakage" was not the right term. What's worrying me is that since so many libraries depend on exceptions, a sudden breaking change like this would prevent new versions of almost any library from being used with 7.8. So, for example, critical security fixes could not be applied. In short, it would make 7.8 very fragile or even unusable very quickly, which would indeed be "major breakage" for those of us who will be needing to use it for the medium term. Is there some way that backwards compatibility could somehow be achieved without the requirement of a new extension like PatternSynonyms, even though that might be the prettiest way? One obvious way would be to use a new name for the new SomeException, or perhaps just a different module name, and export only a smart constructor for the new type. That way there could be a compatibility library in which the smart constructor discards the ExceptionInfo and returns the old type. That would work going way back. Or perhaps something could be done with other fancier type features already present in 7.8, in a way that would then allow us to move to Michael Sl.'s nice PatternSynonym solution in 7.14. Thanks, Yitz

On Tue, Apr 21, 2015 at 3:48 PM Yitzchak Gale
I may also be missing something here, but my read of Michael Sloan's proposal would mean that code written against the GHC 7.8/7.10 (and
API would continue to compile against GHC 7.12 and forward. It's true
Michael Snoyman wrote: prior) that
code using the new functionality added in 7.12 would be unable to compile with 7.10 and earlier, but that's always the case when expanding the API (making this backwards compatible, or in PVP terms a minor version bump)...
I may also not be addressing what you're thinking of as the "major breakage." If so, can you clarify?
You're right, "major breakage" was not the right term.
What's worrying me is that since so many libraries depend on exceptions, a sudden breaking change like this would prevent new versions of almost any library from being used with 7.8. So, for example, critical security fixes could not be applied.
In short, it would make 7.8 very fragile or even unusable very quickly, which would indeed be "major breakage" for those of us who will be needing to use it for the medium term.
Is there some way that backwards compatibility could somehow be achieved without the requirement of a new extension like PatternSynonyms, even though that might be the prettiest way?
One obvious way would be to use a new name for the new SomeException, or perhaps just a different module name, and export only a smart constructor for the new type. That way there could be a compatibility library in which the smart constructor discards the ExceptionInfo and returns the old type. That would work going way back.
Or perhaps something could be done with other fancier type features already present in 7.8, in a way that would then allow us to move to Michael Sl.'s nice PatternSynonym solution in 7.14.
Thanks, Yitz
Can you give an example of a concrete problem you're expecting to run into? I'm not seeing it. End users aren't using pattern synonyms in this proposal, it's an implementation detail of Control.Exception. MIchael

Michael Snoyman wrote:
Can you give an example of a concrete problem you're expecting to run into?
Package foo uploads a new version with a critical bug fix. As is often the case, this new version also supports updated dependencies, including exceptions. The new exceptions breaks the old SomeException type, so foo is forced to specify a lower bound that excludes the old exceptions. I depend on foo and I need to compile using GHC 7.8. Can I get this critical bug fix for foo? We can't always prevent this kind of scenario. And when it does happen in an isolated case, there are work-arounds. But for a ubiquitous dependency like exceptions, this single breaking change would effectively block future upgrades of a significant proportion of Hackage for GHC 7.8.

On Tue, Apr 21, 2015 at 5:56 PM Yitzchak Gale
Michael Snoyman wrote:
Can you give an example of a concrete problem you're expecting to run into?
Package foo uploads a new version with a critical bug fix. As is often the case, this new version also supports updated dependencies, including exceptions. The new exceptions breaks the old SomeException type, so foo is forced to specify a lower bound that excludes the old exceptions.
But that's the scenario I'm asking for more information on. Can you clarify what you're describing here? I'm not seeing a situation where an author couldn't easily be compatible with GHC <=7.8 by sticking to the old API?
I depend on foo and I need to compile using GHC 7.8. Can I get this critical bug fix for foo?
We can't always prevent this kind of scenario. And when it does happen in an isolated case, there are work-arounds. But for a ubiquitous dependency like exceptions, this single breaking change would effectively block future upgrades of a significant proportion of Hackage for GHC 7.8.

I'm +1 on this proposal. On 21-04-2015 12:52, Michael Snoyman wrote:
On Tue, Apr 21, 2015 at 5:56 PM Yitzchak Gale
mailto:gale@sefer.org> wrote: Michael Snoyman wrote: > Can you give an example of a concrete problem you're > expecting to run into?
Package foo uploads a new version with a critical bug fix. As is often the case, this new version also supports updated dependencies, including exceptions. The new exceptions breaks the old SomeException type, so foo is forced to specify a lower bound that excludes the old exceptions.
But that's the scenario I'm asking for more information on. Can you clarify what you're describing here? I'm not seeing a situation where an author couldn't easily be compatible with GHC <=7.8 by sticking to the old API?
I think Michael Gale is thinking about an author that may end up using the new SomeExceptionWithInfo constructor for some reason, thus leaving older GHCs out of any new updates. However, IIUC, this would cause problems for GHC < 7.12, not only GHC < 7.10, since you won't be able to use GHC 7.12's base package on GHC 7.10. So perhaps I'm misunderstanding the issue as well. Cheers, -- Michael Lessa.

I wrote:
Package foo uploads a new version with a critical bug fix. As is often the case, this new version also supports updated dependencies, including exceptions. The new exceptions breaks the old SomeException type, so foo is forced to specify a lower bound that excludes the old exceptions.
Michael Snoyman wrote:
I'm not seeing a situation where an author couldn't easily be compatible with GHC <=7.8 by sticking to the old API?
Felipe Lessa wrote:
I think Michael Gale
heh
is thinking about an author that may end up using the new SomeExceptionWithInfo constructor for some reason, thus leaving older GHCs out of any new updates.
Right, exactly what I was thinking. But perhaps Michael Sn. is correct that explicit use of a SomeException constructor is rare. (Which is what I think is what he means by "sticking to the old API".) If that is really true, then my objection is not valid. And I'm certainly strongly in favor of the goals of this proposal. So I'd be in favor even if *some* breakage results from it, as long as the overall deprecation curve isn't unreasonably steep. Thanks, Yitz

On Thu, Apr 23, 2015 at 12:03 PM Yitzchak Gale
I wrote:
Package foo uploads a new version with a critical bug fix. As is often the case, this new version also supports updated dependencies, including exceptions. The new exceptions breaks the old SomeException type, so foo is forced to specify a lower bound that excludes the old exceptions.
Michael Snoyman wrote:
I'm not seeing a situation where an author couldn't easily be compatible with GHC <=7.8 by sticking to the old API?
Felipe Lessa wrote:
I think Michael Gale
heh
is thinking about an author that may end up using the new SomeExceptionWithInfo constructor for some reason, thus leaving older GHCs out of any new updates.
Right, exactly what I was thinking. But perhaps Michael Sn. is correct that explicit use of a SomeException constructor is rare. (Which is what I think is what he means by "sticking to the old API".) If that is really true, then my objection is not valid.
And I'm certainly strongly in favor of the goals of this proposal. So I'd be in favor even if *some* breakage results from it, as long as the overall deprecation curve isn't unreasonably steep.
Thanks, Yitz
Maybe we're on the same page, but just to be sure, I'd like to clarify: with Michael Sloan's proposal, you can still explicitly use the SomeException constructor. Under GHC <=7.10 it's just a normal data constructor. Under GHC >=7.12 it would be this pattern synonym thing (I really haven't looked into the extension yet). Meaning that anything you could do with GHC 7.10 and earlier could still be done with 7.12 without any breakage. Michael

On Tue, Apr 21, 2015 at 7:56 AM, Yitzchak Gale
Michael Snoyman wrote:
Can you give an example of a concrete problem you're expecting to run into?
Package foo uploads a new version with a critical bug fix. As is often the case, this new version also supports updated dependencies, including exceptions. The new exceptions breaks the old SomeException type, so foo is forced to specify a lower bound that excludes the old exceptions.
This only happens when a package depends on receiving or adding extra exception info. I don't think this will be necessary for most packages. The primary use-case I'm seeing for this extra exception info is being able to display it to the user. Since this will be done by 'displayException' / 'show' / the default exception handler, there's no need for user code to do anything special to get it. In the cases where we do have code that cares about this extra exception info, we would indeed be doing something that wasn't possible before, and so have issues with backwards compatibility. For example, when an exception is thrown while 'bracket' is handling an exception, it would be quite handy to be able to catch the original exception. This is simply not possible today, and so it is not possible to offer this in a way which works on earlier versions of base. I'd be quite concerned if this didn't offer some additional power that wasn't available before. Isn't that the point of changing things / adding such features?

On Tue, Apr 14, 2015 at 11:38 AM, Michael Sloan
data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
Is it necessary for SomeExceptionWithInfo to have a list of a forall data type? Are Exceptions really that mysterious, or can we more concretely describe the information that should be attached to an exception? SomeExceptionWithInfo e IsAsync CallStack ImplicitStack I am still open to the idea of adding a forall data scratchpad, but can we at least try to specify some standard fields? SomeExceptionWithInfo e IsAsync CallStack ImplicitStack [SomeExceptionInfo]

On Tue, Apr 21, 2015 at 8:23 AM, Greg Weber
On Tue, Apr 14, 2015 at 11:38 AM, Michael Sloan
wrote: data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
Is it necessary for SomeExceptionWithInfo to have a list of a forall data type? Are Exceptions really that mysterious, or can we more concretely describe the information that should be attached to an exception?
SomeExceptionWithInfo e IsAsync CallStack ImplicitStack
I did consider this option, but I think as soon as a fixed set is selected, someone's going to put something else in it. Usually we wouldn't want to use such a 'dynamic' mechanism in Haskell, but it's appropriate for something so global as the type used to throw exceptions.
I am still open to the idea of adding a forall data scratchpad, but can we at least try to specify some standard fields?
SomeExceptionWithInfo e IsAsync CallStack ImplicitStack [SomeExceptionInfo]
This is an interesting idea. I particularly see value in having 'IsAsync' be a part of the Exception. This is because `throwIO` / `throw` would need to set this to False when rethrowing async exceptions.

On Tue, Apr 21, 2015 at 1:55 PM, Michael Sloan
On Tue, Apr 21, 2015 at 8:23 AM, Greg Weber
wrote: On Tue, Apr 14, 2015 at 11:38 AM, Michael Sloan
wrote: data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
Is it necessary for SomeExceptionWithInfo to have a list of a forall data type? Are Exceptions really that mysterious, or can we more concretely describe the information that should be attached to an exception?
SomeExceptionWithInfo e IsAsync CallStack ImplicitStack
I did consider this option, but I think as soon as a fixed set is selected, someone's going to put something else in it. Usually we wouldn't want to use such a 'dynamic' mechanism in Haskell, but it's appropriate for something so global as the type used to throw exceptions.
The usual approach is to use information hiding. We are being rescued by pattern synonyms right now because the constructor is directly exported. Why not hide what needs to be hidden to make this more extensible and use smart constructors, etc?.
I am still open to the idea of adding a forall data scratchpad, but can we at least try to specify some standard fields?
SomeExceptionWithInfo e IsAsync CallStack ImplicitStack [SomeExceptionInfo]
This is an interesting idea. I particularly see value in having 'IsAsync' be a part of the Exception. This is because `throwIO` / `throw` would need to set this to False when rethrowing async exceptions.

Right, we have a choice between making a breaking change towards a more
standard API, or using a rather new language extension (bidirectional
pattern synonyms) to avoid breakage.
On Thu, Apr 23, 2015 at 6:30 AM, Greg Weber
On Tue, Apr 21, 2015 at 1:55 PM, Michael Sloan
wrote: On Tue, Apr 21, 2015 at 8:23 AM, Greg Weber
wrote: On Tue, Apr 14, 2015 at 11:38 AM, Michael Sloan
wrote: data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
Is it necessary for SomeExceptionWithInfo to have a list of a forall data type? Are Exceptions really that mysterious, or can we more concretely describe the information that should be attached to an exception?
SomeExceptionWithInfo e IsAsync CallStack ImplicitStack
I did consider this option, but I think as soon as a fixed set is selected, someone's going to put something else in it. Usually we wouldn't want to use such a 'dynamic' mechanism in Haskell, but it's appropriate for something so global as the type used to throw exceptions.
The usual approach is to use information hiding. We are being rescued by pattern synonyms right now because the constructor is directly exported. Why not hide what needs to be hidden to make this more extensible and use smart constructors, etc?.
I am still open to the idea of adding a forall data scratchpad, but can we at least try to specify some standard fields?
SomeExceptionWithInfo e IsAsync CallStack ImplicitStack [SomeExceptionInfo]
This is an interesting idea. I particularly see value in having 'IsAsync' be a part of the Exception. This is because `throwIO` / `throw` would need to set this to False when rethrowing async exceptions.

I have to confess that I don't really like this proposal in its current
form.
We use a little bit of Typeable magic in SomeException to model an open sum
type. It is more or less "just enough" to get us an open set of exceptions
on which we can match.
That gives us a nice case analysis construction, we can basically reason
type by type and ask if SomeException _is_ a particular data type without
losing any information.
Theoretically it means I can give you a nice prism or case handler for it,
match on it, rethrow it and nothing is lost.
This proposal gives up a very nice property in exchange for an ad hoc
ability to decorate exceptions with anything we want. This strikes me as a
short term gain in exchange for giving up a lot of future reasoning power.
What is your exception decorated with? Go spend O(n) time rummaging through
the list of attached decorations to find out! =/
I'm not offering a concrete worked solution, but there are many other
points in this design space. e.g. having a class to let you attach the
particular information you want to particular exceptions, having an
exception type you can throw with a stack intact that acts as an exception
transformer, etc.
None of those require us to give up the simplicity of the open exceptions,
but those first two obvious directions have obvious drawbacks, hence why
"I'm not offering a concrete worked solution."
Davean's variant narrows the focus down considerably. Limiting it to just
the issue at hand, rather than trying to construct a solution to all sorts
of problems we haven't even thought of yet. I could get behind something
with a more retrenched scope, like that.
That said, I'd very much rather err on the side of doing nothing rather
than do the wrong thing here.
We'll be stuck with it for a long time.
-Edward
On Sun, Apr 26, 2015 at 4:26 PM, Michael Sloan
Right, we have a choice between making a breaking change towards a more standard API, or using a rather new language extension (bidirectional pattern synonyms) to avoid breakage.
On Thu, Apr 23, 2015 at 6:30 AM, Greg Weber
wrote: On Tue, Apr 21, 2015 at 1:55 PM, Michael Sloan
wrote: On Tue, Apr 21, 2015 at 8:23 AM, Greg Weber
wrote: On Tue, Apr 14, 2015 at 11:38 AM, Michael Sloan
wrote: data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
Is it necessary for SomeExceptionWithInfo to have a list of a forall data type? Are Exceptions really that mysterious, or can we more concretely describe the information that should be attached to an exception?
SomeExceptionWithInfo e IsAsync CallStack ImplicitStack
I did consider this option, but I think as soon as a fixed set is selected, someone's going to put something else in it. Usually we wouldn't want to use such a 'dynamic' mechanism in Haskell, but it's appropriate for something so global as the type used to throw exceptions.
The usual approach is to use information hiding. We are being rescued by pattern synonyms right now because the constructor is directly exported. Why not hide what needs to be hidden to make this more extensible and use smart constructors, etc?.
I am still open to the idea of adding a forall data scratchpad, but can we at least try to specify some standard fields?
SomeExceptionWithInfo e IsAsync CallStack ImplicitStack [SomeExceptionInfo]
This is an interesting idea. I particularly see value in having 'IsAsync' be a part of the Exception. This is because `throwIO` / `throw` would need to set this to False when rethrowing async exceptions.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Sun, Apr 26, 2015 at 2:37 PM, Edward Kmett
I have to confess that I don't really like this proposal in its current form.
We use a little bit of Typeable magic in SomeException to model an open sum type. It is more or less "just enough" to get us an open set of exceptions on which we can match.
That gives us a nice case analysis construction, we can basically reason type by type and ask if SomeException _is_ a particular data type without losing any information.
Theoretically it means I can give you a nice prism or case handler for it, match on it, rethrow it and nothing is lost.
This proposal gives up a very nice property in exchange for an ad hoc ability to decorate exceptions with anything we want. This strikes me as a short term gain in exchange for giving up a lot of future reasoning power. What is your exception decorated with? Go spend O(n) time rummaging through the list of attached decorations to find out! =/
Yep, I agree that giving up this property sucks. It's discussed at the end of the proposal. Rummaging through the list of decorations also sucks. My reasoning for that being acceptable is that if these annotations are used primarily for diagnostic purposes, then performance isn't so crucial. I'm not offering a concrete worked solution, but there are many other
points in this design space. e.g. having a class to let you attach the particular information you want to particular exceptions, having an exception type you can throw with a stack intact that acts as an exception transformer, etc.
None of those require us to give up the simplicity of the open exceptions, but those first two obvious directions have obvious drawbacks, hence why "I'm not offering a concrete worked solution."
Davean's variant narrows the focus down considerably. Limiting it to just the issue at hand, rather than trying to construct a solution to all sorts of problems we haven't even thought of yet. I could get behind something with a more retrenched scope, like that.
To me, whether we use closed or open datatypes is tertiary to the main issue of how info gets associated with exceptions. If the main issue with my proposal is the breakage of the information preservation of `fromException`, as far as I can tell, that is not addressed by Davean's proposal. So, the narrowing of scope bought us nothing but having simpler types to talk about. One thing to note is that `fromException` does not guarantee preservation of information. So, this only breaks an informal property, not one that is documented. Admittedly, it's one that people are used to relying on.
That said, I'd very much rather err on the side of doing nothing rather than do the wrong thing here.
We'll be stuck with it for a long time.
Yes, such core changes should be made with great care. I hesitated to post the proposal due to this, but was hoping that a more palatable, backwards compatible solution would come up in discussion. While I don't want to get stuck with a bad API, I also don't want to be stuck with uninformative exceptions. The new parts of the API can be stuck in an "Internal" module, and marked specifically for debugging purposes only. This way, base reserves the right to revert this particular API choice if a better option comes along. Personally, I want callstacks for every exception thrown, and that's what this proposal provides.
-Edward
On Sun, Apr 26, 2015 at 4:26 PM, Michael Sloan
wrote: Right, we have a choice between making a breaking change towards a more standard API, or using a rather new language extension (bidirectional pattern synonyms) to avoid breakage.
On Thu, Apr 23, 2015 at 6:30 AM, Greg Weber
wrote: On Tue, Apr 21, 2015 at 1:55 PM, Michael Sloan
wrote: On Tue, Apr 21, 2015 at 8:23 AM, Greg Weber
wrote: On Tue, Apr 14, 2015 at 11:38 AM, Michael Sloan
wrote: data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
Is it necessary for SomeExceptionWithInfo to have a list of a forall data type? Are Exceptions really that mysterious, or can we more concretely describe the information that should be attached to an exception?
SomeExceptionWithInfo e IsAsync CallStack ImplicitStack
I did consider this option, but I think as soon as a fixed set is selected, someone's going to put something else in it. Usually we wouldn't want to use such a 'dynamic' mechanism in Haskell, but it's appropriate for something so global as the type used to throw exceptions.
The usual approach is to use information hiding. We are being rescued by pattern synonyms right now because the constructor is directly exported. Why not hide what needs to be hidden to make this more extensible and use smart constructors, etc?.
I am still open to the idea of adding a forall data scratchpad, but can we at least try to specify some standard fields?
SomeExceptionWithInfo e IsAsync CallStack ImplicitStack [SomeExceptionInfo]
This is an interesting idea. I particularly see value in having 'IsAsync' be a part of the Exception. This is because `throwIO` / `throw` would need to set this to False when rethrowing async exceptions.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Here is an idea to cut though a lot of the confusion in this discussion. It seems to me that _all_ ideas under discussion can be written as libraries, external to the RTS and external to GHC base. Of course, this means that all the functions in base won’t take advantage of these ideas, and won’t throw exceptions with any additional info. However, it should be the case that we can take e.g. Michael’s proposal, turn it into an experimental library, including exports of a few key base functions but now using this new exception approach, and just toss it on hackage. At that point, people can download and experiment with it, or attempt to modify it and hack on it to try out some variations. This isn’t the same as trying it all out _in base_ but it will let people experiment with various approaches, and come to a clearer conclusion on what the tradeoffs are. After some time where people can try the various approaches as experiments, we can revisit a discussion on which, if any, should move into the default base implementation. —Gershom On April 26, 2015 at 7:45:37 PM, John Wiegley (johnw@newartisans.com) wrote:
Edward Kmett writes:
That said, I'd very much rather err on the side of doing nothing rather than do the wrong thing here.
We'll be stuck with it for a long time.
I agree with Edward's sentiments.
John _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Mon, Apr 27, 2015 at 2:03 AM, Gershom B
However, it should be the case that we can take e.g. Michael’s proposal, turn it into an experimental library, including exports of a few key base functions but now using this new exception approach, and just toss it on hackage. At that point, people can download and experiment with it, or attempt to modify it and hack on it to try out some variations. This isn’t the same as trying it all out _in base_ but it will let people experiment with various approaches, and come to a clearer conclusion on what the tradeoffs are. After some time where people can try the various approaches as experiments, we can revisit a discussion on which, if any, should move into the default base implementation.
Maybe include an alternative Prelude, (mostly?) compatible with the base one but using the new functions. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Sun, Apr 26, 2015 at 1:26 PM, Michael Sloan
Right, we have a choice between making a breaking change towards a more standard API, or using a rather new language extension (bidirectional pattern synonyms) to avoid breakage.
That is not what I was trying to get at in my feedback. Using pattern synonyms to maintain backwards compatibility with the current form is independent of what many variations of the new form look like.
On Thu, Apr 23, 2015 at 6:30 AM, Greg Weber
wrote: On Tue, Apr 21, 2015 at 1:55 PM, Michael Sloan
wrote: On Tue, Apr 21, 2015 at 8:23 AM, Greg Weber
wrote: On Tue, Apr 14, 2015 at 11:38 AM, Michael Sloan
wrote: data SomeException = forall e . Exception e => SomeExceptionWithInfo e [SomeExceptionInfo]
data SomeExceptionInfo = forall a . ExceptionInfo a => SomeExceptionInfo a
Is it necessary for SomeExceptionWithInfo to have a list of a forall data type? Are Exceptions really that mysterious, or can we more concretely describe the information that should be attached to an exception?
SomeExceptionWithInfo e IsAsync CallStack ImplicitStack
I did consider this option, but I think as soon as a fixed set is selected, someone's going to put something else in it. Usually we wouldn't want to use such a 'dynamic' mechanism in Haskell, but it's appropriate for something so global as the type used to throw exceptions.
The usual approach is to use information hiding. We are being rescued by pattern synonyms right now because the constructor is directly exported. Why not hide what needs to be hidden to make this more extensible and use smart constructors, etc?.
I am still open to the idea of adding a forall data scratchpad, but can we at least try to specify some standard fields?
SomeExceptionWithInfo e IsAsync CallStack ImplicitStack [SomeExceptionInfo]
This is an interesting idea. I particularly see value in having 'IsAsync' be a part of the Exception. This is because `throwIO` / `throw` would need to set this to False when rethrowing async exceptions.
participants (13)
-
Brandon Allbery
-
Carter Schonwald
-
davean
-
Edward Kmett
-
Evan Laforge
-
Felipe Lessa
-
Gershom B
-
Greg Weber
-
John Lato
-
John Wiegley
-
Michael Sloan
-
Michael Snoyman
-
Yitzchak Gale