[GHC] #9063: Default associated type instances are too general
GHC
ghc-devs at haskell.org
Mon May 5 23:50:23 UTC 2014
#9063: Default associated type instances are too general
-------------------------------------+------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by goldfire):
Here is an example where this problem bites in instances:
{{{
{-# LANGUAGE DataKinds, PolyKinds, TypeFamilies, TypeOperators #-}
module Bug where
import Data.Proxy
class kproxy ~ 'KProxy => PEq (kproxy :: KProxy a) where
type (:==) (x :: a) (y :: a) :: Bool
instance PEq ('KProxy :: KProxy Bool) where
type False :== False = True
type False :== True = False
type True :== False = False
type True :== True = True
instance PEq ('KProxy :: KProxy ()) where
type x :== y = True
}}}
I get
{{{
Type indexes must match class instance head
Found ‘k’ but expected ‘()’
In the type instance declaration for ‘:==’
In the instance declaration for ‘PEq (KProxy :: KProxy ())’
}}}
That's not an overlapping instance error -- I was wrong in my post above.
I guess I didn't look closely at the error. But, GHC should be able to
figure out what I mean here.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9063#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list