[GHC] #8044: "Inaccessible code" error reported in wrong place

#8044: "Inaccessible code" error reported in wrong place -------------------------------------------+------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.7 Keywords: GADTs | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: | Test Case: | Blocking: -------------------------------------------+------------------------------- Here is my file `Bug.hs`: {{{ {-# LANGUAGE GADTs, TypeFamilies #-} module Bug where data X a where XInt :: X Int XBool :: X Bool XChar :: X Char type family Frob a where Frob Int = Int Frob x = Char frob :: X a -> X (Frob a) frob XInt = XInt frob _ = XChar }}} Compiling this file produces the error {{{ Bug.hs:15:6: Couldn't match type ‛Int’ with ‛Char’ Inaccessible code in a pattern with constructor XInt :: X Int, in an equation for ‛frob’ In the pattern: XInt In an equation for ‛frob’: frob XInt = XInt }}} The line/column number single out the pattern `XInt` in the first clause of the function `frob`. But, the real problem (as I see it), is the right- hand side of the ''second'' clause of `frob`. Indeed, when I comment out the second line of the function, the error goes away, even though it was reported on the first line. I do not believe that this error is caused by closed type families, per se, because I have run across it without them, just in code that was too hard to pare down enough to make a bug report out of. This was tested on 7.7.20130702. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8044 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8044: "Inaccessible code" error reported in wrong place --------------------------------------------+------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.7 Resolution: | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Changes (by simonpj): * cc: dimitris@… (added) Comment: Interesting. From the constraints we get: {{{ ((a ~ Int) => X (Frob a) ~ X Int) -- (A) From first eqn for Frob & X (Frob a) ~ X Char -- (B) From second eqn }}} Now the first constraint (A) all by itself is soluble: substitute `Int` for `a`, simplify `(Frob Int)` and you are done. But in general we use type-function equality constraints (including as- yet-unsolved constraints) from outside an implication and push them inwards as "givens" (see `Note [Preparing inert set for implications]` in `TcSMonad`). So we push in a given {{{ Frob a ~ Char }}} into (A) and that leads to `Int~Char` and the error. I think we should narrow the "push in wanteds" stuff. I'll have a go at that. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8044#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8044: "Inaccessible code" error reported in wrong place --------------------------------------------+------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.7 Resolution: | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by heisenbug): I doubt the type family is valid {{{ type family Frob a where Frob Int = Int Frob x = Char }}} The second clause should give the same result for `x = Int` than the first (namely `Int`), but it results in `Char`. Richard can surely express it better than me, though I wonder why it is not rejected at all? ''(I sincerely hope I did not mess this up!)'' -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8044#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8044: "Inaccessible code" error reported in wrong place --------------------------------------------+------------------------------ Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.7 Resolution: | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: --------------------------------------------+------------------------------ Comment (by goldfire): Ah, but {{{Frob}}} is a hot-off-the-presses ''closed type family'', which allows such things. The idea is that the equations match top-to-bottom, much like term-level functions. Because the reasoning is static (at compile-time), we have to be more careful about this top-to-bottom matching, refusing to let `Frob q` reduce to `Char` before we know that `q` cannot possibly become `Int`. This is why the code in the example above is erroneous. Despite the previous case checking for `XInt`, GHC does not know when type-checking the second equation for `frob` that the type variable `a` cannot be `Int`. Thus, it cannot simplify `Frob a` and it cannot accept `XChar` as well-typed. So, the bug I'm reporting is not that GHC rejects my program. It should indeed reject that program. The problem is that the error message points out the wrong (as in, non-existent) error. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8044#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8044: "Inaccessible code" error reported in wrong place -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.1 Component: Compiler | Version: 7.7 (Type checker) | Keywords: GADTs Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by thomie): * milestone: => 7.10.1 Comment: This seems to be fixed. A regression test should probably be added. HEAD now shows an error message about the second clause of `frob`, no longer about the first clause. {{{ $ ghc-7.9.20141121 Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:16:13: Couldn't match type ‘Frob a’ with ‘Char’ Expected type: X (Frob a) Actual type: X Char Relevant bindings include frob :: X a -> X (Frob a) (bound at Bug.hs:15:1) In the expression: XChar In an equation for ‘frob’: frob _ = XChar }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8044#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8044: "Inaccessible code" error reported in wrong place
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 7.10.1
Component: Compiler | Version: 7.7
(Type checker) | Keywords: GADTs
Resolution: | Architecture: Unknown/Multiple
Operating System: | Difficulty: Unknown
Unknown/Multiple | Blocked By:
Type of failure: | Related Tickets:
None/Unknown |
Test Case: |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#8044: "Inaccessible code" error reported in wrong place -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.1 Component: Compiler | Version: 7.7 (Type checker) | Keywords: GADTs Resolution: fixed | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | typecheck/should_fail/T8044 | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * testcase: => typecheck/should_fail/T8044 * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8044#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC