GHC: FunctionalDependencies, UndecidableInstances, and the type-checker

Help me figure out why GHC loops in a functional dependencies + undecidable instances scenario.


I am learning functional dependencies. The GHC manual has a section on rules that instance declaration must follow. One in particular (“Coverage Condition”) applies to functional dependencies.

The manual states that you can lift these restrictions with UndecidableInstances, but stresses that it can cause havoc, including the type-checker going into a loop.
A specific example is provided at the end of the paragraph (here slightly abridged):

{-# Language FunctionalDependencies #-}
{-# Language UndecidableInstances #-}

module Prova where

class Mul a b c | a b -> c where
  (.*.) :: a -> b -> c

instance Mul Int Int Int where (.*.) = undefined
instance Mul Int Float Float where (.*.) = undefined
instance Mul a b c => Mul a [b] [c] where (.*.) = undefined

f b x y = if b then x .*. [y] else y

And indeed if you load it wit ghci, you get an error:

prova.hs:13:23-25: error:
    • Reduction stack overflow; size = 201
      When simplifying the following type: Mul a0 [[c]] [c]
      Use -freduction-depth=0 to disable this check
      (any upper bound you could choose might fail unpredictably with
       minor updates to GHC, so disabling the check is recommended if
       you're sure that type checking should terminate)
    • In the expression: x .*. [y]
      In the expression: if b then x .*. [y] else y
      In an equation for ‘f’: f b x y = if b then x .*. [y] else y
   |
13 | f b x y = if b then x .*. [y] else y
   |                       ^^^

To understand the example, I decided to work it step by step, to see exactly where the type-checker goes into a loop:

// Type-check this:
// f b x y = if b then x .*. [y] else y

b :: Bool
x :: a
y :: b

// Let's tackle `x .*. [y]`
// The only instance head that matches is `Mul a [b] [c]`.
x :: a
[y] :: [b]
    // Constraint: Mul a [b] [c] => …

// And from `else y` we get
y :: [c]

// Then we can say `b ~ [c]`, right? (unification?) So the signature becomes
f :: Mul a [[c]] [c] => Bool -> [c] -> [c]

And indeed if you add f :: Mul a [[c]] [c] => Bool -> a -> [c] -> [c], the code at the top does compile, albeit with this warning:

prova.hs:14:6-47: warning: [-Wsimplifiable-class-constraints]
    • The constraint ‘Mul a [[c]] [c]’ matches
        instance Mul a b c => Mul a [b] [c] -- Defined at prova.hs:11:10
      This makes type inference for inner bindings fragile;
        either use MonoLocalBinds, or simplify it using the instance
    • In the type signature:
        f :: Mul a [[c]] [c] => Bool -> a -> [c] -> [c]
   |
14 | f :: Mul a [[c]] [c] => Bool -> a -> [c] -> [c]
   |      ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

-Wsimplifiable-class-constraints warns you when you — e.g. — write Eq [a] => a -> a instead of Eq a => a -> a.

In this case simply removing a pair of extra brackets from the type parameters in Mul a [[c]] [c] should do. And indeed with:

f :: Mul a [c] c => Bool -> a -> [c] -> [c]

the example compiles.


If you have read until here, thanks! My question is: why was the type-checker not able to deduce this signature on its own?

1 Like

Use -freduction-depth=0 to disable this check

I’ve seen that “hint” before:

These could be relevant:

I think I have an idea why you run this this problem. Let’s revisit f b x y = if b then x .*. [y] else y.

x :: a
y :: b
x .*. [y] -- matches Mul a b c => Mul a [b] [c]
x .*. [y] :: [c]

Due to the else branch:

y :: [c]

You still need to resolve Mul a b c. Lets fill in [c] for b: Mul a b c ~ Mul a [c] c

This matches again with Mul a b c => Mul a [b] [c]. Therefore, from Mul a [c] c we can infer Mul a c d => Mul a [c] [d] where c ~ [d]. We know that c must be some kind of list due to the functional dependency. That’s why I have added c ~ [d].

Now, y already has the type that it is a list of lists:

y :: [[d]]

As you match Mul a b c => Mul a [b] [c] more and more, the type of y grows and grows as more nested list types are inferred. You essentially run into an infinite loop. GHC will cancel type checking after a certain depth.

Why does f :: Mul a [c] c => Bool -> a -> [c] -> [c] typecheck?
I have not tested this, but I think what is happening is that you delay the infinite expansion of the typeclass instances. You tell GHC in the signature that Mul a [c] c is in scope, therefore GHC will not try to resolve Mul a [c] c any further and f typechecks.

However, when you try to use f, GHC still needs to resolve Mul a [c] c. You will once again run into the problem that Mul a [c] c results in an infinite recursion of typeclass matchings.

2 Likes

A couple of tips to do with that Reduction stack overflow message

Yes. It hardly never helps to drop the check/if your instances genuinely are loopy, the compiler will just take longer to arrive at the same overflow.

GHC’s implementation of FunDeps – errm, leaves a lot to be desired [***]. I would write all instances in this form [**]:

instance c ~ Int => Mul Int Int c where (.*.) = undefined
instance c ~ Float => Mul Int Float c where (.*.) = undefined
instance (c' ~ [c], Mul a b c) => Mul a [b] c' where (.*.) = undefined

Why? Because then instance selection can’t fail due to GHC being unable to figure out whether the result type matches or is at least unifiable with the Wanted. The bare fresh tyvar in the instance head guarantees the right instance is selected; the type improvement (via ~) is then sure to apply.

I’m not saying this’ll help for your example (it didn’t – see Answer below). It’ll at least help split out the steps GHC is going through.

[**] This form is an improvement where you have exactly one FunDep, as in this case. It can make things worse if you have multiple/multi-directional FunDeps, because then it’s not as simple as a single position being the target.

Hmm merely compiling is not enough. Can you call f True (1 :: Int) [2, 3 :: Int] ?

Answer No, for example:

ff = f True (1::Int) [2, 3::Int]
-- (or merely at the GHC prompt, ask for the `:type` of that call to `f`)

    * Couldn't match type `Int' with `[Int]' arising from a use of `f'
    * In the expression: f True (1 :: Int) [2, 3 :: Int]

IOW given that third instance for Mul, f's attempt to unify both branches of the if is necessarily loopy. By putting that constraint on f you’ve merely deferred the check – as @simon says: GHC is being over-generous; perhaps you’re going to import this module into somewhere that has another instance for Mul that will break the loop.

a) Because there’s all sorts of constraints you might put on f that would get that code to compile (in particular the compiler isn’t going to guess at what other instances there might be in other modules); but
b) ‘get to compile’ is not the objective. We want ‘get to be runnable’, and the signature you put doesn’t achieve that.

[***] For example, in Hugs:

  • Your original code gets rejected with much the same message type checker has reached the cutoff limit ... may[be] undecidable.
  • Adding the signature you give for f doesn’t compile:
Inferred type is not general enough
*** Expected type : Mul a [b] b => Bool -> a -> [b] -> [b]   -- from the sig.
*** Inferred type : Mul a [[b]] [b] => Bool -> a -> [[b]] -> [[b]]

  • This sig (without any call to f) does compile – but note it seems to be more general than the Inferred type above …
f :: Mul a [[c]] [c] => Bool -> a -> [c] -> [c]
  • … except asking for :type f takes us back to the cutoff limit message.
  • And/or trying to define ff:
Constraints are not consistent with functional dependency
*** Constraint       : Mul Int [Int] Int      -- inferred from the else branch result y
*** And constraint   : Mul Int [Int] [a]      -- inferred from the then branch/use of (.*.)
1 Like

I guess the shortcut answer is: your Wanted type is infinite. Haskell doesn’t support infinite types, so that’s a contradiction. Ex nihilo quodlibet. It’s then down to compiler ergonomics as to what hints it can give/which particular line of code it should point at/whether it could or should suggest any improvement.

Thanks everyone for their answer.
I am still trying to understand this fully, it will take some more tries with manual type-checking.

I will ask for more if needed, for now I am grateful for the explanations!