Re: [GHC] #3382: Panic in tidyNPat when using N+k patterns with overloaded strings

2009-07-21 Thread GHC
#3382: Panic in tidyNPat when using N+k patterns with overloaded strings
-+--
Reporter:  batterseapower|Owner:  
Type:  bug   |   Status:  closed  
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.10.4  
Severity:  normal|   Resolution:  fixed   
Keywords:|   Difficulty:  Unknown 
Testcase:  deSugar/should_run/T3382  |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by simonpj):

  * testcase:  => deSugar/should_run/T3382
  * difficulty:  => Unknown
  * status:  new => closed
  * resolution:  => fixed

Comment:

 Ah yes, excellent point.  Fixed by
 {{{
 Mon Jul 20 07:12:26 GMT Daylight Time 2009  simo...@microsoft.com
   * Fix Trac #3382: desugaring of NPats

   Max spotted that the short-cut rules for desugaring NPats (where
   we compare against a literal) were wrong now that we have overloaded
   strings.
 }}}
 thanks

 Simon

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #3382: Panic in tidyNPat when using N+k patterns with overloaded strings

2009-07-18 Thread GHC
#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: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs