[Haskell] GHC / Hugs Disagree on Constraints

oleg at pobox.com oleg at pobox.com
Sun Oct 10 18:49:17 EDT 2004


Dominic Steinitz wrote:

> Did you get the first solution to work? When I tried it with hugs -98 I got

Yes, in the process discovering some interesting behavior of
Hugs. Here's the complete code that works with Hugs

> module Foo where
>
> class Bits a
>
> instance (Ord a, Bits a, Bounded a, Integral a,
>                  Bits b, Bounded b, Integral b) =>
>     Bounded (LargeKey a b) where
>        minBound = 0
>        (maxBound :: (LargeKey a b)) =
> 	   (fromIntegral::Int->(LargeKey a b)) $
> 			   (1 + fromIntegral (maxBound::b))*
>                            (1 + fromIntegral (maxBound::a)) - 1
> data LargeKey a b = LargeKey a b deriving (Eq, Ord,Show)
> instance (Ord a, Eq a, Ord b, Show a, Show b) =>
>     Num (LargeKey a b) where
>        (+) = undefined
>        fromInteger = undefined

There are two interesting points: first, in order to add a type
annotation to the result of a function, we have to place the whole
function head in parenthesis, as in
	(maxBound :: (LargeKey a b)) = ...
That does confuse GHC and cause it to give some quite weird error
message. So, with parenthesis, it works in Hugs -98 but not in
GHC. Without the parenthesis, it works the other way around.

The other issue is an unnecessary type annotation on the function
fromIntegral. GHC works well without that annotation. Alas, Hugs
(November 2003) reports
	INTERNAL ERROR: findBtyvsInt

The second solution seems better: not only it is in Haskell98, it also
agrees with both Haskell systems.




More information about the Haskell mailing list