#2587: Optimiser bug with extistentials and GADT's
----------------------------------------------------------------------------------------+
Reporter: NeilMitchell
| Owner:
Type: bug
| Status: new
Priority: normal
| Component: Compiler
Version: 6.9
| Severity: normal
Keywords: [EMAIL PROTECTED], [EMAIL PROTECTED] | Testcase:
Architecture: Unknown
| Os: Unknown
----------------------------------------------------------------------------------------+
Given the program:
{{{
{-# LANGUAGE GADTs, ExistentialQuantification #-}
module GadtBug(bug) where
data Existential = forall a . Existential (Gadt a)
data Gadt a where Value :: Gadt Double
bug = [ match undefined | ps <- undefined, _ <- ps ]
where
match (Existential _) = undefined
match (Existential _) = undefined
}}}
Using GHC Head from yesterday, compiling without optimisations I get:
{{{
C:\Neil>ghc --make GadtBug.hs
[1 of 1] Compiling GadtBug ( GadtBug.hs, GadtBug.o )
GadtBug.hs:11:8:
Warning: Pattern match(es) are overlapped
In the definition of `match': match (Existential _) = ...
}}}
With optimisations (-O or -O2) I get:
{{{
C:\Neil\paradise-bug-csdg\alone>ghc --make GadtBug.hs -O
[1 of 1] Compiling GadtBug ( GadtBug.hs, GadtBug.o )
GadtBug.hs:11:8:
Warning: Pattern match(es) are overlapped
In the definition of `match': match (Existential _) = ...
ghc: panic! (the 'impossible' happened)
(GHC version 6.9.20080905 for i386-unknown-mingw32):
idInfo a{tv ag4} [sk]
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
-- Neil
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2587>
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