[GHC] #10910: Data families seem not to be "surely apart" from anything
GHC
ghc-devs at haskell.org
Wed Sep 23 08:40:13 UTC 2015
#10910: Data families seem not to be "surely apart" from anything
-------------------------------------+-------------------------------------
Reporter: oerjan | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.2
Keywords: data | Operating System: Unknown/Multiple
families, closed type families |
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Revisions: |
-------------------------------------+-------------------------------------
The following code is not compiling (GHC 7.10.2), it looks as if data
families are not considered "surely apart" from any type, despite being
injective.
{{{#!hs
{-# LANGUAGE TypeFamilies, DataKinds, GADTs #-}
type family Equals x y where
Equals x x = True
Equals x y = False
data Booly b where
Truey :: Booly True
Falsey :: Booly False
data family ID a
data instance ID Bool = IB
test :: Booly (Equals (ID Bool) Int)
test = Falsey
}}}
(Inspired and simplified from http://stackoverflow.com/questions/32733368
/type-inequalities-in-the-presence-of-data-families#32733368.)
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10910>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list