[GHC] #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion)

#13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 (Type checker) | Keywords: TypeInType, | Operating System: Unknown/Multiple Typeable | Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This code works fine in GHC 8.0.1 and 8.0.2: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} module Foo where import Data.Kind data Foo (a :: Type) (b :: Type) where MkFoo :: (a ~ Int, b ~ Char) => Foo a b data family Sing (a :: k) data SFoo (z :: Foo a b) where SMkFoo :: SFoo MkFoo }}} But in GHC 8.2 and HEAD, it panics: {{{ $ /opt/ghc/8.2.1/bin/ghci Bug.hs GHCi, version 8.2.0.20170622: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Foo ( Bug.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.0.20170622 for x86_64-unknown-linux): typeIsTypeable(Coercion) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13871 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: TypeInType, Resolution: | Typeable Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: bgamari (added) Comment: Commit 8fa4bf9ab3f4ea4b208f4a43cc90857987e6d497 (Type-indexed Typeable) caused this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13871#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: TypeInType, Resolution: | Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13871 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * testcase: => typecheck/should_compile/T13871 * owner: (none) => bgamari Comment: Oh dear, yes, I was slightly worried about issues like this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13871#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: TypeInType, Resolution: | Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13871 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3671, Wiki Page: | Phab:D3672 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D3671, Phab:D3672 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13871#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13871: GHC panic in 8.2 only: typeIsTypeable(Coercion)
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: bgamari
Type: bug | Status: patch
Priority: high | Milestone: 8.2.1
Component: Compiler (Type | Version: 8.2.1-rc2
checker) | Keywords: TypeInType,
Resolution: | Typeable
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Compile-time | Test Case:
crash or panic | typecheck/should_compile/T13871
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3671,
Wiki Page: | Phab:D3672
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13871: GHC panic in 8.2 only: typeIsTypeable(Coercion)
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: bgamari
Type: bug | Status: patch
Priority: high | Milestone: 8.2.1
Component: Compiler (Type | Version: 8.2.1-rc2
checker) | Keywords: TypeInType,
Resolution: | Typeable
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Compile-time | Test Case:
crash or panic | typecheck/should_compile/T13871
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3671,
Wiki Page: | Phab:D3672
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: merge Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: TypeInType, Resolution: | Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13871 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3671, Wiki Page: | Phab:D3672 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13871#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: TypeInType, Resolution: fixed | Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13871 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3671, Wiki Page: | Phab:D3672 -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged with 40cb68a606ceb082815b2452bfb4eac6ea57522b. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13871#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: TypeInType, Resolution: fixed | Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13871 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3671, Wiki Page: | Phab:D3672 -------------------------------------+------------------------------------- Comment (by goldfire): I take it as an eventual goal to have ''all'' types be `Typeable`. Is there a ticket requesting support for types with casts/coercions? I don't think it would be terribly hard to do. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13871#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13871: GHC panic in 8.2 only: typeIsTypeable(Coercion) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Keywords: TypeInType, Resolution: fixed | Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13871 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3671, Wiki Page: | Phab:D3672 -------------------------------------+------------------------------------- Comment (by bgamari): I don't believe there is one. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13871#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC