[Haskell-cafe] Justification for Ord inheriting from Eq?

Brian Hulley brianh at metamilk.com
Thu Apr 6 20:28:33 EDT 2006


John Meacham wrote:
> On Thu, Apr 06, 2006 at 10:52:52PM +0100, Brian Hulley wrote:
>>[snip]
>> The problem of allowing classes (in Haskell) to inherit is that you
>> end up with heirarchies which fix the design according to some
>> criteria which may later turn out to be invalid, whereas if there
>> were no hierarchies then you could just use the particular classes
>> that are needed for the particular function, eg explicitly supplying
>> Eq and Ord instead of just Ord etc (though for a sort function Ord
>> by itself would be sufficient).
>
> well, there are a few reasons you would want to use inheritance in
> haskell, some good, some bad.
>
> 1. one really does logically derive from the other, Eq and Ord are
> like this, the rules of Eq says it must be an equivalance relation
> and that Ord defines a total order over that equivalance relation.
> this is a good thing, as it lets you write code that depends on these
> properties.

As Steve and Robert pointed out, you can't always rely on these properties 
(although it is debatable whether or not floats and doubles have any useful 
numeric properties in the first place).

Also, the use of Ord for sorting comes with extra baggage in the form of a 
total order whereas you might have just wanted to sort some values of a type 
where there is only a partial order. Thus the bundling of < > <= >= 
together, with == being defined in terms of <=  seems overly restrictive.

[rearranged]
> the inflexability of the class hierarchy was my motivation for the
> class aliases proposal.
>
> http://repetae.net/john/recent/out/classalias.html

What about:

class Eq a where (==), (/=) :: ...
class PartialOrd a where
     (<), (>) :: a->a->Bool
     x > y = y < x

class (PartialOrd a) => TotalOrd a where x <= y = not (y < x) ....
   -- => not meaning inheritance but just a restriction on a for use of 
TotalOrd

class alias Ord a = (Eq a, PartialOrd a, TotalOrd a)
   -- components of Ord all on the same level

Then sort could be declared as sort :: PartialOrd a => [a] -> [a]

Changing the subject slightly, a minor problem (no doubt you've already 
noticed it) is that if you allow instance declarations for class aliases, 
there is a danger of overlapping instance definitions eg:

class Monad m where
    (>>=) :: ...

class alias AliasMonadFirst m (Monad m, First m)
class alias AliasMonadSecond m (Monad m, Second m)

instance AliasMonadFirst T where
    x >>= y = DEF1

instance AliasMonadSecond T where
     x >>= y = DEF2

foo :: AliasMonadFirst a, AliasMonadSecond a => -- problem: conflicting 
Monad dictionaries for a==T

The presence of such overlapping instances might be invisible to the 
end-user of the aliases (since it depends on how the aliases are bound which 
is presumably usually hidden to allow later refactoring)

This problem doesn't arise at the moment since the instance declaration only 
allows the non-inherited (ie non-shared) part to be specified (so that foo 
:: MonadIO a, MonadPlus a => ... always uses the same definitions for Monad 
even though the identical definitions for Monad are duplicated in the 2 
dictionaries)

>
> 2. it is more efficient on dictionary passing implementations of
> typeclasses. (does not apply to typecase based implementations like
> jhc)
>
> 3. it is simpler to declare instances for, the default methods of Ord
> can depend on Eq.

2) can be solved using aliases or whole program optimization
3) can be solved with aliases

> 1 is a very good reason.

Only if you are happy with < having to be a total order in every program 
that will ever be written :-)
(Though perhaps I am contradicted by the necessary relationship between 
TotalOrd and PartialOrd)

Regards, Brian. 



More information about the Haskell-Cafe mailing list