[GHC] #8978: Type synonyms are not *exactly* synonyms
GHC
ghc-devs at haskell.org
Wed Apr 9 16:17:50 UTC 2014
#8978: Type synonyms are not *exactly* synonyms
----------------------------+----------------------------------------------
Reporter: joelteon | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: GHC rejects valid program
Unknown/Multiple | Test Case:
Difficulty: Unknown | Blocking:
Blocked By: |
Related Tickets: |
----------------------------+----------------------------------------------
{{{
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
type Syn a = Associated a
class Eq (Associated a) => Foo a where
type Associated a :: *
foo :: a -> Syn a -> Bool
instance Foo () where
type Associated () = Int
foo _ x = x == x
}}}
In 7.6.3 and 7.8.1-rc2, this file compiles. In 7.8.1 release, GHC produces
this error:
{{{
No instance for (Eq (Syn ())) arising from a use of ‘==’
In the expression: x == x
In an equation for ‘foo’: foo _ x = x == x
In the instance declaration for ‘Foo ()’
}}}
even though there is an Eq instance for Associated (), and Syn is just a
type synonym.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8978>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list