{-# 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]
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 ?
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:
# 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
| ^^^^