[GHC] #8017: Empty instance
GHC
ghc-devs at haskell.org
Thu Jun 27 21:46:32 CEST 2013
#8017: Empty instance
-----------------------+----------------------------------------------------
Reporter: wvv | Owner:
Type: bug | Status: new
Priority: normal | Component: GHCi
Version: 7.6.3 | Keywords:
Os: Windows | Architecture: x86
Failure: GHCi crash | Blockedby:
Blocking: | Related:
-----------------------+----------------------------------------------------
Progam
{{{
module T1 where
data T = T1 | T2
instance Eq T
t :: T -> T -> Bool
t = (==)
}}}
use ghci (Windows XP, 32 bit)
{{{
GHCi, version 7.6.3: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Prelude> :cd M:\Haskell
Prelude> :load "T1.hs"
[1 of 1] Compiling T1 ( T1.hs, interpreted )
Ok, modules loaded: T1.
*T1> t T1 T2
*** Exception: stack overflow
*T1>
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/8017>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list