implementing a class using superclasses?

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 However, when I load the code into ghci, I get Lex2Test.hs:13:10: error: • The constraint ‘Lex2 a’ is no smaller than the instance head ‘Ord a’ (Use UndecidableInstances to permit this) • In the instance declaration for ‘Ord a’ |13 | instance Lex2 a => Ord a where | ^^^^^^^^^^^^^^^ I feel I must be missing something. UndecidableInstances seems too extreme for what I am trying to do. (I have never said that I want to go backwards in class inference from Ord to Lex2.) If this were C++, I would be just trying to implement some virtual functions in terms of other virtual functions. Any comments would be appreciated.

In standard Haskell, instances don't work like that. You simply can't make `instance Ord a`, you need some type constructor. Perhaps this would help: newtype Proxy a = Proxy a instance Lex2 a => Ord (Proxy a) where compare (Proxy x) (Proxy y) = comp1 x y <> comp2 x y ~~~ You can make this compile with UndecidableInstances, but that opens another can of worms. Suppose you have data X = ...blablabla instance Ord X instance Primary X instance Secondary X instance Lex2 X That would compile, despite comparisons not being defined. That's because you have defaults for comp1 and comp2, so you'd have compare x y = comp1 x y <> comp2 x y = compare x y <> compare x y which would at best crash with an error, and at worst loop forever.
On 26 Mar 2025, at 22:37, 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
However, when I load the code into ghci, I get
Lex2Test.hs:13:10: error: • The constraint ‘Lex2 a’ is no smaller than the instance head ‘Ord a’ (Use UndecidableInstances to permit this) • In the instance declaration for ‘Ord a’ | 13 | instance Lex2 a => Ord a where | ^^^^^^^^^^^^^^^
I feel I must be missing something. UndecidableInstances seems too extreme for what I am trying to do. (I have never said that I want to go backwards in class inference from Ord to Lex2.)
If this were C++, I would be just trying to implement some virtual functions in terms of other virtual functions.
Any comments would be appreciated.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

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?

Hi Mark, On Wed, 2025-03-26 at 21:37 +0000, Mark McConnell via Haskell-Cafe wrote:
instance Lex2 a => Ord a where compare x y = comp1 x y <> comp2 x y
This attempts to define `Ord a` in general, for *every* type `a` at once. The `Lex2 a` constraint is only checked *after* the compiler has decided this is the instance to use. Besides decidability concerns, this is probably not what you want, since it overlaps with every other type's Ord instance. If you want to express a strategy for implementing one typeclass in terms of others, I would suggest using a newtype together with DerivingVia: newtype UsePrimaryAndSecondary a = MkUsePrimaryAndSecondary a instance (Primary a, Secondary a) => Ord (Lex2 a) where compare (MkLex2 x) (MkLex2 y) = comp1 x y <> comp2 x y data Foo = -- ... deriving Ord via (UsePrimaryAndSecondary Foo) instance Primary Foo where -- ... instance Secondary Foo where -- ... If, on the other hand, you want to express a constraint, as opposed to an implementation strategy, I think the conventional thing to do would be to define Lex2 as a subclass of Ord, Primary, and Secondary, and no additional members. Then put the (informal) requirements in a comment, similar to e.g. the monad laws. You can of course combine the two approaches.
I feel I must be missing something. UndecidableInstances seems too extreme for what I am trying to do. (I have never said that I want to go backwards in class inference from Ord to Lex2.)
This is, in general, how type class resolution works. The compiler matches on the *head* (the thing to the right of =>), and then recurses on the constraints (to the left of the =>). -- Jade

On Wed, 2025-03-26 at 18:08 -0400, Jade Hagborg via Haskell-Cafe wrote:
instance (Primary a, Secondary a) => Ord (Lex2 a) where compare (MkLex2 x) (MkLex2 y) = comp1 x y <> comp2 x y
My bad (copy-paste error), should be instance (Primary a, Secondary a) => Ord (UsePrimaryAndSecondary a) where compare (MkUsePrimaryAndSecondary x) (MkUsePrimaryAndSecondary y) = comp1 x y <> comp2 x y Sorry if that caused confusion.

Thank you to everyone who replied. The thing I was misunderstanding was, to quote Jade, "This attempts to define `Ord a` in general, for *every* type `a` at once. The `Lex2 a` constraint is only checked *after* the compiler has decided this is the instance to use."
I appreciate seeing how a Proxy constructor, or DerivingVia, would solve the problem. However, I decided just to document carefully what I was doing.
On Wednesday, March 26, 2025 at 06:14:00 PM EDT, Jade Hagborg
instance (Primary a, Secondary a) => Ord (Lex2 a) where compare (MkLex2 x) (MkLex2 y) = comp1 x y <> comp2 x y
My bad (copy-paste error), should be instance (Primary a, Secondary a) => Ord (UsePrimaryAndSecondary a) where compare (MkUsePrimaryAndSecondary x) (MkUsePrimaryAndSecondary y) = comp1 x y <> comp2 x y Sorry if that caused confusion.
participants (4)
-
Henning Thielemann
-
Jade Hagborg
-
Mark McConnell
-
MigMit