#2649: 6.10 regression: panic in tyFamInsts on invalid code
-------------------------+--------------------------------------------------
Reporter: Deewiant | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 6.9 | Severity: normal
Keywords: | Testcase:
Architecture: x86 | Os: Windows
-------------------------+--------------------------------------------------
{{{
{-# LANGUAGE ScopedTypeVariables, Rank2Types #-}
module Asdf where
g :: Num a => a -> (forall a. a -> Int) -> Int
g = flip id
f = g 0 $ \(_ :: forall a. Num a => a) -> 0
}}}
{{{
>ghc -c asdf.hs
ghc: panic! (the 'impossible' happened)
(GHC version 6.10.0.20081002 for i386-unknown-mingw32):
types\Type.lhs:(881,0)-(889,46): Non-exhaustive patterns in
function tyFamInsts
}}}
With 6.8.2 I get instead the following, which I think is correct:
{{{
] ghc -XPatternSignatures -c asdf.hs
asdf.hs:7:12:
Couldn't match expected type `a'
against inferred type `forall a1. (Num a1) => a1'
`a' is a rigid type variable bound by
the polymorphic type `forall a. a -> Int' at asdf.hs:7:4
In the pattern: _ :: forall a. (Num a) => a
In the second argument of `($)', namely
`\ (_ :: forall a. (Num a) => a) -> 0'
In the expression: g 0 $ \ (_ :: forall a. (Num a) => a) -> 0
}}}
On the other hand, replacing `f` with:
{{{
f = g 0 $ ((\_ -> 0) :: forall a. Num a => a -> Int)
}}}
Works fine. I don't know why the original code is invalid but it certainly
shouldn't cause a panic.
6.10 wasn't available in the "Version" listing so I filed this for 6.9.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2649>
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