#4203: ghc-6.12.3 fails to compile xmonad-0.9.1 tests
---------------------------------+------------------------------------------
Reporter: slyfox | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 6.12.3
Keywords: | Difficulty:
Os: Unknown/Multiple | Testcase: yet
Architecture: Unknown/Multiple | Failure: Compile-time crash
---------------------------------+------------------------------------------
Comment(by igloo):
Smaller example:
{{{
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Properties where
newtype NonNegative a = NonNegative a
deriving (Eq, Num, Show)
instance Num a => Arbitrary (NonNegative a) where
arbitrary = return 0
newtype EmptyStackSet = EmptyStackSet StackSet
instance Arbitrary EmptyStackSet where
arbitrary = do
_ <- arbitrary :: Gen (NonNegative Int)
return $ EmptyStackSet StackSet
newtype Gen a = Gen a
instance Monad Gen where
return a = Gen a
Gen m >>= k = Gen (let Gen m' = k m in m')
class Arbitrary a where
arbitrary :: Gen a
coarbitrary :: a
data StackSet = StackSet
}}}
{{{
ghc --make -O1 Properties.hs -Wall
[1 of 1] Compiling Properties ( Properties.hs, Properties.o )
ghc: panic! (the 'impossible' happened)
(GHC version 6.12.3 for x86_64-unknown-linux):
expectJust chooseExternalIds: wild_B1
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4203#comment:4>
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