[GHC] #12785: GHC panic, TypeFamily in equality constraint

#12785: GHC panic, TypeFamily in equality constraint -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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: -------------------------------------+------------------------------------- Compiling the attached module I get {{{ $ ghc --interactive Tree.hs GHCi, version 8.1.20161030: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Tree ( Tree.hs, interpreted ) Tree.hs:28:63: error:ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.1.20161030 for x86_64-apple-darwin): tcTyVarDetails cobox0_a1eK :: (m_a1ej[sk:2] :: Peano) ~# ('S n_a1eJ[ssk:3] :: Peano) Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1076:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1080:37 in ghc:Outputable pprPanic, called at compiler/basicTypes/Var.hs:457:22 in ghc:Var Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} When switching the call to `SBranchX` in line 29 to a call to `SBranch` the program compiles. So I suspect that the problem is rooted in the extra constraint attached to constructor `SBranchX`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12785 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12785: GHC panic, TypeFamily in equality constraint -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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 heisenbug): * Attachment "Tree.hs" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12785 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12785: GHC panic, TypeFamily in equality constraint -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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 heisenbug): Seems to be related to #12590, but it is not obvious how they are similar. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12785#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12785: GHC panic, TypeFamily in equality constraint -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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 heisenbug): Hmmm, looks like a case is not implemented. in `tcTyVarDetails` this constructor should be checked: {{{#!haskell Id { varName :: !Name, realUnique :: {-# UNPACK #-} !Int, varType :: Type, idScope :: IdScope, id_details :: IdDetails, -- Stable, doesn't change id_info :: IdInfo } -- Unstable, updated by simplifier }}} '''Note:''' `setTcTyVarDetails` also looks like it is not total. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12785#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12785: GHC panic, TypeFamily in equality constraint -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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 heisenbug): * Attachment "Var.hs.diff" added. This fixes the panic for me -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12785 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12785: GHC panic, TypeFamily in equality constraint -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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 heisenbug): With the attached patch I get: {{{ $ ghci Tree.hs GHCi, version 8.1.20161030: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Tree ( Tree.hs, interpreted ) Tree.hs:29:63: error: • Could not deduce: Payload ('S n1) (Payload n1 s1) ~ s arising from a use of ‘SBranchX’ from the context: m1 ~ 'S n1 bound by a pattern with constructor: Branch :: forall a (n :: Peano). a -> HTree n (HTree ('S n) a) -> HTree ('S n) a, in an equation for ‘nest’ at Tree.hs:29:7-51 • In the second argument of ‘($)’, namely ‘a `SBranchX` tr’ In the expression: Hide $ a `SBranchX` tr In an equation for ‘nest’: nest (Hide a `Branch` (nest . hmap nest -> Hide tr)) = Hide $ a `SBranchX` tr • Relevant bindings include tr :: STree n1 (STree ('S n1) (STree ('S ('S n1)) f)) s1 (bound at Tree.hs:29:49) a :: STree ('S m1) f s (bound at Tree.hs:29:12) nest :: HTree m1 (Hidden ('S m1) f) -> Hidden m1 (STree ('S m1) f) (bound at Tree.hs:27:1) Failed, modules loaded: none. }}} Please review... (and consider the note above) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12785#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12785: GHC panic, TypeFamily in equality constraint -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: yes Blocked By: | Blocking: Related Tickets: #12590 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by heisenbug): * testcase: => yes * related: => #12590 Comment: Another test case is available in #12590 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12785#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12785: GHC panic, `tcTyVarDetails` is missing a case -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: yes Blocked By: | Blocking: Related Tickets: #12590 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by heisenbug): * failure: None/Unknown => Compile-time crash or panic -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12785#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12785: GHC panic, `tcTyVarDetails` is missing a case
-------------------------------------+-------------------------------------
Reporter: heisenbug | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case: yes
Blocked By: | Blocking:
Related Tickets: #12590 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#12785: GHC panic, `tcTyVarDetails` is missing a case -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: yes Blocked By: | Blocking: Related Tickets: #12590 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Here's a much simpler program that also trips up the same error: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeFamilies #-} module Bug (foo) where import Data.Kind (Type) foo :: forall (dk :: Type) (c :: Type -> Type) (t :: dk -> Type) (a :: Type). (dk ~ Type) => (forall (d :: dk). c (t d)) -> Maybe (c a) foo _ = Nothing }}} To make things more interesting, on GHC HEAD this errors with: {{{ $ /opt/ghc/head/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.1.20161218 for x86_64-unknown-linux): tcTyVarDetails cobox_aCE :: (dk_aCl[sk:2] :: *) ~# (* :: *) Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/basicTypes/Var.hs:461:22 in ghc:Var }}} But on GHC 8.0.1 and 8.0.2, it compiles fine! So this is actually a regression. I don't know if heisenbug's patch fixes it, nor what commit caused this regression. I'll look later today. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12785#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12785: GHC panic, `tcTyVarDetails` is missing a case
-------------------------------------+-------------------------------------
Reporter: heisenbug | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case: yes
Blocked By: | Blocking:
Related Tickets: #12590 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):
* cc: simonpj (added)
Comment:
That patch did fix building the program in comment:7, FWIW.
Also, I found out that Simon's commit
a0899b2f66a4102a7cf21569889381446ce63833 caused the regression:
{{{
From a0899b2f66a4102a7cf21569889381446ce63833 Mon Sep 17 00:00:00 2001
From: Simon Peyton Jones

#12785: GHC panic, `tcTyVarDetails` is missing a case -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: yes Blocked By: | Blocking: Related Tickets: #12590 | Differential Rev(s): Phab:D2931 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: => Phab:D2931 Comment: I tried poking around the code from a0899b2f66a4102a7cf21569889381446ce63833. Interestingly, adding back the explicit `isTyVar` check to `isFloatedTouchableMetaTyVar` fixes the program in comment:7, but //not// heisenbug's program. I could try to hunt for the other function that trips up heisenbug's program, but chances are there other undiscovered programs that would trip up this panic through other means. Therefore, to minimize the chances of that happening, I've opted to open Phab:D2931, which simply reverts a0899b2f66a4102a7cf21569889381446ce63833. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12785#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12785: GHC panic, `tcTyVarDetails` is missing a case -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: yes Blocked By: | Blocking: Related Tickets: #12590 | Differential Rev(s): Phab:D2931 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): For the record, I was never convinced that Simon's a0899b2... was a good idea. I think we went with it thinking "let's try and see what happens". And now we see what happens! I advocate for reverting that commit. Simon, the message says that it slows GHC down, but why? If the check is compiled by a sufficiently smart compiler, it shouldn't slow a thing down in the common case. Right after the `isTyVar` check (which should be inlined), we do a `tcTyVarDetails`. This requires case-splitting on the constructor for the `Var`. All we want to do is to replace the default error continuation in the non-`TcTyVar` case with something that returns `False`. Or is GHC not a sufficiently smart compiler? :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12785#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12785: GHC panic, `tcTyVarDetails` is missing a case -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: yes Blocked By: | Blocking: Related Tickets: #12590 | Differential Rev(s): Phab:D2931 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK I have worked it out. We use `tyCoVarsOfType`, `tyCoVarsOfCt` etc to extract the free type variables of a type or constraint. We don't have functions `tyVarsOfType` etc; they would be simple to write, but we don't have them. That means that we may get unwanted coercion variables floating around in the result set. This is annoying, and one alternative would be to add a family of functions returning tyvars. But returning the coercion variables (which appear in casts in types) actually causes no trouble ''provided all the "is" functions return False for coercion variables''. For example, {{{ promoteTyVar tclvl tv | isFloatedTouchableMetaTyVar tclvl tv = ... | otherwise = return () }}} Here `tv` might be a coercion variable, but it'll be ignored provided `isFloatedTouchableMetaTyVar` ignores it. So I'm ok with revering the patch, but please can we add a big Note with those functions explaining why coercion variables can occur is happening? Incidentally, in `TcSimplify` we have this: {{{ ; let meta_tvs = filter (isTyVar <&&> isMetaTyVar) free_tvs ... -- The isTyVar needs to weed out coercion variables }}} Once `isMetaTyVar` filters out coercion variables, we can remove the `isTyVar` here. Reid: over to you. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12785#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12785: GHC panic, `tcTyVarDetails` is missing a case -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: yes Blocked By: | Blocking: Related Tickets: #12590 | Differential Rev(s): Phab:D2931 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): For the record, I'm fully agreed with comment:11. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12785#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12785: GHC panic, `tcTyVarDetails` is missing a case
-------------------------------------+-------------------------------------
Reporter: heisenbug | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case: yes
Blocked By: | Blocking:
Related Tickets: #12590 | Differential Rev(s): Phab:D2931
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#12785: GHC panic, `tcTyVarDetails` is missing a case -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T12785a, | typecheck/should_fail/T12785b Blocked By: | Blocking: Related Tickets: #12590 | Differential Rev(s): Phab:D2931 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * testcase: yes => typecheck/should_compile/T12785a, typecheck/should_fail/T12785b * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12785#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC