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

Tomasz Zielonka tomasz.zielonka at gmail.com
Fri Jun 22 05:46:13 EDT 2007


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


More information about the Haskell-Cafe mailing list