Issue creating Eq Instance

Hello all,

I’m currently working through the “Haskell from first principles” book and have a got a little stuck on one of the exercises concerning type classes.

The exercise is to create an Eq instance for

data EitherOr a b = Hello a | Goodbye b

which I have as

instance (Eq a, Eq b) => Eq (EitherOr a b) where
  (==) (Hello a) (Hello a') = a == a'
  (==) (Goodbye b) (Goodbye b') = b == b'
  (==) _ _ = False

However, upon using this like

Goodbye "bye == Goodbye "bie"

I get a compilation error

Ambiguous type variable ‘a0’ arising from a use of ‘==’
prevents the constraint ‘(Eq a0)’ from being solved.
Probable fix: use a type annotation to specify what ‘a0’ should be.

It seems that, despite technically not needing to know a type for a (as it isn’t used in Goodbye) it still wants one.

I’m assuming I’m missing something but also a little unsure as to how I would remedy it.

Any help appreciated, thank you.

1 Like

I had no idea how to solve it, and it’s taught me something new.

I went fishing around in the docs for the implementation of how Either does Eq and found this:

instance (Eq a) => Eq1 (Either a) where
    liftEq = liftEq2 (==)

This hopefully should maybe give a clue as to what more you will need to implement. If you get really stuck, click on liftEq2 and liftEq for their implementations. It’s kinda gnarly but it makes sense in the end.

Either Eq instance is stock deriving: https://hackage.haskell.org/package/ghc-internal-9.1001.0/docs/src/GHC.Internal.Data.Either.html#line-128

And actually this is the same thing that happens with Either. The a variable „seems” to be irrelevant, but it is needed for the instance to be resolved - indeed, those two a’s could be set to totally different types, and GHC here does not even know if this program should typecheck. There are very few cases when GHC implicitly assumes the type (in example Integer for untyped numeric literals).

The solution is to explicitly add a type annotation to one of the compared terms: (Goodbye ”Bye” :: EitherOr Int String)

1 Like

When you compile a program, type inference must finish with every expression being fed to typeclass functions having a concrete type, even if that is not strictly needed at runtime. So

main = print ['c']

works, but

main = print []

does not, as the a in [a] (the type of []) is ambiguous.

You need to add a type annotation to [] (e.g. ([] :: [Integer])) to make it work.

That’s not 100% true, print Proxy. But here the phantom type a of proxy is not needed since the instance exists for all a. When printing a list, there is a Show constraint on its elements that makes this parameter needed at compile time. So it’s not about every expression needs to have concrete type, but rather every type needed to resolve typeclass constraints has to be known.

1 Like

It needs to know it because in principle you could have different Eq instances for different type parameters. For example

{-# LANGUAGE GHC2021 #-}

data EitherOr a b = Hello a | Goodbye b

instance Eq (EitherOr () String) where
  _ == _ = False

instance Eq (EitherOr Bool String) where
  _ == _ = True

example = do
  print $ (Goodbye "bye" :: EitherOr () String) == Goodbye "bie"
  print $ (Goodbye "bye" :: EitherOr Bool String) == Goodbye "bie"
ghci> example 
False
True

(Perhaps it would be technically possible for the compiler to notice when there’s only one, universally quantified, instance and be more clever, I don’t know. But it seems to be simpler to just force you to annotate with a type in these rare cases.)

1 Like

the ambiguity GHC is telling you about is due to the fact that when you say Goodbye "bye" , you are specifying only one of the two type parameters of your type EitherOr. In other words, all GHC knows once you say x = Goodbye "bye" is x :: EitherOr a String, and it doesn’t know anything about a (GHC picks a random type parameter name a0 to show you the error)

1 Like

Thanks all,

certainly makes sense to me now, given the above, that the type for both a and b would be needed. I’ll also take a look at the Either implementation although, having a quick snoop, fully understanding it may be slightly out of my league currently.

1 Like

And actually this is the same thing that happens with Either.

Note that this actually works in GHCi:

$ ghci
GHCi, version 9.6.6: https://www.haskell.org/ghc/  :? for help
ghci> Right "five"
Right "five"
ghci> :t Right "five"
Right "five" :: Either a String
ghci> Right "fyve" == Right "five"
False
1 Like

Due to ExtendedDefaultRules

2 Likes

ah, that’s how it’s called! I suspect I was looking for this when I inquired about GHCi’s defaulting behavior a few days ago. TIL thanks!

1 Like