[cvs-nhc98] cvs commit: nhc98/src/compiler98 FixSyntax.hs
Malcolm Wallace
malcolm at glass.cse.ogi.edu
Wed Jun 16 10:23:10 EDT 2004
malcolm 2004/06/16 07:23:10 PDT
Modified files:
src/compiler98 FixSyntax.hs
Log:
Fix a pattern-matching bug. Consider the following example:
------------------------------------------------
module Foo where
newtype Blah = Blah Int deriving (Eq, Show)
instance Num Blah where
(Blah i) + (Blah j) = Blah (i + j)
...
fromInteger x = Blah (fromInteger x)
bar :: Blah -> Bool
bar 0 = False
bar _ = True
------------------------------------------------
nhc98 previously failed with:
Fail: What? matchAltIf at 15:9
because the dictionary for (Num.fromInteger {dict:Blah} 0) in the
pattern-match was being flattened to (Num.Blah.fromInteger 0), which
made it impossible to later choose the right instance of (Eq.==).
This fix ensures that fsExp knows whether it is in an expression
context or a pattern-context, and for patterns it now refuses to
flatten the dictionary.
Revision Changes Path
1.21 +69 -71 nhc98/src/compiler98/FixSyntax.hs
More information about the Cvs-nhc98
mailing list