[GHC] #14218: GHC.Stack.HasCallStack not compatible with ConstraintKinds

#14218: GHC.Stack.HasCallStack not compatible with ConstraintKinds -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 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: -------------------------------------+------------------------------------- The programs `Good` and `Bad` are the same, except that `Bad` uses a constraint synonym including `GHC.Stack.HasCallStack` whereas `Good` inlines the constraints. I expect them to produce the same output, but they don't: {{{ $ ./Good ["callStack","f"] $ ./Bad ["f"] }}} Here is the source for `Good.hs`: {{{#!hs {-# LANGUAGE MultiParamTypeClasses #-} -- For nullary 'Trivial' class module Main where import qualified GHC.Stack as Ghc class Trivial where instance Trivial where -- | Print the functions on the call stack. callStack :: (Ghc.HasCallStack, Trivial) => IO () callStack = print $ map fst (Ghc.getCallStack Ghc.callStack) f :: (Ghc.HasCallStack, Trivial) => IO () f = callStack main :: IO () main = f -- Should print @["callStack", "f"]@. }}} Here is the source for `Bad.hs`: {{{#!hs {-# LANGUAGE ConstraintKinds #-} -- For 'C' {-# LANGUAGE MultiParamTypeClasses #-} -- For nullary 'Trivial' class module Main where import qualified GHC.Stack as Ghc class Trivial where instance Trivial where type C = (Ghc.HasCallStack, Trivial) -- | Print the functions on the call stack. callStack :: C => IO () callStack = print $ map fst (Ghc.getCallStack Ghc.callStack) f :: C => IO () f = callStack main :: IO () main = f -- Should print @["callStack", "f"]@. }}} Tested compiled and interpreted with GHC 8.2.1 and 8.0.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14218 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14218: GHC.Stack.HasCallStack not compatible with ConstraintKinds -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 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: | -------------------------------------+------------------------------------- Changes (by ntc2): * Attachment "Good.hs" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14218 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14218: GHC.Stack.HasCallStack not compatible with ConstraintKinds -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 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: | -------------------------------------+------------------------------------- Changes (by ntc2): * Attachment "Bad.hs" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14218 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14218: GHC.Stack.HasCallStack not compatible with constraint synonyms -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: gridaphobe, simonpj (added) Comment: Hmm, yes, this is an unfortunate consequence of the implementation of the `HasCallStack` implementation. I suspect we find the `C` dictionary in scope when we solve for `callStack`'s constraints in `f`. Consequently we just pass it as a whole to `callStack` and the special callstack solver logic is never invoked. I honestly don't know how best to avoid this, but it certainly suggests that the status quo is rather fragile. I fear this issue may be somewhat intrinsic in the implementation strategy. If this is case we should at very least make sure this wrinkle is well-documented. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14218#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14218: GHC.Stack.HasCallStack not compatible with constraint synonyms -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 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): Oh dear.. Ben's explanation sounds plausible to me, though I didn't realize constraint synonyms worked this way. I would have expected them to be transparent to GHC like regular type synonyms, i.e. the `C` constraint would be expanded and we'd get two separate dictionaries rather than a compound dictionary. If this is actually how constraint synonyms work, a simple fix could be to expand them and treat the member constraints individually. But maybe there's a good reason for the current behavior? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14218#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14218: GHC.Stack.HasCallStack not compatible with constraint synonyms -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 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 bgamari):
Ben's explanation sounds plausible to me, though I didn't realize constraint synonyms worked this way.
I actually didn't realize it either until I looked at the tc-trace output. I also don't know whether there is a good reason (other than efficiency) why they *must* be implemented this way. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14218#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14218: GHC.Stack.HasCallStack not compatible with constraint synonyms -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 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 simonpj): It's nothing specific about call-stacks. It's in implicit parameters: {{{ type C2 = (?x::Int, ?y::Int) h1 :: C2 => Int -> IO () h1 v = print (?x+v) -- h2 :: (?x::Int, ?y::Int) => Int -> IO () h2 :: C2 => Int -> IO () h2 v = let ?x = 0 in h1 v main = let { ?x = 3; ?y = 4 } in h2 4 }}} This prints 7; but if you swap to the other (equivalent!) type sig for `h2` it prints 4 (as it should). Reason: in `h2`, when calling `h1` we should really rebuild a pair- constraint to pass on to `h1` so that we "see" the binding (which behaves like a local instance declaration) for `?x`. But we don't: we just have a wanted constraint `[W] C2` and a given one with the same type, and solve one from the other. We don't allow implicit parameters as superclasses for exactly this reason. It matters precisely where an implicit parameter constraint is solved, so you can't meaningfully abstract over them. `HasCallStack` is really just an implicit parameter, so it fails in the same way. Possible solutions: 1. Don't allow implicit parameters in type synonyms, or 2. Expand type synonyms in constraints more aggressively, so they really behave ''exactly'' like the expanded version. I vote for (2). Indeed I was surprised that doesn't happen already. But I think we should prohibit {{{ type instance F [a] = (?x::a, Show a) }}} with an implicit parameter on the right. Now aggressive expansion won't always work. This should be just as illegal as implicit parameters in superclasses. In effect, implicit parameters aren't really a first-class constraint form: you can't abstract over them. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14218#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14218: GHC.Stack.HasCallStack not compatible with constraint synonyms -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 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 ntc2): Is this a known implicit params bug or "feature" then? In any case, I also vote for (2) :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14218#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14218: GHC.Stack.HasCallStack not compatible with constraint synonyms -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 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 simonpj): Well NOW it's a know implicit-parameter bug. No one had previously reported it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14218#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14218: GHC.Stack.HasCallStack not compatible with constraint synonyms
-------------------------------------+-------------------------------------
Reporter: ntc2 | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1
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 Simon Peyton Jones

#14218: GHC.Stack.HasCallStack not compatible with constraint synonyms -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/T14218 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => typecheck/should_run/T14218 * status: new => merge * milestone: => 8.2.2 Comment: Thanks for reporting this bug. It is a rather insidious and long-standing one. The test I added has two cases, one for vanilla implicit parameters and one for call-stacks. Could consider merging this to 8.2, but I doubt it'll affect many people. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14218#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14218: GHC.Stack.HasCallStack not compatible with constraint synonyms
-------------------------------------+-------------------------------------
Reporter: ntc2 | Owner: (none)
Type: bug | Status: merge
Priority: normal | Milestone: 8.2.2
Component: Compiler | Version: 8.2.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| typecheck/should_run/T14218
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#14218: GHC.Stack.HasCallStack not compatible with constraint synonyms -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/T14218 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * version: 8.2.1 => 8.0.1 * resolution: => fixed * milestone: 8.2.2 => 8.4.1 Comment: Given that this isn't really a regression I'm going to punt on this until 8.4. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14218#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14218: GHC.Stack.HasCallStack not compatible with constraint synonyms -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/T14218 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by saurabhnanda): Commenting to be notified of future discussion (is there a better way to do this?) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14218#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14218: GHC.Stack.HasCallStack not compatible with constraint synonyms -------------------------------------+------------------------------------- Reporter: ntc2 | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/T14218 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata):
Commenting to be notified of future discussion (is there a better way to do this?)
You can, under “change the ticket”, add yourself to the “subscribers” or “observers” or however it is called in English. And I am under the impression that since a few months, simply commenting on a post no longer subscribes you. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14218#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC