[GHC] #12081: TypeInType Compile-time Panic

#12081: TypeInType Compile-time Panic -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I've been playing around with GHC 8.0.1-rc4 release and got a panic from the following (stripped down) code: {{{#!hs {-# LANGUAGE TypeInType #-} data Nat = Z | S Nat class C (n :: Nat) where type T n :: Nat f :: (a :: T n) }}} {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.0.20160421 for x86_64-apple-darwin): isInjectiveTyCon sees a TcTyCon T }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12081 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12081: TypeInType Compile-time Panic -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * keywords: => TypeInType Comment: GHC should never panic, so this is certainly a bug. However, your program is not type-correct: any type that classifies a runtime value must have kind `Type` (same as `*`). The type of `f` is given as `(a :: T n)`, which has kind `T n`, not `Type`. I'm not sure what your goal is here, but even without the panic, this program would be rejected by GHC. Thanks for reporting! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12081#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12081: TypeInType Compile-time Panic -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by MichaelK): goldfire, Thanks for the explanation. For background, I've been trying to make a 'good' wrapper type for `Natural` whose type is effectively `Nat`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12081#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12081: TypeInType Compile-time Panic -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by MitchellSalad): I happened to hit this same panic with a simpler example: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE TypeInType #-} data Foo = forall (x :: Foo). Bar x }}} fails with: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): isInjectiveTyCon sees a TcTyCon Foo }}} Without -XTypeInType, it fails with: {{{ foo.hs:5:25: error: • Type constructor ‘Foo’ cannot be used here (Perhaps you intended to use TypeInType) • In the kind ‘Foo’ In the definition of data constructor ‘Bar’ In the data declaration for ‘Foo’ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12081#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12081: TypeInType Compile-time Panic -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by jstolarek): * cc: jstolarek (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12081#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12081: TypeInType Compile-time Panic
-------------------------------------+-------------------------------------
Reporter: MichaelK | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1-rc4
Resolution: | Keywords: TypeInType
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#12081: TypeInType Compile-time Panic -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash | dependent/should_fail/T12081 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => dependent/should_fail/T12081 * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12081#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC