[GHC] #8630: Kind inference fails to account for associated types
GHC
ghc-devs at haskell.org
Fri Dec 27 02:07:08 UTC 2013
#8630: Kind inference fails to account for associated types
-------------------------------------------+-------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type checker) | Version: 7.7
Keywords: | Operating System:
Architecture: Unknown/Multiple | Unknown/Multiple
Difficulty: Unknown | Type of failure:
Blocked By: | None/Unknown
Related Tickets: | Test Case:
| Blocking:
-------------------------------------------+-------------------------------
Consider this:
{{{
{-# LANGUAGE PolyKinds, TypeFamilies, FlexibleInstances #-}
class C a where
type F a
instance C a where
type F a = a -> a
}}}
HEAD gives me
{{{
Expected a type, but ‛a’ has kind ‛k’
In the type ‛a -> a’
In the type instance declaration for ‛F’
In the instance declaration for ‛C a’
}}}
The problem is that the use of `(->)` in the RHS of the definition for the
`F a` instance constrains `a` to be of kind `*`, but GHC does not
propagate this information back to the instance head. This decision is in
conflict with the behavior for ''class'' declarations (as opposed to
''instance'' declarations), where a type variable's use in the definition
informs its kind in the head.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8630>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list