[GHC] #9151: Recursive default associated types don't kind-generalize properly

GHC ghc-devs at haskell.org
Thu May 29 17:10:52 UTC 2014


#9151: Recursive default associated types don't kind-generalize properly
------------------------------------+-------------------------------------
       Reporter:  goldfire          |             Owner:
           Type:  bug               |            Status:  new
       Priority:  normal            |         Milestone:
      Component:  Compiler          |           Version:  7.8.2
       Keywords:                    |  Operating System:  Unknown/Multiple
   Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
     Difficulty:  Unknown           |         Test Case:
     Blocked By:                    |          Blocking:
Related Tickets:                    |
------------------------------------+-------------------------------------
 When I say

 {{{
 {-# LANGUAGE PolyKinds, DataKinds, TypeFamilies, UndecidableInstances #-}

 module Bug where

 import Data.Proxy

 class PEnum (kproxy :: KProxy a) where
   type ToEnum (x :: a) :: Bool
   type ToEnum x = TEHelper

 type TEHelper = ToEnum Int
 }}}

 I get

 {{{
 /Users/rae/temp/Bug.hs:11:24:
     The first argument of ‘ToEnum’ should have kind ‘a’,
       but ‘Int’ has kind ‘*’
     In the type ‘ToEnum Int’
     In the type declaration for ‘TEHelper’
 }}}

 I believe my original code should kind-check, as `ToEnum` should be
 applicable to any kind.

 My guess is that this sort of recursion isn't properly accounted for in
 the kind-checking algorithm in !TcTyClsDecls, and that we kind-check
 `TEHelper` before `ToEnum` is kind-generalized.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9151>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list