Type classes and code generation

Bernard James POPE bjpop@cs.mu.OZ.AU
Tue, 17 Jun 2003 19:14:35 +1000 (EST)


> I had a discussion with someone over the type class mechanism and would like
> to clarify something.
> 
> When I compile this trivial program:
> 
> > module Main where
> > main = putStrLn (show (1 + 2))
> 
> with ghc -Wall, the compiler says:
> 
> Main.lhs:3:
>     Warning: Defaulting the following constraint(s) to type `Integer'
> 	     `Num a' arising from the literal `2' at Main.lhs:3
> 
> This implies to me that the compiler is generating the code for (+) for the
> particular instance, rather than using a run-time dispatch mechanism to
> select the correct (+) function. Is this correct, or am I way off? 

Hi,

I hope I've understod your question.

What this message is telling you is that the compiler is applying Haskell 98's
"defaulting" mechanism.

The numeric literals 1 and 2 in the code are overloaded, that is
they have type: Num a => a

When the program is run the calls to '+' and 'show' must be resolved to
particular instances. However the overloading of their arguments prevents
that. The overloading is thus ambiguous.

Haskell 98 has a rule that (very roughly) says when overloading is ambiguous
and it involves standard numeric classes, apply some defaults to resolve the
ambiguity. In this case the default rule is to resolve the outstanding
constraint 'Num a' with Integer (making the type of 1 and 2 Integer).

After defaulting the instances of + and show can be resolved. 

You can change the behaviour of defaulting, and even turn it off, try:

   module Main where 
   default ()
   ...

Compiling again with -Wall gives:

    Ambiguous type variable(s) `a' in the constraint `Num a'
    arising from the literal `2' at Foo.hs:6
    In the second argument of `(+)', namely `2'
    In the first argument of `show', namely `(1 + 2)'

You can also get the same effect as defaulting by putting explicit type
annotations in your program:

    main = putStrLn (show ((1 + 2) :: Integer)) 

The Haskell Report doesn't say a whole lot about _how_ to implement the
type class overloading, though from what I understand,
most implementations use a similar algorithm (dictionary passing).

You can read all about typical implementations in the literature.
Google for "Type Class", "Implementation", and maybe even "Haskell".

> Does the compiler *always* know what the actual instances being used are? 

A smart compiler can specialise the calls to overloaded functions in
circumstances when the type(s) of its arguments are also known. This is a
good thing because it tends to reduce the cost of overloading at runtime.

More aggresive forms of specialisation are also possible and discussed in
the literature.

I think if you look up the papers on implementing type classes your
questions should be answered. Mail me if you need some references.

Cheers,
Bernie.