Re: Type classes vs C++ overloading Re: [Haskell-cafe] Messing around with types [newbie]

I sent this message yesterday to Bulat but it was intended for the haskel
cafe, so I'm resending it here today.
Thank to everyone who answered me privately. Today I'll keep on
experimenting and read the reference you gave me.
Cristiano
---------- Forwarded message ----------
From: Cristiano Paris
Hello Cristiano,
Thursday, June 21, 2007, 4:46:27 PM, you wrote:
class FooOp a b where foo :: a -> b -> IO ()
instance FooOp Int Double where foo x y = putStrLn $ (show x) ++ " Double " ++ (show y)
this is rather typical question :)
I knew it was... :D unlike C++ which resolves any
overloading at COMPILE TIME, selecting among CURRENTLY available overloaded definitions and complaining only when when this overloading is ambiguous, type classes are the RUN-TIME overloading mechanism
your definition of partialFoo compiled into code which may be used with any instance of foo, not only defined in this module. so, it cannot rely on that first argument of foo is always Int because you may define other instance of FooOp in other module. "10" is really constant function of type:
10 :: (Num t) => t
i.e. this function should receive dictionary of class Num in order to return value of type t (this dictionary contains fromInteger::Integer->t method which used to convert Integer representation of 10 into type actually required at this place)
this means that partialFoo should have a method to deduce type of 10 in order to pass it into foo call. Let's consider its type:
partialFoo :: (FooOp t y) => y -> IO ()
when partialFoo is called with *any* argument, there is no way to deduce type of t from type of y which means that GHC has no way to determine which type 10 in your example should have. for example, if you will define
instance FooOp Int32 Double where
anywhere, then call partialFoo (5.0::Double) will become ambiguous
shortly speaking, overloading resolved based on global class properties, not on the few instances present in current module. OTOH, you build POLYMORPHIC functions this way while C++ just selects best-suited variant of overloaded function and hard-code its call
further reading: http://homepages.inf.ed.ac.uk/wadler/papers/class/class.ps.gz http://haskell.org/haskellwiki/OOP_vs_type_classes chapter 7 of GHC user's guide, "functional dependencies"
Mmmmmhhhh... your point is hard to understand for me. In his message, I can understand Bryan Burgers' point better (thanks Bryan) and I think it's somewhat right even if I don't fully understand the type machinery occuring during ghc compilation (yet). Quoting Bryan: "*From this you can see that 10 is not necessarily an Int, and 5.0 is *not necessarily a Double. So the typechecker does not know, given just 10 and 5.0, which instance of 'foo' to use. But when you explicitly told the typechecker that 10 is an Int and 5.0 is a Double, then the type checker was able to choose which instance of 'foo' it should use." So, let's see if I've understood how ghc works: 1 - It sees 5.0, which belongs to the Fractional class, and so for 10 belonging to the Num class. 2 - It only does have a (FooOp x y) instance of foo where x = Int and y = Double but it can't tell whether 5.0 and 10.0 would fit in the Int and Double types (there's some some of uncertainty here). 3 - Thus, ghci complains. So far so good. Now consider the following snippet: module Main where foo :: Double -> Double foo = (+2.0) bar = foo 5.0 I specified intentionally the type signature of foo. Using the same argument as above, ghci should get stuck in evaluating foo 5.0 as it may not be a Double, but only a Fractional. Surprisingly (at least to me) it works! So, it seems as if the type of 5.0 was induced by the type system to be Double as foo accepts only Double's. If I understand well, there's some sort of asymmetry when typechecking a function application (the case of foo 5.0), where the type signature of a function is dominant, and where typechecking an overloaded function application (the original case) since there type inference can't take place as someone could add a new overloading later as Bulat says. So, I tried to fix my code and I came up with this (partial) solution: module Main where class FooOp a b where foo :: a -> b -> IO () instance (Num t) => FooOp t Double where foo x y = putStrLn $ (show x) ++ " Double " ++ (show y) partialFoo :: Double -> IO () partialFoo = foo 10 bar = partialFoo 5.0 As you can see, I specified that partialFoo does accept Double so the type of 5.0 if induced to be Double by that type signature and the ambiguity disappear (along with relaxing the type of a to be simply a member of the Num class so 10 can fit in anyway). Problems arise if I add another instance of FooOp where b is Int (i.e. FooOp Int Int): module Main where class FooOp a b where foo :: a -> b -> IO () instance (Num t) => FooOp t Double where foo x y = putStrLn $ (show x) ++ " Double " ++ (show y) instance (Num t) => FooOp t Int where foo x y = putStrLn $ (show x) ++ " Int " ++ (show y) partialFoo = foo 10 bar = partialFoo (5.0::Double) while I thought could be solved likewise: module Main where class FooOp a b where foo :: a -> b -> IO () instance (Num t1, Fractional t2) => FooOp t1 t2 where foo x y = putStrLn $ (show x) ++ " Double " ++ (show y) instance (Num t1, Num t2) => FooOp t1 t2 where foo x y = putStrLn $ (show x) ++ " Int " ++ (show y) partialFoo = foo 10 bar = partialFoo 5.0 but it didn't work. Here's ghci's complaint: example.hs:7:0: Duplicate instance declarations: instance (Num t1, Fractional t2) => FooOp t1 t2 -- Defined at example.hs:7:0 instance (Num t1, Num t2) => FooOp t1 t2 -- Defined at example.hs:10:0 Failed, modules loaded: none. It seems that Num and Fractional are somewhat related. Any hint? Were my reasonings correct or was it only crap? Thanks, Cristiano

On Fri, Jun 22, 2007 at 10:57:58AM +0200, Cristiano Paris wrote:
Quoting Bryan:
"*From this you can see that 10 is not necessarily an Int, and 5.0 is *not necessarily a Double. So the typechecker does not know, given just 10 and 5.0, which instance of 'foo' to use. But when you explicitly told the typechecker that 10 is an Int and 5.0 is a Double, then the type checker was able to choose which instance of 'foo' it should use."
I would stress "typechecker does not know, given just 10 and 5.0, which instance of 'foo' to use". The statement "10 is not necessarily an Int" may be misleading. I would rather say "10 can be not only Int, but also any other type in the Num type class".
So, let's see if I've understood how ghc works:
1 - It sees 5.0, which belongs to the Fractional class, and so for 10 belonging to the Num class. 2 - It only does have a (FooOp x y) instance of foo where x = Int and y = Double but it can't tell whether 5.0 and 10.0 would fit in the Int and Double types (there's some some of uncertainty here).
The problem is not that it can't tell whether 5.0 and 10 would fit Int and Double (actually, they do fit), it's that it can't tell if they won't fit another instance of FooOp.
3 - Thus, ghci complains.
So far so good. Now consider the following snippet:
module Main where
foo :: Double -> Double foo = (+2.0)
bar = foo 5.0
I specified intentionally the type signature of foo. Using the same argument as above, ghci should get stuck in evaluating foo 5.0 as it may not be a Double, but only a Fractional. Surprisingly (at least to me) it works!
See above.
So, it seems as if the type of 5.0 was induced by the type system to be Double as foo accepts only Double's.
I think that's correct.
If I understand well, there's some sort of asymmetry when typechecking a function application (the case of foo 5.0), where the type signature of a function is dominant, and where typechecking an overloaded function application (the original case) since there type inference can't take place as someone could add a new overloading later as Bulat says.
There is no asymmetry. The key word here is *ambiguity*. In the (Double -> Double) example there is no ambiguity - foo is not overloaded, in other words it's a single function, so it suffices to check if the parameters have the right types. In your earlier example, both 5.0 and foo are overloaded. If you had more instances for FooOp, the ambiguity could be resolved in many ways, possibly giving different behaviour. Haskell doesn't try to be smart and waits for you to decide. And it pretends it doesn't see that there is only one instance, because taking advantage of this situation could give surprising results later.
but it didn't work. Here's ghci's complaint:
example.hs:7:0: Duplicate instance declarations: instance (Num t1, Fractional t2) => FooOp t1 t2 -- Defined at example.hs:7:0 instance (Num t1, Num t2) => FooOp t1 t2 -- Defined at example.hs:10:0 Failed, modules loaded: none.
Instances are duplicate if they have the same (or overlapping) instance heads. An instance head is the thing after =>. What's before => doesn't count.
It seems that Num and Fractional are somewhat related. Any hint?
It's not important here, but indeed they are: class (Num a) => Fractional a where Best regards Tomek

On 6/22/07, Tomasz Zielonka
The problem is not that it can't tell whether 5.0 and 10 would fit Int and Double (actually, they do fit), it's that it can't tell if they won't fit another instance of FooOp.
You expressed the concept in more correct terms but I intended the same... I'm starting to understand now.
Instances are duplicate if they have the same (or overlapping) instance heads. An instance head is the thing after =>. What's before => doesn't count.
So, the context is irrelevant to distinguishing instances?
It seems that Num and Fractional are somewhat related. Any hint?
It's not important here, but indeed they are: class (Num a) => Fractional a where
I see. Thank you Tomasz. Cristiano
participants (2)
-
Cristiano Paris
-
Tomasz Zielonka