[Haskell-cafe] Re: Inferring types from functional dependencies

oleg at pobox.com oleg at pobox.com
Sat Jun 10 05:38:14 EDT 2006


Jeff Harper defined typeclasses
> class Reciprocate a b | a -> b where
>      recip :: a -> b
> class Multiply a b c  | a b -> c where
>     (*) :: a -> b -> c

and encountered the problem with

> -- Here I define a default (/) operator that uses the
> -- Reciprocate and Multiply class to perform division.
> class (Reciprocate b recip, Multiply a recip c) => Divide a b c | a b -> c
> where
>     (/) :: a -> b -> c
>     (/) x y = x * (recip y)

which doesn't work, because the type variable 'recip' doesn't
appear in the class head. He wrote

> I also, wonder if it would be appropriate to include in future
> versions of Haskell, the ability to infer functional dependences in a
> new class definition, so that my first attempt at a definition of
> class Divide works.


I'm afraid there may be the problem with the example rather than with
Haskell. Let us suppose that the above definition of Divide
works. Jeff Harper writes elsewhere

> However, taking the reciprocal and then multiplying may not always be
> the best way of dividing.  So, I'd like to put this into a divide
> class, so (/) can be defined differently for different types.

The key phrase is that we wish (/) defined differently for different
types, because using reciprocals is not always the best way of
dividing. Then why do we insist that every instance of Divide must be
also an instance of Reciprocate (because that's what the definition of
Divide says)? Why is that that whenever we divide something by the
value of type 'b', it must be possible to reciprocate that value of
type b? Even if we don't use reciprocals in the division?

If we assume that we need Reciprocate only if we are going to use the 
'default' method, the solution becomes obvious. It does involve
overlapping and undecidable instances, sorry. These extensions are
really useful in practice. Here's the solution:

> class Divide a b c | a b -> c where
>     (/) :: a -> b -> c


Here's the most general instance. It applies when nothing more
specific does.  It is in this case that we insist on being able to
take the reciprocal:

> instance (Reciprocate b recip, Multiply a recip c) =>
>     Divide a b c where
>     (/) x y = x * (recip y)

Now, a specific instance only for Integers, which involves no
reciprocals:

> instance Divide Integer Integer (Ratio Integer) where
>     (/) = (%)

Another specific instance. It too involves no
reciprocals. Incidentally, the posted code does not even define an
instance of Reciprocate for Ints!

> instance Divide Int Int (Ratio Integer) where
>     x / y = (fromIntegral x) % (fromIntegral y)

A few tests:

> test0 = (1::Int) / (2::Int)
> test1 = (1::Integer) / (2::Integer)
> test2 = (1::Double) /(2::Double)


P.S. A remark for Haskell': the most general instance above (repeated
below)

> instance (Reciprocate b recip, Multiply a recip c) =>
>     Divide a b c where
>     (/) x y = x * (recip y)

shows why we can never be satisfied with only decidable instances --
why we need the undecidable instances extension. The instance makes it
clear that we cannot decide if the instance selection process for
Divide terminates just by looking at this instance. There is no
information to decide on termination: we must examine instances of
Reciprocate and Multiply (in particular, we should check if those
instances refer back to Divide). Thus, no _local_ instance termination
criterion would ever be able to handle above instance. OTH, it seems
quite unreasonable to require a Haskell system to employ a global
instance selection termination criterion (short of recursion stack
limit or other such `dynamic' test).




More information about the Haskell-Cafe mailing list