#5802: GHC Panic with PolyKinds and TypeFamilies
--------------------------------+-------------------------------------------
Reporter: dominiquedevriese | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (Type checker)
Version: 7.4.1-rc1 | Keywords: PolyKinds
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: Compile-time crash | Testcase:
Blockedby: | Blocking:
Related: 5768, 5717 |
--------------------------------+-------------------------------------------
The following crashes:
{{{
{-# LANGUAGE TypeOperators, PolyKinds, TypeFamilies, ExplicitForAll,
GADTs #-}
module GHCBug where
data Nat = Zero | Succ Nat
data NatV (a :: Nat) where
ZeroV :: NatV Zero
SuccV :: NatV n -> NatV (Succ n)
data Phantom t = Whoo
data ListV (a :: [*]) where
NilV :: ListV '[]
(:::) :: Phantom a -> ListV as -> ListV (a ': as)
type family (:+:) (a :: Nat) (b :: Nat) :: Nat
type instance Zero :+: b = b
type instance (Succ a) :+: b = Succ (a :+: b)
type family TReplicate (n :: Nat) (t :: *) :: [*]
type instance TReplicate Zero t = '[]
type instance TReplicate (Succ n) t = t ': TReplicate n t
replicateTList :: forall (n :: Nat). forall t.
NatV n -> Phantom t -> ListV (TReplicate n t)
replicateTList ZeroV _ = NilV
replicateTList (SuccV n) t = t ::: replicateTList n t
}}}
Potentially related to 5717 and 5768, although those two seem to be
related to ScopedTypeVariables? They also seem to have a different panic
message, although maybe this is because I'm using a debug-built GHC?
I'm not actually using 7.4.1-rc1, but 7.4 HEAD at the time of this
writing.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5802>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs