Re: [Haskell-cafe] Decorating exceptions with backtrace information

2020-05-14 Thread Tyson Whitehead
On Tue, 12 May 2020 at 17:30, Henning Thielemann <
lemm...@henning-thielemann.de> wrote:

> From your list of examples I deduce that the proposal is about programming
> errors. But we have HasCallStack for that one. How does the proposal
> improve or alter the HasCallStack solution? And how does it relate to the
> IO exception system with hierarchical exceptions and SomeException and so
> on?
>

As a parallel item, maybe it would be good if incomplete patterns could
have a HasCallStack constraint so the current "Non-exaustive patterns in
function foo" message could be extended with a helpful backtrace? If a
programmer doesn't want this, then they could use complete matches?
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [Haskell-cafe] Decorating exceptions with backtrace information

2020-05-13 Thread Ben Franksen
Am 12.05.20 um 23:29 schrieb Henning Thielemann:
> A stack overflow sounds like unlimited recursion and thus like a
> programming error.

Perhaps it was just one recursion to many? Computer memory is limited.
Heap overflow is also quite possible even with a program that is
provably terminating. I have used 'ulimit -v' in the past to force ghc
to fail rather than having to reboot my machine :-/

> In contrast to that, a program must be prepared for a
> failure of "malloc".

I don't see any essential difference between allocation by the runtime
and explicit allocation using malloc. I think this is a good thing that
in Haskell you /can/ recover from such a condition.

> Memory exhaustion is an IO exception, it should be
> explicit in the type.

Then it must be explicit in all types, since in general all computations
may exhaust the available memory. And then what use would that type
information have?

> Are MVar deadlocks always detected by the runtime system?

My guess is that deadlock detection in general is undecidable i.e. with
more than one MVar present, but I may be wrong about that.

Cheers
Ben

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [Haskell-cafe] Decorating exceptions with backtrace information

2020-05-12 Thread Niklas Hambüchen
On 5/12/20 10:55 PM, Henning Thielemann wrote:
> "This operation may fail with:
> 
> * ResourceVanished if the handle is a pipe or socket, and the reading end is 
> closed."
> 
> That is, ResourceVanished is part of the public interface and in no way 
> unexpected (or what "unintended" may be). I would prefer to make this 
> explicit in the type of hPutBuf:
> 
> hPutBuf ::
>    (ResourceVanishedException e) =>
>    Handle -> Ptr a -> Int -> ExceptT e IO ()
> 
> Now, what do you intend to do with the call-stack? Isn't it something you can 
> attach to the e value?

Why is this relevant?

The point of debugging is to find programming errors.
It does not matter what the Haddocks say; if a programmer uses the function 
wrong, the exception will occur.

hPutBuf does not currently have that type, nor can anybody rewrite all the 
existing libraries easily.

The point of the proposal is to make the RTS help us debug problems in code as 
it exists today.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [Haskell-cafe] Decorating exceptions with backtrace information

2020-05-12 Thread Henning Thielemann


On Fri, 8 May 2020, Ben Gamari wrote:


Henning Thielemann  writes:


We are talking about the HasCallStack stack traces, yes?
How is their emission addressed by extending exceptions with stack
traces?


HasCallStack stack traces are one type of backtrace that the proposal
supports. However, it's not the only (nor is it even the most useful
sort, in my opinion).

Other mechanisms include cost center stacks from the cost-center
profiler and native stack unwinding.



Interesting. That's a completely new thing.



* Developers cannot easily produce stack traces do debug unintended
exceptions.


What are "unintended exceptions"?
What is an example of an "unintended exception"?


For instance,

* Somewhere deep in my code a colleague used `fromJust` due to a
  miscommunicated invariant


That's a programming error.


* Somewhere in my system a `writeFile "tmp" $ repeat 'a'` failed due to
  filling the disk


Hm, that's also a programming error, but it ends in an IO exception. If it 
would not end in an IO exception (e.g. writing to /dev/null) it would go 
to an infinite loop. Anyway, it is a programming error. However it is an 
unchecked one. That is, there is no warranty that you can catch it by a 
debugger. So I do not think you can achieve much with callstacks here.



* Somewhere in my system I have a partial pattern match in a module
  which was compiled without -Wall


Programming error and btw. before thinking about a GHC extension I would 
enable -Wall ...



* Somewhere in my system I `div` by zero due to lack of input
  validation


Programming error


* I use a record selector on a sum.


Programming error


* A logic error results in an assertion failure deep in my program, but
  it's unclear which path my program took to arrive at the assertion


Sounds like Programming error



This list could go on and on...


From your list of examples I deduce that the proposal is about programming 
errors. But we have HasCallStack for that one. How does the proposal 
improve or alter the HasCallStack solution? And how does it relate to the 
IO exception system with hierarchical exceptions and SomeException and so 
on?




Currently the proposal does not cover asynchronous exceptions but it
wouldn't be particularly hard to extend it in this direction. This would
allow far better reporting of heap/stack overflows and MVar deadlocks
(which are particularly hard to debug at the moment).


Hm, what kind of heap or stack overflow are you thinking of?

A stack overflow sounds like unlimited recursion and thus like a 
programming error. In contrast to that, a program must be prepared for a 
failure of "malloc". Memory exhaustion is an IO exception, it should be 
explicit in the type.


Are MVar deadlocks always detected by the runtime system?
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [Haskell-cafe] Decorating exceptions with backtrace information

2020-05-12 Thread Henning Thielemann


On Fri, 8 May 2020, Ben Gamari wrote:


We can debate whether partial functions like `fromJust` should exist; however,
the fact of the matter is that they do exist and they are used.


That's not my point. I say: fromJust on Nothing is a programming error, 
ok. We must debug this. HasCallStack helps here. However, it does not have 
to do with exceptions or with the proposals as I understand them.



Furthermore, even `base`'s own IO library (e.g. `openFile`) uses
synchronous exceptions to report errors.


Right. I say: Such exceptions are part of the public interface and should 
be expressed in types. If you encounter any problems when not doing this, 
I would first try to solve the problem with exceptions explicit in the 
type. E.g. Haddock for openFile says:


This operation may fail with:

* isAlreadyInUseError ...
* isDoesNotExistError ...
* isPermissionError ...

Thus the type should be:

openFile ::
   (AlreadyInUseException e,
DoesNotExistException e,
PermissionException e) =>
   FilePath -> IOMode -> ExceptT e IO Handle



Perhaps this helps to shed some light on the motivation?


Unfortunately no. I only see the immortal confusion about (programming) 
errors vs. (IO) exceptions. And I think that part of this confusion is 
that IO exceptions in 'base' are hidden in the IO type and that there are 
hybrid functions like 'throw' that can be called like 'error' but they 
cause IO exceptions that can be caught by 'catch'.

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [Haskell-cafe] Decorating exceptions with backtrace information

2020-05-12 Thread Henning Thielemann


On Fri, 8 May 2020, Niklas Hambüchen wrote:


What are "unintended exceptions"?
What is an example of an "unintended exception"?


A recent example from my production server:

   hPutBuf: resource vanished (Broken pipe)



Ok, I lookup the Haddock comment of hPutBuf and it says:

"This operation may fail with:

* ResourceVanished if the handle is a pipe or socket, and the reading end 
is closed."


That is, ResourceVanished is part of the public interface and in no way 
unexpected (or what "unintended" may be). I would prefer to make this 
explicit in the type of hPutBuf:


hPutBuf ::
   (ResourceVanishedException e) =>
   Handle -> Ptr a -> Int -> ExceptT e IO ()

Now, what do you intend to do with the call-stack? Isn't it something you 
can attach to the e value?___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Decorating exceptions with backtrace information

2020-05-11 Thread Ben Gamari
Michael Sloan  writes:

> Thanks so much for making a proposal for this, Ben!!  It's great to see
> progress here.
>
> I'm also glad that there is now a proposal process.  I made a fairly
> similar proposal almost exactly 5 years ago to the libraries list -
> https://mail.haskell.org/pipermail/libraries/2015-April/025471.html - but
> without the subtlety of particular backtrace representations.  Skimming the
> ensuing thread may still be informative.
>
Thanks for the reference, Michael! My feeling is that the proposal in
that thread is a bit too dynamic. That being said, I can see the
argument for wanting, for instance, a robust way to determine that an
exception is asynchronous.

> In particular, there is one thing I would like to highlight from that old
> proposal.  I think it'd be good to have a standard way to represent a chain
> of exceptions, and build this into `catch` and `finally`.  Python and Java
> both have a mechanism for this, and both refer to it as a "cause"
> exception.  When an exception is thrown during exception handling, the
> exception being handled is preserved as its "cause".  I find this mechanism
> to be incredibly useful in Java, it has made the underlying issue much
> clearer in many cases, and in other cases at least provides helpful
> context.  I have no doubt such a mechanism would have saved me many hours
> of debugging exceptions in Haskell systems I've worked on in the past.
>
> I considered commenting about that directly on the proposal, but I figure
> this is a better place to suggest expanding the scope of the change :) .
> Totally understandable if you want to keep this proposal focused on
> stacktraces, but I think it'd be good to consider this as a potential
> future improvement.
>
Indeed I can see the point. I'll keep this point in the back of my mind.
I'm not eager to further expand the scope of the proposal at the moment,
but we should be certain that the backtrace design doesn't
unintentionally close the door to this use-case.

However, one question I would have is whether the exception-chaining
use-case *needs* to be handled in SomeException. For instance, you could
rather leave this to user code. You might even give this pattern a
typeclass. For instance,

class HasChainedException e where
getChainedException :: e -> Maybe SomeException

data MyException = MyException { causedBy :: SomeException }

instance HasChainedException MyException where
getChainedException = causedBy

Cheers,

- Ben


signature.asc
Description: PGP signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [Haskell-cafe] Decorating exceptions with backtrace information

2020-05-09 Thread Michal J Gajda
Ben,
I agree with you that is a great idea!

I can add a few more real world examples:
* we get exception from a foreign library that we bound,
* we get an exception from a platform (I believe Windows supports
throwing exceptions to programs),
* user presses CTRL-C and we want to know where our program hanged.
* we get infamous <>, because in theory nobody wants
non-terminating programs, but in practice everybody gets them
sometimes.

I also use `ExceptT`, `EitherT` for processing large sets of data,
because that allows me to contain the errors efficiently. However from
time to time, I get an error to blow up **and I cannot even locate
which library was guilty**. It would be nice to extract them
automatically and put them into error database before they are
prioritized.
-- 
  Cheers
Michał
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [Haskell-cafe] Decorating exceptions with backtrace information

2020-05-09 Thread Compl Yue
This reminds me a joke to put it in a humorous way:

> A software QA engineer walks into a bar. He orders a beer. Orders 0 beers. 
> Orders 999 beers. Orders a lizard. Orders -1 beers.
> First real customer walks in and asks where the bathroom is. The bar bursts 
> into flames, killing everyone.

LOL,
Compl

> On 2020-05-09, at 02:18, Ben Gamari  wrote:
> 
> Henning Thielemann  writes:
> 
>> On Fri, 8 May 2020, Niklas Hambüchen wrote:
>> 
>>> On 5/8/20 7:32 PM, Henning Thielemann wrote:
>>> 
 Can someone please give me examples where current state lacks
>>> 
>>> * Currently stack traces are not printed, so users cannot forward them 
>>> to the developer, even if both the users and the developers would like 
>>> that.
>> 
>> We are talking about the HasCallStack stack traces, yes?
>> How is their emission addressed by extending exceptions with stack
>> traces?
> 
> HasCallStack stack traces are one type of backtrace that the proposal
> supports. However, it's not the only (nor is it even the most useful
> sort, in my opinion).
> 
> Other mechanisms include cost center stacks from the cost-center
> profiler and native stack unwinding.
> 
>> 
>>> * Developers cannot easily produce stack traces do debug unintended 
>>> exceptions.
>> 
>> What are "unintended exceptions"?
>> What is an example of an "unintended exception"?
> 
> For instance,
> 
> * Somewhere deep in my code a colleague used `fromJust` due to a
>   miscommunicated invariant
> 
> * Somewhere in my system a `writeFile "tmp" $ repeat 'a'` failed due to
>   filling the disk
> 
> * Somewhere in my system I have a partial pattern match in a module
>   which was compiled without -Wall
> 
> * Somewhere in my system I `div` by zero due to lack of input
>   validation
> 
> * I use a record selector on a sum.
> 
> * A logic error results in an assertion failure deep in my program, but
>   it's unclear which path my program took to arrive at the assertion
> 
> This list could go on and on...
> 
> Currently the proposal does not cover asynchronous exceptions but it
> wouldn't be particularly hard to extend it in this direction. This would
> allow far better reporting of heap/stack overflows and MVar deadlocks
> (which are particularly hard to debug at the moment).
> 
> Cheers,
> 
> - Ben
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [Haskell-cafe] Decorating exceptions with backtrace information

2020-05-08 Thread Ben Gamari
Henning Thielemann  writes:

> On Fri, 8 May 2020, Niklas Hambüchen wrote:
>
>> On 5/8/20 7:32 PM, Henning Thielemann wrote:
>>
>>> Can someone please give me examples where current state lacks
>>
>> * Currently stack traces are not printed, so users cannot forward them 
>> to the developer, even if both the users and the developers would like 
>> that.
>
> We are talking about the HasCallStack stack traces, yes?
> How is their emission addressed by extending exceptions with stack
> traces?

HasCallStack stack traces are one type of backtrace that the proposal
supports. However, it's not the only (nor is it even the most useful
sort, in my opinion).

Other mechanisms include cost center stacks from the cost-center
profiler and native stack unwinding.

>
>> * Developers cannot easily produce stack traces do debug unintended 
>> exceptions.
>
> What are "unintended exceptions"?
> What is an example of an "unintended exception"?

For instance,

 * Somewhere deep in my code a colleague used `fromJust` due to a
   miscommunicated invariant

 * Somewhere in my system a `writeFile "tmp" $ repeat 'a'` failed due to
   filling the disk

 * Somewhere in my system I have a partial pattern match in a module
   which was compiled without -Wall

 * Somewhere in my system I `div` by zero due to lack of input
   validation

 * I use a record selector on a sum.

 * A logic error results in an assertion failure deep in my program, but
   it's unclear which path my program took to arrive at the assertion

This list could go on and on...

Currently the proposal does not cover asynchronous exceptions but it
wouldn't be particularly hard to extend it in this direction. This would
allow far better reporting of heap/stack overflows and MVar deadlocks
(which are particularly hard to debug at the moment).

Cheers,

- Ben


signature.asc
Description: PGP signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [Haskell-cafe] Decorating exceptions with backtrace information

2020-05-08 Thread Ben Gamari
Henning Thielemann  writes:

> On Fri, 8 May 2020, Niklas Hambüchen wrote:
>
>> On 5/8/20 5:37 PM, Henning Thielemann wrote:
>>
>>> a callstack is not useful for a user.
>>
>> Call stacks have been very useful to me as a user of non-Haskell tools 
>> so far, because they are excellent for attaching to bug reports and 
>> usually led to developers fixing my problems faster.
>
> This confirms that they are not for you, but you only forward them to the 
> developer.
>
>
> Can someone please give me examples where current state lacks and how they 
> are addressed by the proposal(s)?

We can debate whether partial functions like `fromJust` should exist; however,
the fact of the matter is that they do exist and they are used.
Furthermore, even `base`'s own IO library (e.g. `openFile`) uses
synchronous exceptions to report errors.

This becomes particularly painful when building large systems:
Even if I am careful to avoid such functions in my own code, as my
dependency footprint grows it becomes more likely that some transitive
dependency will expose a partial interface (perhaps even without my
knowledge). This is a problem that industrial users are all too familiar
with.

Perhaps this helps to shed some light on the motivation?

Cheers,

- Ben


signature.asc
Description: PGP signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [Haskell-cafe] Decorating exceptions with backtrace information

2020-05-08 Thread Niklas Hambüchen
On 5/8/20 7:52 PM, Henning Thielemann wrote:
> We are talking about the HasCallStack stack traces, yes?
> How is their emission addressed by extending exceptions with stack traces?

The way I understand the proposal, we may be equally talking about DWARF or 
profiling cost-center based stack traces.
From a debugging perspective, I guess the developer does not care so much about 
which implementation is used, as long as the trace points out the code path 
that led to the creation of the exception.

> What are "unintended exceptions"?
> What is an example of an "unintended exception"?

A recent example from my production server:

hPutBuf: resource vanished (Broken pipe)

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [Haskell-cafe] Decorating exceptions with backtrace information

2020-05-08 Thread Henning Thielemann


On Fri, 8 May 2020, Niklas Hambüchen wrote:


On 5/8/20 7:32 PM, Henning Thielemann wrote:


Can someone please give me examples where current state lacks


* Currently stack traces are not printed, so users cannot forward them 
to the developer, even if both the users and the developers would like 
that.


We are talking about the HasCallStack stack traces, yes?
How is their emission addressed by extending exceptions with stack traces?

* Developers cannot easily produce stack traces do debug unintended 
exceptions.


What are "unintended exceptions"?
What is an example of an "unintended exception"?___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [Haskell-cafe] Decorating exceptions with backtrace information

2020-05-08 Thread Niklas Hambüchen
On 5/8/20 7:32 PM, Henning Thielemann wrote:
> This confirms that they are not for you, but you only forward them to the 
> developer.

Yes, stack traces are in general for developers.

> Can someone please give me examples where current state lacks

* Currently stack traces are not printed, so users cannot forward them to the 
developer, even if both the users and the developers would like that.
* Developers cannot easily produce stack traces do debug unintended exceptions.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [Haskell-cafe] Decorating exceptions with backtrace information

2020-05-08 Thread Henning Thielemann


On Fri, 8 May 2020, Niklas Hambüchen wrote:


On 5/8/20 5:37 PM, Henning Thielemann wrote:


a callstack is not useful for a user.


Call stacks have been very useful to me as a user of non-Haskell tools 
so far, because they are excellent for attaching to bug reports and 
usually led to developers fixing my problems faster.


This confirms that they are not for you, but you only forward them to the 
developer.



Can someone please give me examples where current state lacks and how they 
are addressed by the proposal(s)?___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [Haskell-cafe] Decorating exceptions with backtrace information

2020-05-08 Thread Niklas Hambüchen
On 5/8/20 5:37 PM, Henning Thielemann wrote:
> I can imagine that it would be helpful for the user to get a stacked 
> exception information like:
>    Parse error on line 42, column 23
>    while reading file "foo/bar"
>    while traversing directory "blabla"

That seems to be rather specific use case.
It'd be a cool feature but I'm not aware of any programming language following 
that interpretation so far.

I personally would be happy to be able to get the same type of stack trace for 
exceptions as in other programming langues (and as the proposal suggests).

> If you must debug exceptions, then this sounds like exceptions were abused 
> for programming errors.

I'd be pretty happy to be able to debug them better; no matter if they were 
"abused" for anything or not, I must still debug them in practice.

Given that they traverse program flow invisibly (e.g. not lexically, like 
return values) and can become visible in different places than they arose, 
having a call stack to debug their creation would be useful.

> a callstack is not useful for a user.

Call stacks have been very useful to me as a user of non-Haskell tools so far, 
because they are excellent for attaching to bug reports and usually led to 
developers fixing my problems faster.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [Haskell-cafe] Decorating exceptions with backtrace information

2020-05-08 Thread Henning Thielemann


There seem to be multiple beginnings of the discussion. What is currently 
discussed?


If someone says "exceptions" and "backtrace" in one sentence, I suspect 
like many times before, that again confusion of the concepts of exceptions 
and errors is ahead. Errors already support call stacks. Why should 
exceptions get them, too? Exceptions should carry information that is 
useful for a user, but a callstack is not useful for a user.


I can imagine that it would be helpful for the user to get a stacked 
exception information like:

   Parse error on line 42, column 23
   while reading file "foo/bar"
   while traversing directory "blabla"

But since you refer to the CallStack feature of GHC, this seems not to be 
addressed in the proposals.




On Fri, 8 May 2020, Carter Schonwald wrote:

I have no doubt such a mechanism would have saved me many hours of 
debugging exceptions in Haskell systems I've worked on in the past.


If you must debug exceptions, then this sounds like exceptions were abused 
for programming errors.




Ben writes in:
   http://www.well-typed.com/blog/2020/04/dwarf-3/

"Unfortunately, the untyped nature of Haskell exceptions complicates the 
migration path for existing code."


Actually, it only proves again, that it was wrong from the beginning to 
hide information about potential exceptions in the IO monad instead of 
making them explicit via ExceptionalT, ExceptT or the like.

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Decorating exceptions with backtrace information

2020-05-08 Thread Carter Schonwald
On Fri, May 8, 2020 at 9:32 AM Carter Schonwald 
wrote:

> ben, could you please email the libraries list with this too? This seems
> like a core libraries / base change rather than a ghc-the-compiler change
>
> On Thu, May 7, 2020 at 6:57 PM Michael Sloan  wrote:
>
>> Thanks so much for making a proposal for this, Ben!!  It's great to see
>> progress here.
>>
>> I'm also glad that there is now a proposal process.  I made a fairly
>> similar proposal almost exactly 5 years ago to the libraries list -
>> https://mail.haskell.org/pipermail/libraries/2015-April/025471.html -
>> but without the subtlety of particular backtrace representations.  Skimming
>> the ensuing thread may still be informative.
>>
>> In particular, there is one thing I would like to highlight from that old
>> proposal.  I think it'd be good to have a standard way to represent a chain
>> of exceptions, and build this into `catch` and `finally`.  Python and Java
>> both have a mechanism for this, and both refer to it as a "cause"
>> exception.  When an exception is thrown during exception handling, the
>> exception being handled is preserved as its "cause".  I find this mechanism
>> to be incredibly useful in Java, it has made the underlying issue much
>> clearer in many cases, and in other cases at least provides helpful
>> context.  I have no doubt such a mechanism would have saved me many hours
>> of debugging exceptions in Haskell systems I've worked on in the past.
>>
>> I considered commenting about that directly on the proposal, but I figure
>> this is a better place to suggest expanding the scope of the change :) .
>> Totally understandable if you want to keep this proposal focused on
>> stacktraces, but I think it'd be good to consider this as a potential
>> future improvement.
>>
>> -Michael
>>
>> On Thu, May 7, 2020 at 3:55 PM Ben Gamari  wrote:
>>
>>>
>>> Hi everyone,
>>>
>>> After a nice discussion on IRC about the unfortunate state of error
>>> reporting in Haskell, I felt compelled to write down some long-lingering
>>> thoughts regarding backtraces on exceptions. The result is GHC proposal
>>> #330 [1]. I think the approach is viable and perhaps even
>>> straightforward. I have the sketch of an implementation here [2].
>>>
>>> Please have a look at the proposal and leave your comments. If there is
>>> consensus it is possible that we could have this done for 8.12.
>>>
>>> Cheers,
>>>
>>> - Ben
>>>
>>>
>>> [1] https://github.com/ghc-proposals/ghc-proposals/pull/330
>>> [2] https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3236
>>> ___
>>> ghc-devs mailing list
>>> ghc-devs@haskell.org
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>>
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Decorating exceptions with backtrace information

2020-05-08 Thread Carter Schonwald
ben, could you please email the libraries list with this too? This seems
like a core libraries / base change rather than a ghc-the-compiler change

On Thu, May 7, 2020 at 6:57 PM Michael Sloan  wrote:

> Thanks so much for making a proposal for this, Ben!!  It's great to see
> progress here.
>
> I'm also glad that there is now a proposal process.  I made a fairly
> similar proposal almost exactly 5 years ago to the libraries list -
> https://mail.haskell.org/pipermail/libraries/2015-April/025471.html - but
> without the subtlety of particular backtrace representations.  Skimming the
> ensuing thread may still be informative.
>
> In particular, there is one thing I would like to highlight from that old
> proposal.  I think it'd be good to have a standard way to represent a chain
> of exceptions, and build this into `catch` and `finally`.  Python and Java
> both have a mechanism for this, and both refer to it as a "cause"
> exception.  When an exception is thrown during exception handling, the
> exception being handled is preserved as its "cause".  I find this mechanism
> to be incredibly useful in Java, it has made the underlying issue much
> clearer in many cases, and in other cases at least provides helpful
> context.  I have no doubt such a mechanism would have saved me many hours
> of debugging exceptions in Haskell systems I've worked on in the past.
>
> I considered commenting about that directly on the proposal, but I figure
> this is a better place to suggest expanding the scope of the change :) .
> Totally understandable if you want to keep this proposal focused on
> stacktraces, but I think it'd be good to consider this as a potential
> future improvement.
>
> -Michael
>
> On Thu, May 7, 2020 at 3:55 PM Ben Gamari  wrote:
>
>>
>> Hi everyone,
>>
>> After a nice discussion on IRC about the unfortunate state of error
>> reporting in Haskell, I felt compelled to write down some long-lingering
>> thoughts regarding backtraces on exceptions. The result is GHC proposal
>> #330 [1]. I think the approach is viable and perhaps even
>> straightforward. I have the sketch of an implementation here [2].
>>
>> Please have a look at the proposal and leave your comments. If there is
>> consensus it is possible that we could have this done for 8.12.
>>
>> Cheers,
>>
>> - Ben
>>
>>
>> [1] https://github.com/ghc-proposals/ghc-proposals/pull/330
>> [2] https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3236
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Decorating exceptions with backtrace information

2020-05-07 Thread Michael Sloan
Thanks so much for making a proposal for this, Ben!!  It's great to see
progress here.

I'm also glad that there is now a proposal process.  I made a fairly
similar proposal almost exactly 5 years ago to the libraries list -
https://mail.haskell.org/pipermail/libraries/2015-April/025471.html - but
without the subtlety of particular backtrace representations.  Skimming the
ensuing thread may still be informative.

In particular, there is one thing I would like to highlight from that old
proposal.  I think it'd be good to have a standard way to represent a chain
of exceptions, and build this into `catch` and `finally`.  Python and Java
both have a mechanism for this, and both refer to it as a "cause"
exception.  When an exception is thrown during exception handling, the
exception being handled is preserved as its "cause".  I find this mechanism
to be incredibly useful in Java, it has made the underlying issue much
clearer in many cases, and in other cases at least provides helpful
context.  I have no doubt such a mechanism would have saved me many hours
of debugging exceptions in Haskell systems I've worked on in the past.

I considered commenting about that directly on the proposal, but I figure
this is a better place to suggest expanding the scope of the change :) .
Totally understandable if you want to keep this proposal focused on
stacktraces, but I think it'd be good to consider this as a potential
future improvement.

-Michael

On Thu, May 7, 2020 at 3:55 PM Ben Gamari  wrote:

>
> Hi everyone,
>
> After a nice discussion on IRC about the unfortunate state of error
> reporting in Haskell, I felt compelled to write down some long-lingering
> thoughts regarding backtraces on exceptions. The result is GHC proposal
> #330 [1]. I think the approach is viable and perhaps even
> straightforward. I have the sketch of an implementation here [2].
>
> Please have a look at the proposal and leave your comments. If there is
> consensus it is possible that we could have this done for 8.12.
>
> Cheers,
>
> - Ben
>
>
> [1] https://github.com/ghc-proposals/ghc-proposals/pull/330
> [2] https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3236
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Decorating exceptions with backtrace information

2020-05-07 Thread Ben Gamari

Hi everyone,

After a nice discussion on IRC about the unfortunate state of error
reporting in Haskell, I felt compelled to write down some long-lingering
thoughts regarding backtraces on exceptions. The result is GHC proposal
#330 [1]. I think the approach is viable and perhaps even
straightforward. I have the sketch of an implementation here [2].

Please have a look at the proposal and leave your comments. If there is
consensus it is possible that we could have this done for 8.12.

Cheers,

- Ben


[1] https://github.com/ghc-proposals/ghc-proposals/pull/330
[2] https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3236


signature.asc
Description: PGP signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs