[GHC] #12860: GeneralizedNewtypeDeriving + MultiParamTypeClasses sends typechecker into an infinite loop
GHC
ghc-devs at haskell.org
Mon Apr 9 16:01:34 UTC 2018
#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):
Well, maybe. The original program and the program in comment:11 have
another key difference. The latter uses `UndecidableInstances`, so I
suppose it's entirely reasonable that we get a stack overflow error on
that one. The former program, on the other hand, does not use
`UndecidableInstances`.
Really, we ought to reject the former program outright with an error
message similar to the one that we get if we leave off
`UndecidableInstances` from the latter program:
{{{#!hs
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
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
}}}
{{{
Bug.hs:12:10: error:
• Illegal instance declaration for ‘C b (Foo a)’
The coverage condition fails in class ‘C’
for functional dependency: ‘a -> b’
Reason: lhs type ‘b’ does not determine rhs type ‘Foo a’
Un-determined variable: a
Using UndecidableInstances might help
• In the instance declaration for ‘C b (Foo a)’
|
12 | instance C b a => C b (Foo a) where
| ^^^^^^^^^^^^^^^^^^^^
}}}
If we did this, then I would consider this issue resolved.
This coverage condition check is performed in `checkValidInstance`.
Curiously, we don't call `checkValidInstance` on derived instances at the
comment. There are relevant comments
[http://git.haskell.org/ghc.git/blob/b14c03737574895718eed786a60dfdfd42ab49ce:/compiler/typecheck/TcDerivInfer.hs#l594
here]:
{{{#!hs
-- checkValidInstance tyvars theta clas inst_tys
-- Not necessary; see Note [Exotic derived instance
contexts]
; traceTc "TcDeriv" (ppr deriv_rhs $$ ppr theta)
-- Claim: the result instance declaration is guaranteed
valid
-- Hence no need to call:
-- checkValidInstance tyvars theta clas inst_tys
}}}
As this ticket shows, this isn't quite right. So perhaps we need to carve
out the bit that checks the coverage condition and just check that.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12860#comment:12>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list