[cvs-nhc98] Matching instances of Num

Sven Panne Sven.Panne at aedion.de
Tue Jun 15 14:26:58 EDT 2004


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 at 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.



More information about the Cvs-nhc98 mailing list