[Haskell-cafe] implementing a class using superclasses?
Henning Thielemann
lemming at henning-thielemann.de
Wed Mar 26 21:49:08 UTC 2025
On Wed, 26 Mar 2025, Mark McConnell via Haskell-Cafe wrote:
> Here is a simplified, self-contained version of some code I'm working
> on. I have a Ord type Foo that I want to be ordered primarily by comp1,
> and, in case of ties, secondarily by comp2. It is important to my users
> to know that the primary sorting will always be by comp1. Therefore, I
> am trying to use to the type system to articulate that Foo must be
> ordered in a two-fold lexicographic way. My code is
>
> module Lex2Test where
>
> class Ord a => Primary a where
> comp1 :: a -> a -> Ordering
> comp1 = compare
>
> class Ord a => Secondary a where
> comp2 :: a -> a -> Ordering
> comp2 = compare
>
> class (Primary a, Secondary a) => Lex2 a
>
> instance Lex2 a => Ord a where
> compare x y = comp1 x y <> comp2 x y
This instance declaration means, that you want to define an Ord instance
universally for all types 'a'. This includes all the types that already
have Ord instances, like Int, Char, Bool etc.
Did you want to define an instance on Foo instead?
More information about the Haskell-Cafe
mailing list