#3528: GHC crash: equality and class contexts on datatype accessor
-------------------+--------------------------------------------------------
Reporter: guest | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (Type checker)
Version: 6.10.4 | Severity: normal
Keywords: | Testcase:
Os: Linux | Architecture: x86
-------------------+--------------------------------------------------------
The following program:
{{{
{-# LANGUAGE FlexibleContexts, NoMonomorphismRestriction, Rank2Types,
TypeFamilies #-}
module Foo where
class A a
data B b = B {
c :: (Int ~ Int, A b) => Int
}
d = c
}}}
produces the following bug when compiled with 'ghc foo.hs':
{{{
ghc: panic! (the 'impossible' happened)
(GHC version 6.10.4 for i386-unknown-linux):
applyTypeToArgs
ipv{v B4} [lid] $dA{v ag5} [lid]
(ghc-prim:GHC.Types.Int{(w) tc 3J}
~
ghc-prim:GHC.Types.Int{(w) tc 3J},
main:Foo.A{tc rfx} b{tv ag2} [sk]) =>
ghc-prim:GHC.Types.Int{(w) tc 3J}
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3528>
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