[GHC] #14904: Compiler panic (piResultTy)

#14904: Compiler panic (piResultTy) -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: 14873 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Type-checking the following type family {{{#!hs type family F (f :: forall a. g a) :: Type where F (f :: forall a. g a) = Int }}} panics with the message: {{{#!txt ghc: panic! (the 'impossible' happened) (GHC version 8.4.0.20180118 for x86_64-apple-darwin): piResultTy k_aVM[tau:1] a_aVF[sk:1] Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in ghc:Outputable pprPanic, called at compiler/types/Type.hs:950:35 in ghc:Type }}} The panic happens with HEAD, 8.4 and 8.2. 8.0 rejects the program with an error message, but even it panics on the following version: {{{#!hs type family F f :: Type where F ((f :: forall a. g a) :: forall a. g a) = Int }}} #14873 seemed somewhat related, so I tried with the patch implemented in 3d252037234ce48f9bdada7d5c9b1d8eba470829, but that fails with the same panic too. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14904 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14904: Compiler panic (piResultTy) -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 14873 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by kcsongor): * Attachment "Bug.hs" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14904 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14904: Compiler panic (piResultTy) -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 14873 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * keywords: => TypeInType Comment: This is clearly in my wheelhouse... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14904#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14904: Compiler panic (piResultTy) -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14873 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: 14873 => #14873 Comment: It looks like commit faec8d358985e5d0bf363bd96f23fe76c9e281f7 (`Track type variable scope more carefully.`) nabbed this one. After that commit, I get error messages instead of panics on each program in the ticket. For the first program: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Bug where import Data.Kind type family F (f :: forall a. g a) :: Type where F (f :: forall a. g a) = Int }}} {{{ $ ghc/inplace/bin/ghc-stage2 Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:8:1: error: You have written a *complete user-suppled kind signature*, but the following variable is undetermined: k0 :: * Perhaps add a kind signature. Inferred kinds of user-written variables: g :: k0 -> * f :: forall (a :: k0). g a | 8 | type family F (f :: forall a. g a) :: Type where | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} For the second program: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Bug2 where import Data.Kind type family F f :: Type where F ((f :: forall a. g a) :: forall a. g a) = Int }}} {{{ $ ghc/inplace/bin/ghc-stage2 Bug2.hs [1 of 1] Compiling Bug2 ( Bug2.hs, Bug2.o ) Bug2.hs:9:7: error: • Expected kind ‘forall (a :: k1). g a’, but ‘f’ has kind ‘k0’ • In the first argument of ‘F’, namely ‘((f :: forall a. g a) :: forall a. g a)’ In the type family declaration for ‘F’ | 9 | F ((f :: forall a. g a) :: forall a. g a) = Int | ^ }}} I'll add regression tests and close this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14904#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14904: Compiler panic (piResultTy) -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14873 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by kcsongor): Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14904#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14904: Compiler panic (piResultTy)
-------------------------------------+-------------------------------------
Reporter: kcsongor | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.2.2
checker) |
Resolution: | Keywords: TypeInType
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #14873 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#14904: Compiler panic (piResultTy) -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T14904a, | typecheck/should_fail/T14904b Blocked By: | Blocking: Related Tickets: #14873 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * testcase: => typecheck/should_fail/T14904a, typecheck/should_fail/T14904b * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14904#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14904: Compiler panic (piResultTy) -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T14904a, | typecheck/should_fail/T14904b Blocked By: | Blocking: Related Tickets: #14873 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Hooray for RyanGlScott! :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14904#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14904: Compiler panic (piResultTy) -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T14904a, | typecheck/should_fail/T14904b Blocked By: | Blocking: Related Tickets: #14873 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sighingnow): For `ASSERT`-enabled ghc-stage2, the testcase T14904b still raises an "ASSERT failed!" panic. Not sure if it's worth further fix. T14904b.hs: {{{#!hs import Data.Kind type family F f :: Type where F ((f :: forall a. g a) :: forall a. g a) = Int }}} The panic error message: {{{ λ ginplace\bin\ghc-stage2.exe--make T.hs [1 of 1] Compiling T14904b ( T.hs, T.o ) ghc-stage2.exe: panic! (the 'impossible' happened) (GHC version 8.5.20180608 for x86_64-unknown-mingw32): ASSERT failed! 1 0 k_aWM[tau:0] (g_aWI[sig:0] |> {co_aWV}) a_aX4[tau:0] Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler\utils\Outputable.hs:1161:37 in ghc:Outputable pprPanic, called at compiler\utils\Outputable.hs:1220:5 in ghc:Outputable assertPprPanic, called at compiler\\typecheck\\TcMType.hs:745:54 in ghc:TcMType CallStack (from -prof): TcRnDriver.tc_rn_src_decls (compiler\typecheck\TcRnDriver.hs:(496,4)-(560,7)) TcRnDriver.tcRnSrcDecls (compiler\typecheck\TcRnDriver.hs:259:25-65) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14904#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14904: Compiler panic (piResultTy)
-------------------------------------+-------------------------------------
Reporter: kcsongor | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone: 8.6.1
Component: Compiler (Type | Version: 8.2.2
checker) |
Resolution: fixed | Keywords: TypeInType
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| typecheck/should_fail/T14904a,
| typecheck/should_fail/T14904b
Blocked By: | Blocking:
Related Tickets: #14873 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#14904: Compiler panic (piResultTy) -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T14904a, | typecheck/should_fail/T14904b, | indexed-types/should_fail/T14904 Blocked By: | Blocking: Related Tickets: #14873 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: typecheck/should_fail/T14904a, typecheck/should_fail/T14904b => typecheck/should_fail/T14904a, typecheck/should_fail/T14904b, indexed- types/should_fail/T14904 Comment: I can't predict all the consequences of this bug, so even though it doesn't seem to cause problems in a non-DEBUG-enabled compiler, I suggest merging to 8.6. Again, Richard might you check my work? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14904#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14904: Compiler panic (piResultTy) -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T14904a, | typecheck/should_fail/T14904b, | indexed-types/should_fail/T14904 Blocked By: | Blocking: Related Tickets: #14873 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Checked. Looks good, except for the typo fix I pushed. Yes, this was an oversight. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14904#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC