[GHC] #13871: GHC panic in 8.2 only: typeIsTypeable(Coercion)
GHC
ghc-devs at haskell.org
Fri Jun 23 23:44:02 UTC 2017
#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
More information about the ghc-tickets
mailing list