[GHC] #8129: Constraint solver panic when -ddump-tc-trace is used

#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

#8129: Constraint solver panic due to derived type function equality --------------------------------------------+------------------------------ Reporter: adamgundry | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler (Type checker) | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Changes (by adamgundry): * priority: normal => high Comment: The above example, without `-ddump-tc-trace`, now causes the latest HEAD to panic with: {{{ ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.7.20130915 for i386-unknown-linux): ASSERT failed! file compiler/typecheck/TcMType.lhs line 809 [D] _ :: main:Main.F{tc rpc} x_aAu{tv} [tau[0]] ghc-prim:GHC.Types.~{(w) tc 31Q} y_aAv{tv} [tau[0]] (CFunEqCan) }}} It looks like the problem was introduced in e365d4963f1061878269502f256b4a56ca273a78 (the fix to #8262). The new code calls `solveWantedsTcMWithEvBinds` with `solve_wanteds`, rather than `solve_wanteds_and_drop`. But `solveWantedsTcMWithEvBinds` calls `zonkWC`, which works only with wanted (not derived) constraints. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8129#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8129: Constraint solver panic due to derived type function equality
--------------------------------------------+------------------------------
Reporter: adamgundry | Owner:
Type: bug | Status: new
Priority: high | Milestone:
Component: Compiler (Type checker) | Version: 7.7
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time crash | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
--------------------------------------------+------------------------------
Comment (by Simon Peyton Jones

#8129: Constraint solver panic due to derived type function equality --------------------------------------------+------------------------------ Reporter: adamgundry | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler (Type checker) | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by simonpj): Darn; I meant #8314, not #8134. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8129#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8129: Constraint solver panic due to derived type function equality -------------------------------------------------+------------------------- Reporter: adamgundry | Owner: Type: bug | Status: Priority: high | closed Component: Compiler (Type checker) | Milestone: Resolution: fixed | Version: 7.7 Operating System: Unknown/Multiple | Keywords: Type of failure: Compile-time crash | Architecture: Test Case: | Unknown/Multiple indexed_types/should_fail/T8129 | Difficulty: Blocking: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Changes (by simonpj): * status: new => closed * testcase: => indexed_types/should_fail/T8129 * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8129#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8129: Constraint solver panic due to derived type function equality
-------------------------------------------------+-------------------------
Reporter: adamgundry | Owner:
Type: bug | Status:
Priority: high | closed
Component: Compiler (Type checker) | Milestone:
Resolution: fixed | Version: 7.7
Operating System: Unknown/Multiple | Keywords:
Type of failure: Compile-time crash | Architecture:
Test Case: | Unknown/Multiple
indexed_types/should_fail/T8129 | Difficulty:
Blocking: | Unknown
| Blocked By:
| Related Tickets:
-------------------------------------------------+-------------------------
Comment (by Simon Peyton Jones

#8129: Constraint solver panic due to derived type function equality -------------------------------------------------+------------------------- Reporter: adamgundry | Owner: Type: bug | Status: Priority: high | closed Component: Compiler (Type checker) | Milestone: Resolution: fixed | Version: 7.7 Operating System: Unknown/Multiple | Keywords: Type of failure: Compile-time crash | Architecture: Test Case: | Unknown/Multiple indexed_types/should_fail/T8129 | Difficulty: Blocking: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Comment (by nfrisby): It seems that tests/indexed-types/should_fail/T8129.stderr is missing from the repo. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8129#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8129: Constraint solver panic due to derived type function equality -------------------------------------------------+------------------------- Reporter: adamgundry | Owner: Type: bug | Status: Priority: high | closed Component: Compiler (Type checker) | Milestone: Resolution: fixed | Version: 7.7 Operating System: Unknown/Multiple | Keywords: Type of failure: Compile-time crash | Architecture: Test Case: | Unknown/Multiple indexed_types/should_fail/T8129 | Difficulty: Blocking: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Comment (by rwbarton): Or `tests/indexed-types/should_fail/T8129.stdout`, rather. I see {{{ Could not deduce (C x0 y0) Could not deduce (C x0 y0) }}} but I have no idea whether it's correct. (Simon?) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8129#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8129: Constraint solver panic due to derived type function equality
-------------------------------------------------+-------------------------
Reporter: adamgundry | Owner:
Type: bug | Status:
Priority: high | closed
Component: Compiler (Type checker) | Milestone:
Resolution: fixed | Version: 7.7
Operating System: Unknown/Multiple | Keywords:
Type of failure: Compile-time crash | Architecture:
Test Case: | Unknown/Multiple
indexed_types/should_fail/T8129 | Difficulty:
Blocking: | Unknown
| Blocked By:
| Related Tickets:
-------------------------------------------------+-------------------------
Comment (by Krzysztof Gogolewski

#8129: Constraint solver panic due to derived type function equality -------------------------------------------------+------------------------- Reporter: adamgundry | Owner: Type: bug | Status: Priority: high | closed Component: Compiler (Type checker) | Milestone: Resolution: fixed | Version: 7.7 Operating System: Unknown/Multiple | Keywords: Type of failure: Compile-time crash | Architecture: Test Case: | Unknown/Multiple indexed_types/should_fail/T8129 | Difficulty: Blocking: | Unknown | Blocked By: | Related Tickets: -------------------------------------------------+------------------------- Comment (by monoidal): This is due to "grep deduce T8129.trace" in Makefile. I fixed it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8129#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC