[Haskell-cafe] implementing a class using superclasses?

MigMit migmit at gmail.com
Wed Mar 26 21:48:13 UTC 2025


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 <haskell-cafe at haskell.org> 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.




More information about the Haskell-Cafe mailing list