Avoid tedious implementation of Ord

I have a datatype with quite a few constructors, all of them simple enough that Haskell can derive the Ord instance automatically. As in:

data Foo a
  = A a
  | B Int
  deriving (Eq, Ord)

Now I want to add a third constructor like so:

data Foo a
  = A a
  | B Int
  | C a (a -> Bool)

But now Haskell can't manually derive Eq and Ord on Foo for me. Now, it happens that I have some domain-specific knowledge about how two values constructed with C should be ordered:

instance Eq a => Eq (Foo a) where
  -- Boilerplate I don't want to write
  A x == A y = x == y
  B x == B y = x == y
  -- This is the case I really care about
  C x f == C y g = x == y && f x == g y
  _ == _ = False

instance Ord a => Ord (Foo a) where
  -- Boilerplate I don't want to write
  A x `compare` A y = x `compare` y
  A x `compare` _ = LT

  B x `compare` B y = x `compare` y
  B x `compare` A _ = GT
  B _ `compare` _ = LT

  -- This is the case I really care about
  C x f `compare` C y g
    | x == y = f x `compare` g y
    | otherwise = x `compare` y
  C{} `compare` _ = GT

But in order to do this, I also have to manually implement the ordering on A and B values, which is really tedious (especially for the Ord instance).

Is there any trick that would allow me to implement (==) and compare only on the C case, but somehow get the "default" behaviour on the other constructors?

Upvotes: 5

Views: 199

Answers (3)

Daniel Wagner
Daniel Wagner

Reputation: 152837

Since you know something special about these functions, consider storing information about that something special and re-interpreting to function-land only as necessary. For example, perhaps what you know is that they are partially-applied (<); then something like this:

{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}

data Foo a
    = A a
    | B Int
    | C_ a a
    deriving (Eq, Ord, Read, Show)

pattern C a f <- C_ a ((<) -> f)

Of course if you have a more complicated expression language than just addition you may want to define a separate type for your AST and a separate function for evaluating the AST; but the AST itself should in most simple cases where your proposed comparison rule is right be derivably-equal/orderable.

Upvotes: 2

Iceland_jack
Iceland_jack

Reputation: 7014

This "package" of a function an its argument (known as the Store comonad (.. which has no Eq instance)) can be the instances of Eq and Ord that you seek

data Store s a = Store (s -> a) s

instance (Eq s, Eq a) => Eq (Store s a) where
  (==) :: Store s a -> Store s a -> Bool
  Store f s == Store f' s' =
    (s == s')
    &&
    (f s == f' s')

instance (Ord s, Ord a) => Ord (Store s a) where
  compare :: Store s a -> Store s a -> Ordering
  Store f s `compare` Store f' s' = 
    (compare s s')
    <>
    (f s `compare` f' s')

Now you can derive both Eq and Ord

data Foo a
  = A a
  | B Int
  | C (Store a Bool)
  deriving (Eq, Ord)

Upvotes: 3

Andr&#225;s Kov&#225;cs
Andr&#225;s Kov&#225;cs

Reputation: 30103

You could parameterize Foo with the types of special cases, then implement special instances separately for newtypes:

data Foo' c a
  = A a
  | B Int
  | C (c a)
  deriving (Eq, Ord)

data C a = MkC a (a -> Bool)

instance Eq a => Eq (C a) where
  MkC x f == MkC y g = x == y && f x == g y

instance Ord a => Ord (C a) where
  MkC x f `compare` MkC y g
    | x == y = f x `compare` g y
    | otherwise = x `compare` y

type Foo = Foo' C

Upvotes: 5

Related Questions