
#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 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 archblob): I have played with the test case a little to see if I can reduce it, and to see when exactly the error happens. Here is what I have: {{{#!haskell {-# LANGUAGE PolyKinds, TypeFamilies, UndecidableInstances #-} module Bug where class PEnum (k :: a) where type ToEnum (x :: a) :: * type ToEnum x = TEHelper type TEHelper = ToEnum Int }}} That fails as the test case in the ticket, and this one passes: {{{#!haskell {-# LANGUAGE PolyKinds, TypeFamilies, UndecidableInstances #-} module Bug where class PEnum (k :: a) where type ToEnum (x :: b) :: * type ToEnum x = TEHelper type TEHelper = ToEnum Int }}} Also this is the output from {{{-ddump-tc-trace}}} : {{{ rn12 rn13 Tc2 (src) Tc3 kcTyClGroup module Bug class PEnum (k :: a) where type family ToEnum (x :: a) :: * type instance ToEnum x = TEHelper type TEHelper = ToEnum Int env2 [(a, Type variable ‘a’ = a)] env2 [] kcTyClGroup: initial kinds [(PEnum, AThing a -> Constraint), (ToEnum, AThing a -> *)] env2 [] kcd1 TEHelper [] tc_lhs_type: ToEnum Int Expected kind ‘k_av5’ tc_lhs_type: ToEnum Expected kind ‘k_av6’ lk1 ToEnum lk2 ToEnum AThing a -> * writeMetaTyVar k_av6 := a -> * tc_lhs_type: Int The first argument of ‘ToEnum’ should have kind ‘a’ lk1 Int lk2 Int Type constructor ‘Int’ checkExpectedKind Int * a checkExpectedKind 1 Int * a ([(k0, 1)], [(av4, a)]) ([(k0, 1)], [(av4, a)]) Adding error: Bug.hs:9: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’ tryTc/recoverM recovering from IOEnv failure Bug.hs:9: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’ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9151#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler