[GHC] #12860: GeneralizedNewtypeDeriving + MultiParamTypeClasses sends typechecker into an infinite loop
GHC
ghc-devs at haskell.org
Sun Aug 6 15:17:28 UTC 2017
#12860: GeneralizedNewtypeDeriving + MultiParamTypeClasses sends typechecker into
an infinite loop
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.0.1
checker) | Keywords: FunDeps,
Resolution: | deriving
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
The problem isn't limited to just derived instances. If you try to write
out the code that would be derived by hand:
{{{#!hs
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
module Bug where
class C a b | a -> b where
c :: a -> Int
newtype Foo a = Foo a
instance C b a => C b (Foo a) where
c (Foo a) = c a
}}}
Then GHC will also "loop" (i.e., it will stack overflow on GHC 8.0.2 or
later, and properly loop on GHC 8.0.1):
{{{
• Reduction stack overflow; size = 201
When simplifying the following type: C a0 (Foo a)
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: c a
In an equation for ‘c’: c (Foo a) = c a
In the instance declaration for ‘C b (Foo a)’
|
14 | c (Foo a) = c a
| ^^^
}}}
So if anything, we should be placing an extra check in the constraint
solver, not just GND.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12860#comment:11>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list