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