Sorry if this is caused by exactly the same as my last tcLookupTyVar
report. Since I can't tell, I'll report it anyway.

   panic! (the `impossible' happened):
           tcLookupTyVar:a_r6F

   Please report it as a compiler bug to [EMAIL PROTECTED]


If the instance definition for (*) at the end of this toy module
is replaced by the definition that is commented, this all compiles
fine. Strange, because the two implementations are equivalent modulo
the theory {(*) = multiply}.

Remove the `multiply :: a -> a -> a' part, and it compiles without
problems.


Hope this helps.


Regards,


Marc van Dongen

****************************************************************************

> module Rings( Group, Ring ) where

> import qualified Prelude( Ord(..), Eq(..), Num(..) )
> import Prelude hiding( Ord(..), Eq(..), Num(..), MonadZero( zero ) )

> class Group a where
>   compare     :: a -> a -> Prelude.Ordering
>   fromInteger :: Integer -> a
>   (+) :: a -> a -> a
>   (-) :: a -> a -> a
>   zero :: a
>   one  :: a
>   zero = fromInteger 0
>   one  = fromInteger 1

> -- class (Group a) => Ring a where
> -- (*) :: a -> a -> a
> -- (*) a b =
> --                  case (compare a zero) of
> --                    EQ -> zero
> --                    LT -> zero - ((*) (zero - a) b)
> --                    GT -> case compare a one of
> --                            EQ -> b
> --                            _  -> b + ((*) (a - one) b)

> class (Group a) => Ring a where
>   (*) :: a -> a -> a
>   (*) a b = multiply a b
>           where multiply :: a -> a -> a
>                 multiply a b
>                   = case (compare a zero) of
>                       EQ -> zero
>                       LT -> zero - (multiply (zero - a) b)
>                       GT -> case compare a one of
>                               EQ -> b
>                               _  -> b + (multiply (a - one) b)

Reply via email to