#6068: Panic in GHCi when using functional dependencies and promoted kinds
------------------------------+---------------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Component: GHCi
Version: 7.5 | Keywords: PolyKinds
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: GHCi crash | Testcase:
Blockedby: | Blocking:
Related: |
------------------------------+---------------------------------------------
Consider the following code:
{{{
{-# LANGUAGE PolyKinds, DataKinds, TypeFamilies, GADTs,
MultiParamTypeClasses,
FunctionalDependencies, FlexibleInstances,
UndecidableInstances #-}
import Prelude hiding (Maybe, Nothing)
data Maybe :: * -> * where
Nothing :: Maybe a
data family Sing (a :: k)
data instance Sing (a :: Maybe k) where
SNothing :: Sing Nothing
data KProxy (a :: *) = KProxy
data Existential (p :: KProxy k) =
forall (a :: k). Exists (Sing a)
class HasSingleton a (kp :: KProxy k) | a -> kp where
exists :: a -> Existential kp
instance forall a (mp :: KProxy (Maybe ak)). HasSingleton (Maybe a) mp
where
exists Nothing = Exists SNothing
}}}
When I load it into GHCi and ask for
{{{
*Main> :t exists Nothing
}}}
I get the following:
{{{
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 7.5.20120426 for x86_64-apple-darwin):
tcTyVarDetails ak{tv avTW} [tv]
}}}
When I add {{{foo = exists Nothing}}} to the end of the compiled code,
however, the behavior is as expected. I did try adding all relevant GHC
extensions to the running instance of GHCi, but that did not solve the
problem.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/6068>
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