Matching instances of Num

Consider the following module: ------------------------------------------------ module Foo where newtype Blah = Blah Int deriving (Eq, Show) instance Num Blah where (Blah i) + (Blah j) = Blah (i + j) (Blah i) - (Blah j) = Blah (i - j) (Blah i) * (Blah j) = Blah (i * j) negate (Blah i) = Blah (negate i) abs (Blah i) = Blah (abs i) signum (Blah i) = Blah (signum i) fromInteger x = Blah (fromInteger x) bar :: Blah -> Bool bar 0 = False bar _ = True ------------------------------------------------ nhc98 (HEAD) fails with: ------------------------------------------------ panne@jeanluc:> nhc98 -c Foo.hs Fail: What? matchAltIf at 15:9 ------------------------------------------------ I'm not sure if the error is in FixSyntax.fsExp' or Case.matchAltIf itself because I don't know enough about nhc98's dictionary handling and pattern matching. Help required... :-} Cheers, S.

Sven Panne
bar :: Blah -> Bool bar 0 = False bar _ = True ------------------------------------------------ Fail: What? matchAltIf at 15:9 ------------------------------------------------
Fixed (I think). It didn't matter whether Blah was a data or a newtype; we got the same crash.
I'm not sure if the error is in FixSyntax.fsExp' or Case.matchAltIf itself because I don't know enough about nhc98's dictionary handling and pattern matching. Help required... :-}
It was in fsExp. It shouldn't have been flattening out dictionaries in patterns (only in expressions). Regards, Malcolm
participants (2)
-
Malcolm Wallace
-
Sven Panne