#3067: GHCi panics with 'initTc:LIE' while :stepping on code with funny types
-----------------------------+----------------------------------------------
Reporter: mnislaih | Owner:
Type: bug | Status: new
Priority: normal | Component: GHCi
Version: 6.10.1 | Severity: normal
Keywords: | Testcase:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
-----------------------------+----------------------------------------------
This is due to runtime type reconstruction not dealing correctly with type
functions.
I managed to come up a minimal example.
{{{
{-# LANGUAGE TypeFamilies #-}
type family Id x
type instance Id Int = Int
type instance Id Bool = Bool
class Convert x y where convert :: x -> y
instance Convert x x where convert = id
f :: Convert a (Id a) => a -> Id a
f x = convert x
g :: Convert a (Id a) => a -> Id a
g x = let x' = f x in x'
}
{{{
[1 of 1] Compiling Main ( ../code/debuggerExamples/lie.hs,
interpreted )
Ok, modules loaded: Main.
*Main GOA> :step g False
:step g False
Stopped at ../code/debuggerExamples/lie.hs:15:0-23
_result :: Id a = _
14 g :: Convert a (Id a) => a -> Id a
15 g x = let x' = f x in x'
^^^^^^^^^^^^^^^^^^^^^^^^
[../code/debuggerExamples/lie.hs:15:0-23] *Main GOA> :step
:step
ghc: panic! (the 'impossible' happened)
(GHC version 6.10.1 for i386-apple-darwin):
initTc:LIE
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3067>
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