Julian Fleischer wrote:
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?

My guess would be, that while 3 and 4 are both of a type instantiating Prelude.Num (your terminology "are Prelude.Nums" is quite confusing -- Prelude.Num is not a type but a type class), they need not be of the same type (e.g., 3 could be of type Integer, and 4 of type Double).

Jochem

--
Jochem Berndsen | joc...@functor.nl
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to