Instance resolution during default method definition in class?

See my example (gist).

I am perplexed by the error message. I assumed when compiling line 12, GHC would simply refer to the definition of turn in line 9. This seems straightforward and the types are compatible, but GHC seems to insist to check for concrete instances instead of the type in the class definition when type checking and deferring resolution until later.

How can I satisfy the compiler achieve what I want?

(Also, is this indeed suboptimal semantics in GHC or am I missing something?)

2 Likes

The issue is a bit subtle but the compiler is right in this case: parts of the code are ambiguous. If we look at the default definition for norm:

norm x = wrap $
  (un x) -  (un turn) * (fromIntegral . floor ) ( (un x) / (un turn))

There are two places where the expression un turn appears. What is the type of this expression? It is:

un turn :: (Angle b, Floating x) => b x

I’m using b instead of a intentionally: it can be any Angle! There is nothing here telling the compiler that the types of x and turn are equal. There are several ways to fix this, the most explicit one being just adding type signatures.

This requires us to turn on ScopedTypeVariables at the top of the file, so that we can refer to the type variable x inside an expression:

{-# LANGUAGE ScopedTypeVariables #-}

And then we can fix this issue by telling the compiler which Angle to use (a x):

class  Angle a where
  -- normalizes the angle
  norm    ::  forall x. (RealFrac x, Floating x) => a x -> a x
  norm x = wrap $ (un x) -  (un (turn :: a x)) * (fromIntegral . floor ) ( (un x) / (un (turn :: a x)))

I had to add this signature to a few other places in the file as well, but that made it compile.

2 Likes

Thanks! That’s great and you explained it very clearly!

1 Like

Another question, if you don’t mind:

Does the wrap / unwrap optimize away at runtime, because we have a newtype or does the fact that the constructors/deconstructors are assigned to an instance function cause some issues so that they cannot be eliminated by the compiler?

It depends!

The compiler knows that Rad and unRad are the same as id. It also knows this about Deg and unDeg. However, it’s not clear when you just write un or wrap – a typeclass may use complex implementations for these.

In the worst case, the instance is not known at compile time and a dictionary will be passed in at runtime, so there’s some overhead there. However, if everything gets properly inlined and optimized, in a lot of cases GHC will know that e.g. un = unRad; and then it will be optimized away.

Hope this helps!