#3412: the 'impossible' happened (expectJust chooseExternalIds)
-----------------------------+----------------------------------------------
Reporter: int-e | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 6.11 | Severity: normal
Keywords: | Testcase:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
-----------------------------+----------------------------------------------
This module fails to compile with ghc head (with optimizations and using a
'perf' build):
{{{
module Bug where
import Ix
newtype U = U Int deriving (Eq, Ord)
instance Ix U where
index (U from, U to) (U idx) = index (from, to) idx
}}}
The output is as follows - the underlined part is the identifier that it
fails to find. (I added a {{{++ show id}}} to the message.)
{{{
# ghc -c -fforce-recomp -O Bug.hs
ghc-stage2: panic! (the 'impossible' happened)
(GHC version 6.11.20090801 for i386-unknown-linux):
expectJust chooseExternalIds { GHC.Arr.$windex2 }
^^^^^^^^^^^^^^^^
}}}
Here's a stripped down version of {{{Ix.hs}}} that still exhibits the bug,
to make the example more self-contained. It has to be compiled with -O as
well:
{{{
module Ix2 where
class Ix a where
index :: (a, a) -> a -> Int
instance Ix Int where
index (m, n) i
| m <= i && i <= n = m - i
| otherwise = indexError i
{-# NOINLINE indexError #-}
indexError :: a -> b
indexError _ = undefined
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3412>
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