> module Example where

I'm in a small quandary regarding some properties of instances I don't
fully understand.
What we have are three interrelated classes:

> class P t where
>       pmethod :: t -> t
> class Q t where
>       qmethod :: t -> t
>       fromNat :: Integer -> t
> class C t where
>       cmethod :: t -> t

And here the crucial instance:

> instance (P t, Q t) => C t where
>       cmethod = pmethod . qmethod

Now, the problematic aspect of all this is the following:

{hugs} Example> :type cmethod . fromNat $ 1
{hugs} cmethod . fromNat $ 1 :: (C a, Q a) => a

This is the expected typing, which I expect to be valid.

But the inferencer chokes on an actual binding like the following:
x = cmethod . fromNat $ 1

Example> let x = cmethod . fromNat $ 1 in 0
ERROR: Unresolved overloading
*** Type       : (Q a, P a) => Integer
*** Expression : let {...} in 0

For some reason, _explicitly_ typing it is okay. The other
confusing aspect of this is that it "picked up" a the constraint
(P a), which does not seem necessary. If anyone knows enough
about what's going on here to help me understand what's going on,
I'd be much obliged for any pointers, explanations, and so on.

This example originally arose while futzing around with
some instances on the numeric classes (as usual =).

Thanks,
Bill
--
<Jon_I> 'the Baire category theorem has no connection with
                category theory'
<Wo^tW> nonsense. *everything* is connected to category theory.
--

The unenlightening details behind all this:

> data Dummy = A | B deriving (Eq, Ord, Read, Show)
> instance P Dummy where
>       pmethod = id
> instance Q Dummy where
>       qmethod A = B
>       qmethod B = A
>       fromNat 0 = A
>       fromNat _ = B

Reply via email to