Reduction stack overflow

Consider this snippet of code

{-# LANGUAGE QuantifiedConstraints #-}

module Foo where

import Control.Monad.Writer

data Foo = Foo

foo :: (forall e. Monoid e => MonadWriter e (m e)) => m [Foo] Int
foo = pure 1

It produces an error

Reduction stack overflow; size = 201
When simplifying the following type: Monoid [Foo]

See here if you want to play with it.

Am I wrong or the compiler is telling me that it is not able to find an instance Monoid [Foo]?

Some of the articles found during a brief websearch using ghc haskell "reduction stack" increase mention this option:

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)

On my system:

# ghci -freduction-depth=0 Foo.hs
GHCi, version 9.8.2: https://www.haskell.org/ghc/  :? for help
[1 of 1] Compiling Foo              ( Foo.hs, interpreted )

…and still going. So what happens when you use -freduction-depth=0 ?

It would seem strange to me that this is a case of not enough room for recursion, since there is no recursive type involved.

It just looks like ghc is not able to find the Monoid [a] instance.

Btw, just running ghci -freduction-depth=0 Foo.hs just keeps going…

I think this program indeed yields an infinite loop in the constraint solver. The issue is that MonadWriter e (m e) has Monoid e as a superclass, so when GHC tries to solve the Applicative (m [Foo]) constraint arising from pure:

  • It can use the quantified constraint to get MonadWriter [Foo] (m [Foo]) (and hence Monad (m [Foo]) and hence Applicative (m [Foo])), if only it can solve Monoid [Foo].
  • Now in order to produce Monoid [Foo], rather than using the global instance, it foolishly decides to use the quantified constraint and take the superclass. But then it needs to solve Monoid [Foo] again, and the loop begins.

GHC really ought to at least require UndecidableInstances for this, but currently it fails to do so:

6 Likes

ah, that makes some sense, thanks for the explanation!

1 Like

UndecidableInstances makes no difference here:

# ghci -XUndecidableInstances -freduction-depth=0 Foo.hs
GHCi, version 9.8.2: https://www.haskell.org/ghc/  :? for help
[1 of 1] Compiling Foo              ( Foo.hs, interpreted )

I noticed that switching the compiler version to 8.6.5 or 8.8.4 works.
A regression then?

foo :: (forall a. a, forall e. Monoid e => MonadWriter e (m e)) => m [Foo] Int
foo = pure 1

Compiles but I don’t know what it means.
Also this compiles on 9.10.1 and 9.8.2 and 9.6.6 but not below.

It compiles with GHC 9.8.2? Hmm:

  • # ghc -V
    The Glorious Glasgow Haskell Compilation System, version 9.8.2
    
  • # ghc -c Foo.hs
    
    Foo.hs:10:7: error: [GHC-40404]
        • Reduction stack overflow; size = 201
          When simplifying the following type: Monoid [Foo]
        • In the expression: pure 1
          In an equation for ‘foo’: foo = pure 1
        Suggested fix:
          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)
       |
    10 | foo = pure 1
       |       ^^^^
    
  • # ghc -c -XUndecidableInstances Foo.hs
    
    Foo.hs:10:7: error: [GHC-40404]
        • Reduction stack overflow; size = 201
          When simplifying the following type: Monoid [Foo]
        • In the expression: pure 1
          In an equation for ‘foo’: foo = pure 1
        Suggested fix:
          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)
       |
    10 | foo = pure 1
       |       ^^^^
    
  • # ghc -c -freduction-depth=0 Foo.hs
    
    ^C
    #
    
  • # ghc -c -XUndecidableInstances -freduction-depth=0 Foo.hs
    
    ^C
    #
    

Regression or not, it’s certainly something that needs careful monitoring; principle of least surprise and all…

1 Like

It means you would never be able to use foo, as instantiating it would require a solution to every constraint ever dreamed up by machine or man.

A more effective workaround for this specific case would be

foo :: (Monoid [Foo], forall e. Monoid e => MonadWriter e (m e)) => m [Foo] Int
foo = pure 1

(You’ll get a compiler warning about a simplifiable class constraint—accurate, but you made me do this, GHC!)

2 Likes

Interesting thread. I have opened a ticket #25412: Superclasses of quantified constraints leads to solver loop · Issues · Glasgow Haskell Compiler / GHC · GitLab, and added some diagnosis, for those who are interested.

6 Likes