[GHC] #8129: Constraint solver panic when -ddump-tc-trace is used
GHC
ghc-devs at haskell.org
Tue Aug 13 14:27:47 CEST 2013
#8129: Constraint solver panic when -ddump-tc-trace is used
-------------------------------------+-------------------------------------
Reporter: adamgundry | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.7
checker) | Operating System: Unknown/Multiple
Keywords: | Type of failure: Compile-time
Architecture: Unknown/Multiple | crash
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: |
-------------------------------------+-------------------------------------
{{{
{-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-}
{-# OPTIONS_GHC -ddump-tc-trace #-}
type family F (x :: *) :: *
class (y ~ F x) => C x y
z = () :: C x y => ()
}}}
causes a panic while tracing the typechecker:
{{{
solveNestedImplications starting {
original inerts = Equalities:
Type-function equalities: [D] _ :: F x_aeH ~ y_aeI
(CFunEqCan)
Dictionaries: [W] $dC_aeK :: C x_aeH y_aeI (CDictCan)
Irreds:
Insolubles = {}
Solved dicts 0
Solved funeqs 0
thinner_inerts = Equalities:ghc-stage2: panic! (the 'impossible'
happened)
(GHC version 7.7.20130812 for i386-unknown-linux):
No match in record selector ctev_evar
}}}
If `-ddump-tc-trace` is not used, the correct constraint solving error is
generated:
{{{
Could not deduce (C x0 y0)
arising from the ambiguity check for an expression type signature
from the context (C x y)
bound by an expression type signature: C x y => ()
}}}
It seems that `prepareInertsForImplications` in `TcSMonad` assumes that
all the
`inert_funeqs` are givens or wanteds; if there are some deriveds, then the
above panic results.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8129>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list