
Hi devs, I'm sure there's an easy answer to this, but I'm wondering: why is the CallStack feature implemented with implicit parameters instead of just a magical constraint? Whenever I use this feature, I don't want to have to enable -XImplicitParams and then make sure I get the name right. What would be wrong with, e.g.,
undefined :: AppendsCallStack => a
Seems simpler. Is it problems with a nullary class? Thanks, Richard

Hi, Am Mittwoch, den 20.01.2016, 00:39 -0500 schrieb Richard Eisenberg:
I'm sure there's an easy answer to this, but I'm wondering: why is the CallStack feature implemented with implicit parameters instead of just a magical constraint? Whenever I use this feature, I don't want to have to enable -XImplicitParams and then make sure I get the name right. What would be wrong with, e.g.,
undefined :: AppendsCallStack => a
Seems simpler. Is it problems with a nullary class?
I tried to construct this using what we have right now: ==> AppendCallStack.hs <== {-# LANGUAGE ConstraintKinds, ImplicitParams #-} module AppendCallStack (AppendsCallStack) where import GHC.Stack type AppendsCallStack = ?x::CallStack ==> Bar.hs <== module Bar where import AppendCallStack foo x :: AppendsCallStack => a -> a foo x = error "Test" But with GHC-7.10 I get [1 of 2] Compiling AppendCallStack ( AppendCallStack.hs, AppendCallStack.o ) [2 of 2] Compiling Bar ( Bar.hs, Bar.o ) Bar.hs:5:1: Invalid type signature: foo x :: AppendsCallStack => a -> a Should be of form <variable> :: <type> although the constraint seems to be a constraint all right: *AppendCallStack> :kind AppendsCallStack AppendsCallStack :: GHC.Prim.Constraint and with GHC HEAD I get [1 of 2] Compiling AppendCallStack ( AppendCallStack.hs, AppendCallStack.o ) AppendCallStack.hs:6:1: error: • Illegal implicit parameter ‘?x::CallStack’ • In the type synonym declaration for ‘AppendsCallStack’ Too bad... Greetings, Joachim -- Joachim “nomeata” Breitner mail@joachim-breitner.de • http://www.joachim-breitner.de/ Jabber: nomeata@joachim-breitner.de • GPG-Key: 0xF0FBF51F Debian Developer: nomeata@debian.org

| foo x :: AppendsCallStack => a -> a Remove the "x"! S | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces@haskell.org] On Behalf Of | Joachim Breitner | Sent: 20 January 2016 09:08 | To: ghc-devs@haskell.org | Subject: Re: CallStack naming | | Hi, | | Am Mittwoch, den 20.01.2016, 00:39 -0500 schrieb Richard Eisenberg: | > I'm sure there's an easy answer to this, but I'm wondering: why is | the | > CallStack feature implemented with implicit parameters instead of | just | > a magical constraint? Whenever I use this feature, I don't want to | > have to enable -XImplicitParams and then make sure I get the name | > right. What would be wrong with, e.g., | > | > > undefined :: AppendsCallStack => a | > | > Seems simpler. Is it problems with a nullary class? | | I tried to construct this using what we have right now: | | ==> AppendCallStack.hs <== | {-# LANGUAGE ConstraintKinds, ImplicitParams #-} module | AppendCallStack (AppendsCallStack) where | | import GHC.Stack | | type AppendsCallStack = ?x::CallStack | | ==> Bar.hs <== | module Bar where | | import AppendCallStack | | foo x :: AppendsCallStack => a -> a | foo x = error "Test" | | But with GHC-7.10 I get | | [1 of 2] Compiling AppendCallStack ( AppendCallStack.hs, | AppendCallStack.o ) | [2 of 2] Compiling Bar ( Bar.hs, Bar.o ) | Bar.hs:5:1: | Invalid type signature: foo x :: AppendsCallStack => a -> a | Should be of form <variable> :: <type> | | although the constraint seems to be a constraint all right: | | *AppendCallStack> :kind AppendsCallStack | AppendsCallStack :: GHC.Prim.Constraint | | and with GHC HEAD I get | | [1 of 2] Compiling AppendCallStack ( AppendCallStack.hs, | AppendCallStack.o ) | | AppendCallStack.hs:6:1: error: | • Illegal implicit parameter ‘?x::CallStack’ | • In the type synonym declaration for ‘AppendsCallStack’ | | Too bad... | | Greetings, | Joachim | | -- | Joachim “nomeata” Breitner | mail@joachim-breitner.de • | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fwww.jo | achim- | breitner.de%2f&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7cd5d44 | 2348f364bcc8a0108d321792a7c%7c72f988bf86f141af91ab2d7cd011db47%7c1&sda | ta=5KAXu5980%2bc4CchVNfWyo1mlD6D8%2bQKn9Qjp6ypv0eE%3d | Jabber: nomeata@joachim-breitner.de • GPG-Key: 0xF0FBF51F | Debian Developer: nomeata@debian.org

Hi, Am Mittwoch, den 20.01.2016, 10:32 +0000 schrieb Simon Peyton Jones:
foo x :: AppendsCallStack => a -> a
Remove the "x"!
heh. Silly me. So let’s try again: With 7.10 it now works: ==> AppendCallStack.hs <== {-# LANGUAGE ConstraintKinds, ImplicitParams #-} module AppendCallStack (AppendsCallStack) where import GHC.Stack type AppendsCallStack = ?callStack::CallStack ==> Bar.hs <== {-# LANGUAGE FlexibleContexts #-} module Main where import AppendCallStack import MyError foo :: AppendsCallStack => a -> a foo x = myerror "Test" main = print (foo ()) ==> MyError.hs <== {-# LANGUAGE ImplicitParams #-} module MyError where import GHC.Stack myerror :: (?callStack :: CallStack) => String -> a myerror msg = error (msg ++ ": " ++ showCallStack ?callStack) Note that I need FlexibleContexts on the usage site to be able to use this, otherwise I get Non type-variable argument in the constraint: ?callStack::GHC.Stack.CallStack See it in action: $ ghc --make Bar && ./Bar Bar: Test: ?callStack, called at ./MyError.hs:7:51 in main:MyError myerror, called at Bar.hs:8:9 in main:Main foo, called at Bar.hs:10:15 in main:Main With GHC-HEAD, it compiles no longer(!): [1 of 2] Compiling AppendCallStack ( AppendCallStack.hs, AppendCallStack.o ) AppendCallStack.hs:6:1: error: • Illegal implicit parameter ‘?callStack::CallStack’ • In the type synonym declaration for ‘AppendsCallStack’ So Richard, does it do what you want with GHC-7.10? And given that GHC HEAD rejects it, was 7.10 wrong or is there a bug in HEAD? Greetings, Joachim -- Joachim “nomeata” Breitner mail@joachim-breitner.de • http://www.joachim-breitner.de/ Jabber: nomeata@joachim-breitner.de • GPG-Key: 0xF0FBF51F Debian Developer: nomeata@debian.org

On Jan 20, 2016, at 6:50 AM, Joachim Breitner
With GHC-HEAD, it compiles no longer(!):
[1 of 2] Compiling AppendCallStack ( AppendCallStack.hs, AppendCallStack.o )
AppendCallStack.hs:6:1: error: • Illegal implicit parameter ‘?callStack::CallStack’ • In the type synonym declaration for ‘AppendsCallStack’
So Richard, does it do what you want with GHC-7.10? And given that GHC HEAD rejects it, was 7.10 wrong or is there a bug in HEAD?
Eek. That's a bug. :( Richard
Greetings, Joachim
-- Joachim “nomeata” Breitner mail@joachim-breitner.de • http://www.joachim-breitner.de/ Jabber: nomeata@joachim-breitner.de • GPG-Key: 0xF0FBF51F Debian Developer: nomeata@debian.org
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Hi, Am Mittwoch, den 20.01.2016, 09:56 -0500 schrieb Richard Eisenberg:
Eek. That's a bug. :(
There we go: https://ghc.haskell.org/trac/ghc/ticket/11466 Greetings, Joachim -- Joachim “nomeata” Breitner mail@joachim-breitner.de • http://www.joachim-breitner.de/ Jabber: nomeata@joachim-breitner.de • GPG-Key: 0xF0FBF51F Debian Developer: nomeata@debian.org

| I'm sure there's an easy answer to this, but I'm wondering: why is the | CallStack feature implemented with implicit parameters instead of just | a magical constraint? Whenever I use this feature, I don't want to | have to enable -XImplicitParams and then make sure I get the name | right. What would be wrong with, e.g., | | > undefined :: AppendsCallStack => a | | Seems simpler. Is it problems with a nullary class? Hmm. Actually I think that's quite a good idea. The call-stack idea started here https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations. We want to be able to get hold of the current call stack. It obviously doesn't make sense to say currentCallStack :: CallStack But as the call stack is an implicit parameter (operationally), it obviously DOES make sense to say ?currentStack :: (?currentStack :: CallStack) => CallStack if ?currentStack is an implicit parameter. And it went from there. There are disadvantages: * Need to use -XImplicitParams (Richard's point) * Need to align two names: foo :: (?loc :: CallStack) => Int -> Int foo x = if x<0 then error "urk" else -x won't work, because 'error' needs (?callStack :: CallStack) * The special cases in the type checker need a 2-level pattern match: for the magic "IP" class, and then the magic "CallStack" type * In principle you might have multiple call stacks kicking around at the same time boo :: (?a::CallStack, ?b::CallStack) => Int -> Int Now I'm not really sure what is supposed to happen about solving these constraints. Perhaps it could be a feature, but it's not one anyone has asked for, and even having to think about it makes my head hurt. Your alternative suggestion is to have a magic nullary class, the ICallStack class ("I" for implicit) so that class ICallStack where callStack :: CallStack At least that's is the implementation, but all the user can see is the overloaded function callStack :: ICallStack => CallStack The solving rules, the CallStack type, and functions for printing it, would be precisely as now. I like this. What about others? (We'd have to think about what to do for 8.0 but first lets see what we want.) Simon

On Wed, Jan 20, 2016, at 02:25, Simon Peyton Jones wrote:
| > undefined :: AppendsCallStack => a | | Seems simpler. Is it problems with a nullary class?
Hmm. Actually I think that's quite a good idea.
I agree, this is much nicer than enabling ImplicitParams and having to remember the naming convention! However, it seems to me that we could implement this as a constraint synonym (pending Joachim's bug #11466). So the main benefit from giving CallStack its own class would be in simplifying the implementation.
There are disadvantages:
* The special cases in the type checker need a 2-level pattern match: for the magic "IP" class, and then the magic "CallStack" type
I don't think this is so bad, we already have a function isCallStackCt that encapsulates the logic.
* In principle you might have multiple call stacks kicking around at the same time boo :: (?a::CallStack, ?b::CallStack) => Int -> Int Now I'm not really sure what is supposed to happen about solving these constraints. Perhaps it could be a feature, but it's not one anyone has asked for, and even having to think about it makes my head hurt.
Ugh, I don't want to think about this either.
Your alternative suggestion is to have a magic nullary class, the ICallStack class ("I" for implicit) so that
class ICallStack where callStack :: CallStack
At least that's is the implementation, but all the user can see is the overloaded function
callStack :: ICallStack => CallStack
The solving rules, the CallStack type, and functions for printing it, would be precisely as now.
I like this. What about others?
I think there's a problem with this approach. The new ability to freeze CallStacks relies on being able to construct new dictionaries on-the-fly for ImplicitParams. So if we were to re-implement CallStacks with their own class, we would have to copy the shadowing logic that we already have for ImplicitParams. So I'm in favor of Joachim's constraint synonym. Eric

| > * In principle you might have multiple call stacks kicking around | > at the same time | > boo :: (?a::CallStack, ?b::CallStack) => Int -> Int | > Now I'm not really sure what is supposed to happen about solving | > these constraints. Perhaps it could be a feature, but it's not | > one anyone has asked for, and even having to think about it makes | > my head hurt. | | Ugh, I don't want to think about this either. But if it's just a synonym, this is entirely possible to do. | > class ICallStack where | > callStack :: CallStack | I think there's a problem with this approach. The new ability to | freeze CallStacks relies on being able to construct new dictionaries | on-the-fly for ImplicitParams. So if we were to re-implement | CallStacks with their own class, we would have to copy the shadowing | logic that we already have for ImplicitParams. I don't understand the problem. Can you be more specific. Regardless, it sounds as though we agreeing that the *user-visible* aspect should use this API. So no more '?callstack' in the user API. Right? Would you like to start amending the wiki page with the proposed new design, from the user point of view. We can continue to argue about implementation! | So I'm in favor of Joachim's constraint synonym. Currently I'm not :-) Simon

On Wed, Jan 20, 2016, at 08:14, Simon Peyton Jones wrote:
| > * In principle you might have multiple call stacks kicking around | > at the same time | > boo :: (?a::CallStack, ?b::CallStack) => Int -> Int | > Now I'm not really sure what is supposed to happen about solving | > these constraints. Perhaps it could be a feature, but it's not | > one anyone has asked for, and even having to think about it makes | > my head hurt. | | Ugh, I don't want to think about this either.
But if it's just a synonym, this is entirely possible to do.
True. I don't think it would cause problems for the solver, but it could certainly be a pitfall for users.
| > class ICallStack where | > callStack :: CallStack
| I think there's a problem with this approach. The new ability to | freeze CallStacks relies on being able to construct new dictionaries | on-the-fly for ImplicitParams. So if we were to re-implement | CallStacks with their own class, we would have to copy the shadowing | logic that we already have for ImplicitParams.
I don't understand the problem. Can you be more specific.
I've written up a few notes about the proposal on the wiki. https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations#Al... The problem is that I don't know how to implement `withFrozenCallStack` (included in the wiki) as a Haskell function if CallStacks aren't implicit parameters under-the-hood.
Regardless, it sounds as though we agreeing that the *user-visible* aspect should use this API. So no more '?callstack' in the user API. Right?
Indeed!

Hi, Am Mittwoch, den 20.01.2016, 09:24 -0800 schrieb Eric Seidel:
The problem is that I don't know how to implement `withFrozenCallStack` (included in the wiki) as a Haskell function if CallStacks aren't implicit parameters under-the-hood.
breaking it further down, the problem is not with `withFrozenCallStack` per se, but rather with any code that wants to set the current callstack, e.g. anything of the current form let ?callStack = ... in .. How would that look with a magic nullary constraint "AppendsCallStack"? It’d probably need a built-in function setCallStack :: CallStack -> (AppendsCallStack => a) -> a with which we can likely implement `withFrozenCallStack` again: withFrozenCallStack :: AppendsCallStack => (AppendsCallStack => a) -> a withFrozenCallStack do_this = -- we pop the stack before freezing it to remove -- withFrozenCallStack's call-site let callStack = freezeCallStack (popCallStack callStack) in setCallStack callStack do_this It might need a second call to popCallStack depending on the precise semantics of `callStack :: AppendsCallStack => CallStack` (i.e. whether that does pop one entry off itself). Greetings, Joachim -- Joachim “nomeata” Breitner mail@joachim-breitner.de • http://www.joachim-breitner.de/ Jabber: nomeata@joachim-breitner.de • GPG-Key: 0xF0FBF51F Debian Developer: nomeata@debian.org

| It’d probably need a built-in function | | setCallStack :: CallStack -> (AppendsCallStack => a) -> a Correct. This is easy to write in Core but not in Haskell. We also need something similar for Typeable, when we get a type-indexed version of TypeRep withTypeable :: TypeRep a -> (Typeable a => r) => r Additionally, for ICallStack (bikeshed: I don’t like "AppendsCallStack") we would need to ensure that the new local instance over-rode all others, like for implicit parameters; see Note [Shadowing of Implicit Parameters] in TcInteract. This part isn't necessary for Typeable because all witnesses are the same. Bother. Well, in the short term, let's * implement it with the constraint synonym * bikeshed about names * write down the user-visible API, ensuring that it makes no mention of implicit parameters (provide setCallStack) Then we can implement the API differently later if we so desire. The main disadvantage is that the abstraction is leaky. We can't *prevent* users from seeing and using the implicit parameter. Does that sound like a plan. Might you do it Eric? The urgency is just to get 8.0 out with an API that we like Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces@haskell.org] On Behalf Of | Joachim Breitner | Sent: 21 January 2016 09:19 | To: ghc-devs@haskell.org | Subject: Re: CallStack naming | | Hi, | | Am Mittwoch, den 20.01.2016, 09:24 -0800 schrieb Eric Seidel: | > The problem is that I don't know how to implement | > `withFrozenCallStack` (included in the wiki) as a Haskell function | if | > CallStacks aren't implicit parameters under-the-hood. | | breaking it further down, the problem is not with | `withFrozenCallStack` per se, but rather with any code that wants to | set the current callstack, e.g. anything of the current form | | let ?callStack = ... | in .. | | How would that look with a magic nullary constraint | "AppendsCallStack"? | It’d probably need a built-in function | | setCallStack :: CallStack -> (AppendsCallStack => a) -> a | | with which we can likely implement `withFrozenCallStack` again: | | withFrozenCallStack :: AppendsCallStack => (AppendsCallStack => a) -> | a withFrozenCallStack do_this = | -- we pop the stack before freezing it to remove | -- withFrozenCallStack's call-site | let callStack = freezeCallStack (popCallStack callStack) | in setCallStack callStack do_this | | It might need a second call to popCallStack depending on the precise | semantics of `callStack :: AppendsCallStack => CallStack` (i.e. | whether that does pop one entry off itself). | | Greetings, | Joachim | | | -- | Joachim “nomeata” Breitner | mail@joachim-breitner.de • | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fwww.jo | achim- | breitner.de%2f&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7cdece5 | 7f942bc42b0dd2308d32243eff4%7c72f988bf86f141af91ab2d7cd011db47%7c1&sda | ta=67ZZO9n8VFDeRV7DCzaI46uxdf%2bPMC4Plx5XY8tMcUc%3d | Jabber: nomeata@joachim-breitner.de • GPG-Key: 0xF0FBF51F | Debian Developer: nomeata@debian.org

On Thu, Jan 21, 2016, at 04:07, Simon Peyton Jones wrote:
Well, in the short term, let's * bikeshed about names
Ok, I don't like ICallStack :) It sounds like a C# interface, which, while technically sort of accurate, is very misleading since users will never write an instance. I'd prefer something a bit more descriptive, like - WithCallStack - HasCallStack - GetsCallStack (in no particular order)
* write down the user-visible API, ensuring that it makes no mention of implicit parameters (provide setCallStack)
Then we can implement the API differently later if we so desire.
In that case we'll probably want to move the CallStack section of the user guide elsewhere, right now it's a subsection of ImplicitParams.
The main disadvantage is that the abstraction is leaky. We can't *prevent* users from seeing and using the implicit parameter.
True, so perhaps a single mention of the implicit parameter, explaining that it's not part of the API and that using it is *explicitly unsupported*, i.e. we may change the implementation later.
Does that sound like a plan. Might you do it Eric? The urgency is just to get 8.0 out with an API that we like
Sure, I'll try to have a patch out later today.

| In that case we'll probably want to move the CallStack section of the | user guide elsewhere, right now it's a subsection of ImplicitParams. Yes! | True, so perhaps a single mention of the implicit parameter, | explaining that it's not part of the API and that using it is | *explicitly unsupported*, i.e. we may change the implementation later. Yes! | - WithCallStack | - HasCallStack | - GetsCallStack I vote for HasCallStack. Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces@haskell.org] On Behalf Of Eric | Seidel | Sent: 21 January 2016 16:15 | To: ghc-devs@haskell.org | Subject: Re: CallStack naming | | On Thu, Jan 21, 2016, at 04:07, Simon Peyton Jones wrote: | > Well, in the short term, let's | > * bikeshed about names | | Ok, I don't like ICallStack :) It sounds like a C# interface, which, | while technically sort of accurate, is very misleading since users | will never write an instance. I'd prefer something a bit more | descriptive, like | | - WithCallStack | - HasCallStack | - GetsCallStack | | (in no particular order) | | > * write down the user-visible API, ensuring that it makes | > no mention of implicit parameters (provide setCallStack) | > | > Then we can implement the API differently later if we so desire. | | In that case we'll probably want to move the CallStack section of the | user guide elsewhere, right now it's a subsection of ImplicitParams. | | > The main disadvantage is that the abstraction is leaky. We can't | > *prevent* users from seeing and using the implicit parameter. | | True, so perhaps a single mention of the implicit parameter, | explaining that it's not part of the API and that using it is | *explicitly unsupported*, i.e. we may change the implementation later. | | > Does that sound like a plan. Might you do it Eric? The urgency is | > just to get 8.0 out with an API that we like | | Sure, I'll try to have a patch out later today. | _______________________________________________ | ghc-devs mailing list | ghc-devs@haskell.org | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.h | askell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc- | devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c520a5cb5bf08467 | e9bd908d3227dfb21%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=Bv%2fkj | FszUZpmWXmU0AcnrumJU9XfUU5v%2fdMCKUP4dGY%3d

On Thu, Jan 21, 2016, at 04:07, Simon Peyton Jones wrote:
| It’d probably need a built-in function | | setCallStack :: CallStack -> (AppendsCallStack => a) -> a
Correct. This is easy to write in Core but not in Haskell.
Ugh, I just realized that we can't write setCallStack (with implicit parameters) in Haskell either. Well, we can, but it adds an entry to the stack.. Why? Let's look at the implementation setCallStack :: CallStack -> (HasCallStack => a) -> a setCallStack stk do_this = let ?callStack = stk in do_this Rebinding ?callStack works just fine, but the occurrence of do_this causes GHC to push an entry onto the stack, which is less than ideal. What does this look like in practice? If we evaluate setCallStack foo (error "die") the resulting stack will be error *do_this* foo The rebinding trick works for withFrozenCallStack precisely because we freeze the CallStack, so the push from do_this is ignored. So, long story short, I'm not convinced of the utility of setCallStack. I think perhaps we should not provide it, and just do the rebinding trick inside withFrozenCallStack (which was the only use-case for setCallStack to begin with).

OK. Let's make sure the wiki page and documentation reflects this. Thanks SImon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces@haskell.org] On Behalf Of Eric | Seidel | Sent: 27 January 2016 18:16 | To: ghc-devs@haskell.org | Subject: Re: CallStack naming | | On Thu, Jan 21, 2016, at 04:07, Simon Peyton Jones wrote: | > | It’d probably need a built-in function | > | | > | setCallStack :: CallStack -> (AppendsCallStack => a) -> a | > | > Correct. This is easy to write in Core but not in Haskell. | | Ugh, I just realized that we can't write setCallStack (with implicit | parameters) in Haskell either. Well, we can, but it adds an entry to | the stack.. Why? Let's look at the implementation | | setCallStack :: CallStack -> (HasCallStack => a) -> a | setCallStack stk do_this = | let ?callStack = stk in do_this | | Rebinding ?callStack works just fine, but the occurrence of do_this | causes GHC to push an entry onto the stack, which is less than ideal. | | What does this look like in practice? If we evaluate | | setCallStack foo (error "die") | | the resulting stack will be | | error | *do_this* | foo | | The rebinding trick works for withFrozenCallStack precisely because we | freeze the CallStack, so the push from do_this is ignored. | | So, long story short, I'm not convinced of the utility of setCallStack. | I think perhaps we should not provide it, and just do the rebinding | trick inside withFrozenCallStack (which was the only use-case for | setCallStack to begin with). | _______________________________________________ | ghc-devs mailing list | ghc-devs@haskell.org | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.ha | skell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc- | devs%0a&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c37a3c50163ce4 | 0dc0ee408d32745f348%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=dVg%2b | q2D%2b2mgmgSWh8Ic9o09P%2f9mem4CpDgd0YzZZpPc%3d

Simon Peyton Jones
OK. Let's make sure the wiki page and documentation reflects this.
It looks like the Wiki [1] hasn't yet been updated. Let's make sure this happens. Thanks! - Ben [1] https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations

Thanks for the reminder! I've added a section [1] on setCallStack with my explanation from above. [1]: https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations#Ge... On Tue, Feb 2, 2016, at 10:50, Ben Gamari wrote:
Simon Peyton Jones
writes: OK. Let's make sure the wiki page and documentation reflects this.
It looks like the Wiki [1] hasn't yet been updated. Let's make sure this happens.
Thanks!
- Ben
[1] https://ghc.haskell.org/trac/ghc/wiki/ExplicitCallStack/ImplicitLocations Email had 1 attachment: + signature.asc 1k (application/pgp-signature)

On 2016-01-20 at 06:39:32 +0100, Richard Eisenberg wrote:
I'm sure there's an easy answer to this, but I'm wondering: why is the CallStack feature implemented with implicit parameters instead of just a magical constraint? Whenever I use this feature, I don't want to have to enable -XImplicitParams and then make sure I get the name right. What would be wrong with, e.g.,
undefined :: AppendsCallStack => a
Seems simpler. Is it problems with a nullary class?
Btw, would that, as a side-effect, make the currently shown type-signature in GHCi a bit nicer than the current ,---- | GHCi, version 8.1.20160117: http://www.haskell.org/ghc/ :? for help | Loaded GHCi configuration from /home/hvr/.ghci | | λ:1> :info error | error :: forall (v :: GHC.Types.Levity) (a :: TYPE v). ?callStack::GHC.Stack.Types.CallStack => [Char] -> a -- Defined in ‘GHC.Err’ | | λ:2> :info undefined | undefined :: forall (v :: GHC.Types.Levity) (a :: TYPE v). ?callStack::GHC.Stack.Types.CallStack => a -- Defined in ‘GHC.Err’ `---- ...?
participants (6)
-
Ben Gamari
-
Eric Seidel
-
Herbert Valerio Riedel
-
Joachim Breitner
-
Richard Eisenberg
-
Simon Peyton Jones