[GHC] #11035: Add implicit call-stacks to partial functions in base

#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- From https://www.reddit.com/r/haskell/comments/3qpefo/a_very_unfortunate_error_me... {{{ ghci> minimumBy compare [] *** Exception: Prelude.foldr1: empty list CallStack: error, called at libraries/base/GHC/List.hs:999:3 in base-4.8.2.0:GHC.List }}} This is not a very useful call-stack. It tells us that error was called in GHC.List, and if we happen to have the source we can even see where it was called. https://github.com/ghc/ghc/blob/master/libraries/base/GHC/List.hs#L999 But that's '''still''' not very helpful because: 1. It points us to some generic `errorEmptyList` function. This function always diverges, so by our current rule it ought to get a CallStack constraint. Oops! 2. Even if we add the CallStack to `errorEmptyList`, the next culprit will (presumably) be `foldr1`, where the stack ends again. `foldr1` is partial, but it doesn't '''always''' diverge, so our current rule would say it shouldn't get a CallStack. This is quite unfortunate because the CallStack will point the finger at `foldr1`, but the error message itself '''already does that'''. So we haven't really gained anything by using the CallStack-aware `error` in base. What we really want to know is where `foldr1` was called, which just so happens to be `minimumBy` itself! Ben Gamari pinged me earlier today on IRC with a similar instance in GHC.Arr. ---- So, I think we should '''consider''' expanding the use of CallStacks in base by one level, to partial functions. By "partial" I specifically mean functions that directly call `error` or one of its wrappers (like `errorEmptyList`). That means that {{{#!haskell head [] = error "bad" head (x:xs) = x }}} would get a CallStack, but {{{#!haskell minimumBy cmp = foldr1 min' where min' x y = case cmp x y of GT -> y _ -> x }}} would '''not''', even though `minimumBy` is also partial in the traditional sense. I recall three arguments against broader use of CallStacks: 1. '''Performance concerns''': CallStacks exist at runtime in the form of an extra parameter to each CallStack-aware function. This is a valid concern and we should certainly do some benchmarking to see what the effects are. 2. '''Readability concerns''': Adding CallStacks will clutter otherwise simple type signatures, e.g. {{{#!haskell head :: [a] -> a head :: (?callStack :: CallStack) => [a] -> a }}} Also a valid concern, especially considering that base functions are the first novices will encounter. But I think we can mitigate this one in two steps. (1) The `:type` command in ghci already suppresses the CallStacks (because it happens to invoke the constraint solver), but `:info` shows them. I think this is fine as is. (2) If haddock shows CallStacks (I'm not sure if it does), we could patch haddock to render them differently. For example, instead of rendering the full type, just render {{{ head :: [a] -> a }}} with a badge that indicates that `head` is location-aware. That would reduce the cognitive overhead of the larger type signature, while retaining the important data. 3. '''Slippery slope''': Where do we draw the line? Why should `head` get a CallStack but not `minimumBy`? I don't have a good answer to this one yet, apart from a suspicion that my proposal will get us a closer to an 80/20 balance. I'm sure this would need to go through the Core Libraries Committee, but I'd also like feedback from fellow GHC devs. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I like this general idea. But I want to find a way to the bottom of the slope, where '''all''' partial functions in base get call stack information. This plan alleviates your problem (3) quite nicely. * For problem (1): it seems quite easy to write a core-to-core pass that scrubs away the call stacks. This core pass would be enabled by `-O` but could be countermanded with `-fno-scrub-call-stacks` (in case there is an error only in optimized code, say). base would be compiled with `-fno- scrub-call-stacks`. This approach doesn't fix the performance of library functions, though. So we could instead have base export two versions of the functions, one with call stacks and one without. How do we relate the two? Via `RULES`: {{{#!hs foldr1 :: (?callstack :: CallStack) => ... faster_foldr1 :: ... {-# RULES "foldr1 call stack scrub" foldr1 = faster_foldr1 #-} }}} Without optimizations, we get the call stack. With optimizations, we don't. Huzzah. It's easy to imagine someone wanting to disable only these call-stack- ish RULES but keep others. Perhaps we should consider tagging RULES somehow to allow activating or deactivating RULES in groups. But that's a proposal for another day, and I don't think we absolutely need that here. * For problem (2): Your suggestions are good. We could also do a cheap trick like this: {{{#!hs type PartialFunction = (?callstack :: CallStack) head :: PartialFunction => [a] -> a }}} Yes, this needs `ConstraintKinds`, but I sorta like it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe): Regarding problem (1): I get the feeling this will require code duplication at the source level, which would be a Bad Thing. We can't just write {{{#!haskell foldr1 :: (?callStack :: CallStack) => ... foldr1 = faster_foldr1 faster_foldr1 :: ... faster_foldr1 f [] = error faster_foldr1 f (x:xs) = foldr f xs }}} because the call to `error` in `faster_foldr1` won't see a given CallStack, and the chain will be broken there. Instead we'd have to write {{{#!haskell foldr1 :: (?callStack :: CallStack) => ... foldr1 f [] = error foldr1 f (x:xs) = foldr f x xs faster_foldr1 :: ... faster_foldr1 f [] = error faster_foldr1 f (x:xs) = foldr f xs }}} It may be the case that most partial functions in base are either simple themselves (like `head`) or have simple definitions in terms of a total function (like `foldr`). So maybe the duplication wouldn't be ''that'' bad, but I'm still pretty wary of this route... A more heavyweight solution could be to have GHC generate a callstack-free version of each function that takes a CallStack, along with a RULE like you described. Then the source-level duplication is gone, but the desugarer or simplifier becomes more complex. In either scenario we end up exporting multiple versions of the "same" function, which will bloat library sizes. But maybe that's not so bad, the binaries shouldn't be affected. (I kinda like the `PartialFunction` constraint too, it's cute.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carter): Question: won't the dwarf based runtime stack traces that Ben Gamari is polishing for ghc 8 provide equivalent ish information , but without any performance implications? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe): Possibly, I admit I'm not super familiar with the DWARF work. My main concern would be that the DWARF stack trace will expose haskell's lazy evaluation just like the cost-centre traces do. I find these difficult to debug because they jump all over the place as values are demanded. That might be useful for performance debugging, but for debugging a crash I just want to know '''where''' things were called, not what sequence of "demandings" led me to the crash. In other words, I want a trace based on the static call graph, which is what the implicit call-stacks provide. I hope that makes sense. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): How about we stay on top of the slipperly slope for a while, and let people experiment with their call-stack enabled custom Preludes first for a while? In fact, what I do not like about {{{ ghci> minimumBy compare [] *** Exception: Prelude.foldr1: empty list CallStack: error, called at libraries/base/GHC/List.hs:999:3 in base-4.8.2.0:GHC.List }}} is that it leaks implementation details. This is great in your own code, but a polished library should _not_ leak a call stack about its details; it should either print plain exception or the call stack that finishes at the library’s API. At least for “expected exceptions” like `"empty list"`. So I would say what we have to do here is to prevent this call to error from adding a call stack. For that, uses of `error` in library functions¹ should explicitly use `let ?foo::CallStack = emptyCallStack in error "..."` to prevent the constraint solver from adding an implementation- leaky call-stack here (if that even works, maybe what I want to achieve here requires modifications to the solver). ¹ Of course, precisely those that do not propagate the `?_::CallStack` constraint to the caller. If we decide to do that, then everything is fine. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe):
it should either print plain exception or the call stack that finishes at the library’s API
I would say that `minimumBy`s call stack does "finish at the library's api;" the root is in GHC.List, which is part of base. Perhaps you mean that a function `f` should only print call stacks whose root is `f`. That's an interesting point, and does seem reasonable for production code, but it sounds very non-trivial to implement. You can think of the CallStack solver as rewriting your code as follows. Whenever it sees a CallStack constraint, eg from a call to `error` {{{ f x = error }}} it inserts a new implicit binder that adds the current call-site {{{ f x = let ?callStack = <this-call-site> `pushCallStack` ?callStack in error }}} The `?callStack` on the rhs will either be discharged by the CallStack in `f`s context (if `f` requested one) or by the empty CallStack. So we can't just write `let ?callStack = emptyCallStack in error` because that's effectively what GHC is already doing for us. Instead we would need multiple versions of the callstack-aware functions, as Richard suggested. In general, I think Richard's suggestion of a call-stack scrubbing pass for optimized code should satisfy your concern as well. If I compile packages from hackage with optimizations (the default I think), then I won't see the implementation details. If I don't, I'll see the details, but I can at least submit a more informative bug report! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata):
So we can't just write `let ?callStack = emptyCallStack in error` because that's effectively what GHC is already doing for us. Instead we would need multiple versions of the callstack-aware functions, as Richard suggested.
What if we add a special `rootCallStack :: CallStack` which is a value such that {{{ x `pushCallStack` rootCallStack = rootCallStack }}} but {{{ rootCallStack `pushCallStack` x = rootCallStack “:” x }}} as before and a call stack that consists of only a rootCallStack causes no stack trace to be printed. This allows the following two important patterns: {{{ f x = let ?callStack = rootCallStack in {... something with error or any other callStack expecting function ...} }}} would prevent any CallStack information to appear in `{...}`, and {{{ f x = let ?callStack = rootCallStack `pushCallStack` ?callStack in {... something with error or any other callStack expecting function ...} }}} which would include a CallStack in exceptions raised in `{...}`, but the stack would end in `f`, and not expose any of the structure of the implementation. I’d like to have something like this for API hygiene and implementation hiding. But note that if we had that, constant propagation (or `rootCallStack`) and a specialization mechanism that’s very much like the existing type class constraint specialization would allow the compiler to specialize the implementation in the former case to one that does _not_ pass CallStacks around any more. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe):
What if we add a special `rootCallStack :: CallStack` ...
I think this is doable. One thing worth stressing is that in your scenario the programmer has to '''explicitly''' say where they want the call-stack to be cut off (or to kill it altogether). This is in stark contrast to the existing scenarios, where call-stacks are handled entirely behind the scenes by GHC. But it sounds like you really want the option for explicit control, and I kinda understand why. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Yes, I kinda hijacked this ticket by accident; sorry for that. Do you want me to open a separate one? But yes: In a carefully crafted library for public consumption, explicit control over the produced call stacks seem to be desirable. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

How about we stay on top of the slipperly slope for a while, and let
#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:5 nomeata]: people experiment with their call-stack enabled custom Preludes first for a while? Perhaps that's true. But this change would be quite under-the-hood, so I'm less worried about changing libraries in this way.
In fact, what I do not like about {{{ ghci> minimumBy compare [] *** Exception: Prelude.foldr1: empty list CallStack: error, called at libraries/base/GHC/List.hs:999:3 in
}}} is that it leaks implementation details. This is great in your own code, but a polished library should _not_ leak a call stack about its details; it should either print plain exception or the call stack that finishes at
base-4.8.2.0:GHC.List the library’s API. At least for “expected exceptions” like `"empty list"`. I disagree with this push toward perfection. I understand what you're getting at here, and I agree in principle. But I think this issue (which does seem to be independent from the original ticket) is not terribly important to solve. In other languages, I've seen standard libraries spill their implementation details all over the place in stack traces. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:2 gridaphobe]:
Regarding problem (1): I get the feeling this will require code duplication at the source level, which would be a Bad Thing.
A more heavyweight solution could be to have GHC generate a callstack- free version of each function that takes a CallStack, along with a RULE
Yes, that's true. I realized that as I wrote my post, but didn't really dwell on it. It is a Bad Thing. like you described. Then the source-level duplication is gone, but the desugarer or simplifier becomes more complex. Yes, this is indeed more heavyweight. Worth it? Probably not. I'd love input from someone who knows about the DWARF stuff! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): *Please* do not do this in base, instead provide a separate package that people can use if they want this functionality. I'm concerned about all the points you raise in the description. I don't think I need to expand on them, you've done a great job of explaining the problems this leads to. So this gets a strong -1 from me, at least in base. We should be deeply suspicious about hard-wiring a particular debugging method into the types of core library functions. It just seems entirely wrong. Useful perhaps, but wrong. Let's not forget we have no less than 3 ways to get call stacks, each with advantages and disadvantages: * Profiling * Execution stacks (DWARF) * Implicit call stacks None of these is perfect, where perfect is something like: full call stacks available all the time with no changes to the source code, no performance overhead, and no need to recompile. Each method compromises on one or more of these things. Implicit call stacks are great for finding out where you called 'error' from, but they don't scale up to solve the general problem. We start to need multiple versions of functions, and RULES and magic in Haddock to hide this mess from users. In contrast, you can just compile everything with profiling and get full call stacks, or you can use execution stacks which probably provide enough information in most cases. Neither of these things requires any source-level changes. That's why I think we should stop where we are with implicit call stacks. I should also mention that I'm working on extending profiling to work with GHCi, so people using GHCi will get the benefit of full and detailed call stacks without any changes at the source level. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

*Please* do not do this in base, instead provide a separate package that
#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe): Replying to [comment:12 simonmar]: people can use if they want this functionality.
I'm concerned about all the points you raise in the description. I
don't think I need to expand on them, you've done a great job of explaining the problems this leads to. So this gets a strong -1 from me, at least in base. Noted. I actually do have a separate package that exports location-aware variants of common partial functions (https://hackage.haskell.org/package /located-base), and I don't mind keeping the broader use of CallStacks out of base. I opened this ticket primarily because I'm not very satisfied with the error produced in the description: {{{ ghci> minimumBy compare [] *** Exception: Prelude.foldr1: empty list CallStack: error, called at libraries/base/GHC/List.hs:999:3 in base-4.8.2.0:GHC.List }}} This CallStack adds no value to the error (since `foldr1` is already identified as the culprit), but does add a fair bit of noise. Adding more CallStacks would make this error much more useful, but it doesn't sound like that will happen at this point. The other thing we could do is suppress CallStacks inside base. We'd still export a CallStack-enhanced `error` and `undefined`, we just wouldn't use them internally. Do you think the error message would be better without the partial CallStack, or does it seem more like a non-issue? ------------
I should also mention that I'm working on extending profiling to work with GHCi, so people using GHCi will get the benefit of full and detailed call stacks without any changes at the source level.
Is there a ticket for this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Replying to [comment:5 nomeata]:
In fact, what I do not like about {{{ ghci> minimumBy compare [] *** Exception: Prelude.foldr1: empty list CallStack: error, called at libraries/base/GHC/List.hs:999:3 in
}}} is that it leaks implementation details. This is great in your own code, but a polished library should _not_ leak a call stack about its
#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe): Replying to [comment:10 goldfire]: base-4.8.2.0:GHC.List details; it should either print plain exception or the call stack that finishes at the library’s API. At least for “expected exceptions” like `"empty list"`.
I disagree with this push toward perfection. I understand what you're
getting at here, and I agree in principle. But I think this issue (which does seem to be independent from the original ticket) is not terribly important to solve. In other languages, I've seen standard libraries spill their implementation details all over the place in stack traces. I'm generally inclined to agree that there's no harm in spilling implementation details in the stack trace, I can't think of a single language that lets you do what Joachim is suggesting. That being said, it sounds like it could be a very lightweight extension of the existing machinery, so it might be interesting to experiment with. But it probably should be a separate ticket :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar):
Do you think the error message would be better without the partial CallStack, or does it seem more like a non-issue?
We could have a non-callstack version of error, and use that from `minimumBy` and other functions in base that call `error`?
I should also mention that I'm working on extending profiling to work with GHCi, so people using GHCi will get the benefit of full and detailed call stacks without any changes at the source level.
Is there a ticket for this?
I just made one: #11047 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe): Replying to [comment:15 simonmar]:
We could have a non-callstack version of error, and use that from `minimumBy` and other functions in base that call `error`?
Yes, that's the idea. We could even add a one-off version of Richard's RULE to optimize away the callstacks for `error` in distributed code, which I think would make Joachim happier. I'm just wondering if the cosmetic issue is enough to warrant the extra (probably small) maintenance burden. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11035: Add implicit call-stacks to partial functions in base -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata):
I'm generally inclined to agree that there's no harm in spilling implementation details in the stack trace, I can't think of a single language that lets you do what Joachim is suggesting.
Since when has that become an argument _against_ a change? Especially if no one else is doing it, then we should be doing it ;-)
That being said, it sounds like it could be a very lightweight extension of the existing machinery, so it might be interesting to experiment with. But it probably should be a separate ticket :)
Agreed; #11049. If that is implemented you might use that machinery to fix this bug without having to maintain two variants of error, as you can suppress the CallStack at the point where error (or `foldl1`) is called. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11035#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC