[GHC] #8044: "Inaccessible code" error reported in wrong place
GHC
ghc-devs at haskell.org
Mon Jul 8 10:57:26 CEST 2013
#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
More information about the ghc-tickets
mailing list