Exceptions with Context Re: Proposal: Add exception info

Carter Schonwald carter.schonwald at gmail.com
Sun Apr 26 23:57:05 UTC 2015


no, the idea / premise is there'd be a new "throwWithCallStack" and or
"throwWithExtraInfo"

the POINT here is there no point in doing changes to exception machinery
UNTIL those various new stack trace pieces ÅRE PRESENT.

:)

On Sun, Apr 26, 2015 at 7:52 PM, Michael Sloan <mgsloan at gmail.com> wrote:

> So, based on discussion in IRC, it's clear that with Davean's proposal the
> thrower would need to call a function which does something like:
>
>     stack <- currentCallStack
>     throwIO (WithStack stack e)
>
> However, this requires that every thrower change their code if they want
> to provide callstacks.  Moreover, every exception handler that wants to
> handle this exception would need to change as well.  This would be a
> breaking API change for every library that adds support for callstacks.
> Perhaps this is our only viable option..
>
> With my proposal, we can have every use of throw provide a callstack, but
> lose the information preservation of fromException.
>
> -Michael
>
> On Tue, Apr 21, 2015 at 9:08 PM, Carter Schonwald <
> carter.schonwald at gmail.com> wrote:
>
>> no michael, Daveans proposal is that we add certain catchWithExtraInfo ::
>> Exception e => IO a -> (ExtraInfo  -> e -> IO a ) -> IO a style operations
>> to the exceptions modules, for various choices  of "extraInfo"
>>
>> The idea being, NO current exception codes should have to change. Nor
>> does SomeException need to change.
>> i will try to articulate my concerns about your proposed design in more
>> details on the other proposal thread after i've had a bit more sleep and
>> thought about it more
>>
>>
>> On Tue, Apr 21, 2015 at 11:50 PM, Michael Sloan <mgsloan at gmail.com>
>> wrote:
>>
>>> Either I am misunderstanding davean's proposal, or you are
>>> misunderstanding mine.  Namely:
>>>
>>> * How is his proposal more extensible?  His specializes it to just
>>> passing callstack information.
>>>
>>> * I'm not sure exactly how he proposes to change the catch.  If it's
>>> changed to always preserve the extra exception info, then this will be a
>>> massive API breakage.
>>>
>>> -Michael
>>>
>>> On Tue, Apr 21, 2015 at 7:23 PM, Carter Schonwald <
>>> carter.schonwald at gmail.com> wrote:
>>>
>>>> hrm,  i like this proposal more, and it seems like with some fleshing
>>>> out it can be strictly more extensible yet backwards compatible than
>>>> michael's
>>>>
>>>> I'll need to mull it a bit more before I cast my vote, but this seems
>>>> to sketch out a design that provides the same information, but in a more
>>>> extensible/backwards compatible fashion (at least in a first cut of
>>>> thinking about it)
>>>>
>>>> (i'm splitting this into a new thread so the discussions dont get mixed
>>>> up)
>>>>
>>>> On Tue, Apr 21, 2015 at 9:40 PM, davean <davean at xkcd.com> wrote:
>>>>
>>>>> 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.html#AssertionFailed>.
>>>>> 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-Conduit.html#g:12
>>>>> 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 <mgsloan at gmail.com>
>>>>> 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 at 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 <mgsloan at gmail.com> 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 <mgsloan at 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 <qdunkan at gmail.com>
>>>>>>>>> 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 <mgsloan at gmail.com>
>>>>>>>>>> wrote:
>>>>>>>>>> > On Thu, Apr 16, 2015 at 8:08 PM, Carter Schonwald
>>>>>>>>>> > <carter.schonwald at 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 <
>>>>>>>>>> mgsloan at 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
>>>>>>>>>> >>> <carter.schonwald at 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 <
>>>>>>>>>> mgsloan at 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#currentCallStack
>>>>>>>>>> >>>>> [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 at haskell.org
>>>>>>>>>> >>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>>>>>>>>>> >>>>>
>>>>>>>>>> >>>>
>>>>>>>>>> >>>
>>>>>>>>>> >>
>>>>>>>>>> >
>>>>>>>>>> >
>>>>>>>>>> > _______________________________________________
>>>>>>>>>> > Libraries mailing list
>>>>>>>>>> > Libraries at haskell.org
>>>>>>>>>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>>>>>>>>>> >
>>>>>>>>>>
>>>>>>>>>
>>>>>>>>>
>>>>>>>>
>>>>>>
>>>>>> _______________________________________________
>>>>>> Libraries mailing list
>>>>>> Libraries at haskell.org
>>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>>>>>>
>>>>>>
>>>>>
>>>>
>>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20150426/3828caf7/attachment-0001.html>


More information about the Libraries mailing list