[GHC] #9318: Type error reported in wrong place with repeated type family expressions
GHC
ghc-devs at haskell.org
Tue Jul 15 12:24:34 UTC 2014
#9318: Type error reported in wrong place with repeated type family expressions
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.8.3
checker) | Differential Revisions:
Keywords: | Architecture:
Operating System: Unknown/Multiple | Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+-------------------------------------
When I say
{{{
{-# LANGUAGE TypeFamilies #-}
type family F x
type instance F Int = Bool
foo :: F Int -> ()
foo True = ()
bar :: F Int -> ()
bar 'x' = ()
}}}
I get
{{{
/Users/rae/temp/Bug.hs:7:5:
Couldn't match type ‘Char’ with ‘Bool’
Expected type: F Int
Actual type: Bool
In the pattern: True
In an equation for ‘foo’: foo True = ()
/Users/rae/temp/Bug.hs:10:5:
Couldn't match type ‘Bool’ with ‘Char’
Expected type: F Int
Actual type: Char
In the pattern: 'x'
In an equation for ‘bar’: bar 'x' = ()
}}}
The second error is most certainly correct, but the first one is most
certainly not. Note that the first error is reported on the definition of
`foo`, which should type-check. Also, the "Couldn't match ..." bit doesn't
correspond at all with the expected/actual bit. And, the expected/actual
bit shows two types that are in fact equal.
This behavior can be seen in HEAD (as of Jul. 2), 7.8.3, and 7.8.2. This
is a regression from 7.6.3, where this behavior does not appear.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9318>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list