[Haskell-cafe] MultiParamTypeClasses, FunctionalDependencies and FlexibleInstances using GHCi

Julian Fleischer julian.fleischer at fu-berlin.de
Fri May 14 08:18:42 EDT 2010


Hello,

i'm playin' around with GHCs Haskell and some extensions. I'm already aware of that functional dependencies are "very very tricky", but there is something I don't understand about there implementation in GHC. I've constructed my own TypeClass "Num" providing a signature for (+), having multiple params a, b and c. I'm than declaring a (flexible) Instance for Prelude.Num, simply using (Prelude.+) for the definition of my (+) - and it does not work as I expect it to.

First, this is the code:
> {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, TypeSynonymInstances, FlexibleInstances #-}
> import qualified Prelude
> 
> class Num a b c | a b -> c where
> 	(+) :: a -> b -> c
> 
> instance (Prelude.Num x) => Num x x x where
> 	(+) = (Prelude.+)

now if I load it into GHCi and type "3 + 4" i get a whole bunch of error-messages.

I do understand that
> (3::Prelude.Int) + (4::Prelude.Int)
works, since I've explicitly declared 3 and 4 to be Prelude.Int and there is a functional dependency stating that (+) :: a b determines the results type c, by the Instance declaration cleary c will be the same as a and b.

Now, if I type
> 3 + 4
it does not work, and i really don't understand why. If i ask GHCi for 3's type ($ :t 3) it will answer "3 :: (Prelude.Num t) => t". But, if 3 and 4 are Prelude.Nums and there is an instanfe Num x x x for x of Prelude.Num - than why can't GHC deduce from the definitions that 3 and 4, both Prelude.Nums, can be used with (+) since there is an instance for Prelude.Num and my class Num - and the result will of course be something of Prelude.Num?

best regards,
Julian
-------------- next part --------------
A non-text attachment was scrubbed...
Name: smime.p7s
Type: application/pkcs7-signature
Size: 3633 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20100514/59c3e676/smime.bin


More information about the Haskell-Cafe mailing list