"Occurs check" not considered when reducing closed type families
Hello,
consider the following example:
{-# LANGUAGE TypeFamilies #-}
type family Same a b where
Same a a = Int
Same a b = Char
example :: Same a [a] -> a
example = undefined
bad :: a
bad = example 'c'
This program should type check, using the following reasoning: a
and [a]
can never be equal, therefore the first equation for Same
does not apply, and so we can fall trough to the second one, thus reducing Same
to Char
. Therefore, bad
should be accept.
GHC rejects this program with the following error:
• Couldn't match expected type ‘Same a [a]’ with actual type ‘Char’
• In the first argument of ‘example’, namely ‘'c'’
In the expression: example 'c'
In an equation for ‘bad’: bad = example 'c'
• Relevant bindings include bad :: a (bound at tmp/test.hs:11:1)
Trac metadata
Trac field | Value |
---|---|
Version | 8.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler (Type checker) |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |