I said:

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

That is if the `a -> a -> a' in my previous posting is replaced by
               `(Group a) => a -> -> a'.
It still crashes though.

| Remove the `multiply :: (Group a) => a -> a -> a' part, and it compiles without
| problems.

> 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 :: (Group a) => a -> a -> a

Group a => added

>                 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)

________________________________________________________________
                       Marc van Dongen | phone:   +353 21 903083
        Department of Computer Science | Fax:     +353 21 903113
University College Cork, Cork, Ireland | Email: [EMAIL PROTECTED]

Reply via email to