[GHC] #12007: Pattern families regression

#12007: Pattern families regression -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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 following code compiles fine for me in GHC 7.10.1, but fails in GHC 8.1.20160502 {{{ {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ViewPatterns #-} data Foo a = Foo a a pattern A a1 a2 = Foo a1 a2 pattern B a1 a2 = A a1 a2 }}} The problem is the nested pattern. Compiling gives: {{{ [1 of 1] Compiling Main ( Bug1.hs, interpreted ) ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.1.20160502 for x86_64-unknown-linux): kindPrimRep.go rep_a85f Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12007 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12007: Pattern families regression -------------------------------------+------------------------------------- Reporter: MikeIzbicki | 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 MikeIzbicki): * version: 7.10.3 => 8.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12007#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12007: Pattern families regression -------------------------------------+------------------------------------- Reporter: MikeIzbicki | 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 mpickering): I think this only happens when loading the file into ghci? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12007#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12007: Pattern families regression -------------------------------------+------------------------------------- Reporter: MikeIzbicki | 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 Iceland_jack): Defining it in ghci seems to work {{{ ghci> data Foo a = Foo a a ghci> pattern A x y = Foo x y ghci> pattern B x y = A x y ghci> }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12007#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12007: Pattern families regression -------------------------------------+------------------------------------- Reporter: MikeIzbicki | 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 mpickering): * cc: goldfire (added) Comment: So I could trigger the same panic with the example here https://ghc.haskell.org/trac/ghc/ticket/11549#comment:1 with rc-3 but it is fixed in HEAD. Here is the core which I think is causing the panic. Maybe Richard can look and see if he thinks anything dodgy is going on? Maybe there is some improper use of runtime rep polymorphism. {{{ -- RHS size: {terms: 18, types: 21, coercions: 0} T12007.$mB :: forall r_a19o t_a19m. Foo t_a19m -> (t_a19m -> t_a19m -> r_a19o) -> (GHC.Prim.Void# -> r_a19o) -> r_a19o [GblId, Arity=3, Caf=NoCafRefs] T12007.$mB = \ (@ (rep_a19n :: GHC.Types.RuntimeRep)) (@ (r_a19o :: TYPE rep_a19n)) (@ t_a19m) (scrut_a19q :: Foo t_a19m) (cont_a19r :: t_a19m -> t_a19m -> r_a19o) (fail_a19s :: GHC.Prim.Void# -> r_a19o) -> let { cont1_a19h :: t_a19m -> t_a19m -> r_a19o [LclId, Arity=2] cont1_a19h = \ (a1_a18K :: t_a19m) (a2_a18L :: t_a19m) -> cont_a19r a1_a18K a2_a18L } in case scrut_a19q of { Foo a1_a18I a2_a18J -> cont_a19r a1_a18I a2_a18J } }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12007#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12007: Pattern families regression -------------------------------------+------------------------------------- Reporter: MikeIzbicki | 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 MikeIzbicki): Replying to [comment:4 mpickering]:
So I could trigger the same panic with the example here https://ghc.haskell.org/trac/ghc/ticket/11549#comment:1 with rc-3
but it is fixed in HEAD.
I just updated my GHC repo and rebuilt GHC today before submitting, so I thought I tested it with HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12007#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12007: Pattern families regression -------------------------------------+------------------------------------- Reporter: MikeIzbicki | 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 mpickering): Sorry I was unclear in my last comment. The examples form the comment triggered the same kind of error in older builds but are now fixed. I can still reproduce the error you report but only when loading the file into ghci. I'm suggesting that whatever check is used to reject the now fixed examples should also reject the internally generated matching function which causes this panic. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12007#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms 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 mpickering): * keywords: => PatternSynonyms -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12007#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms 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 mpickering): Mike, does this happen for you when you compile the file normally? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12007#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms 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 MikeIzbicki): Replying to [comment:8 mpickering]:
Mike, does this happen for you when you compile the file normally?
No. It only happens when I load it in ghci. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12007#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms 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): I have learned a bit more. * Here is a smaller test case {{{ pattern A a1 = a1 pattern B a1 = A a1 }}} * The bug is that `kindRep` falls over. I'm pretty sure it's the call from `typePrimRep`. * The code spat out by `CorePrep` is absolutely fine. * The crash comes when the bytecode codegen gets hold of it. I wish I knew ''which'' call to `typePrimRep` in the bytecode generator was causing the crash. Maybe someone can try stack-tracing (with our new lightweight `CallStack` stuff) to narrow it down? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12007#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms 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 wanted a break from dissertation-writing so I took a look. The problem is surely in the byte-code generator, which is opaque to me. The nub of the problem seems to be here: {{{#!hs -- introduce a let binding for a ticked case expression. This rule -- *should* only fire when the expression was not already let-bound -- (the code gen for let bindings should take care of that). Todo: we -- call exprFreeVars on a deAnnotated expression, this may not be the -- best way to calculate the free vars but it seemed like the least -- intrusive thing to do schemeE d s p exp@(AnnTick (Breakpoint _id _fvs) _rhs) = if isUnliftedType ty then do ... else do id <- newId ty ... where exp' = deAnnotate' exp ty = exprType exp' }}} The problem is that `ty :: TYPE rep` for a skolem `rep`. So we've created an abomination: a runtime variable (the `id`) whose type is representation polymorphic. Indeed, even the `isUnliftedType` query is bogus, because there is no way to know whether or not `ty` is unlifted at this point. How we've gotten here or what this code is doing, I don't know. But this is definitely the source of the problem! I'm afraid I won't have a chance to dig deeper here, but hopefully these bread crumbs can be picked up by the next traveler. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12007#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12007: Panic when loading file with nested pattern synonyms into ghci
-------------------------------------+-------------------------------------
Reporter: MikeIzbicki | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
Resolution: | Keywords:
| PatternSynonyms
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

#12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/scripts/T12007 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge * testcase: => ghci/scripts/T12007 Comment: Maybe merge to 8.0 branch in due course -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12007#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/scripts/T12007 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Merged to `ghc-8.0` as 726d1ddba45d24c998ae378ed5e688a2d24665e7. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12007#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/scripts/T12007 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.0.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12007#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/scripts/T12007 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12007#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC