[cvs-nhc98] patch applied (hat): Fix a pattern-matching bug. Consider the following example:

Malcolm Wallace Malcolm.Wallace at cs.york.ac.uk
Tue Oct 10 07:27:16 EDT 2006


Wed Jun 16 07:23:09 PDT 2004  malcolm
  * 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.

    M ./src/compiler98/FixSyntax.hs -71 +69


More information about the Cvs-nhc98 mailing list