#3382: Panic in tidyNPat when using N+k patterns with overloaded strings
-----------------------------+----------------------------------------------
Reporter: batterseapower | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 6.10.4 | Severity: normal
Keywords: | Testcase:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
-----------------------------+----------------------------------------------
Spotted this while reading the source code to tidyNPat. It looked dubious
to me, and indeed it is:
{{{
{-# OPTIONS_GHC -XOverloadedStrings #-}
module Main where
import Data.String
instance IsString Int where
fromString x = 1337
f :: Int -> String
f "hello" = "correct"
f _ = "false"
main = do
print $ f 1337
print $ f 1338
}}}
Result:
{{{
mbolingbr...@mb566 ~/Programming/Checkouts
$ ghc --make Boog.hs
[1 of 1] Compiling Main ( Boog.hs, Boog.o )
ghc: panic! (the 'impossible' happened)
(GHC version 6.10.3 for i386-apple-darwin):
tidyNPat
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3382>
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