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.