
#9858: Typeable instances should be kind-aware -------------------------------------+------------------------------------- Reporter: dreixel | Owner: dreixel Type: bug | Status: new Priority: highest | Milestone: 7.10.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by oerjan): Ah, I had misunderstood what the wiki page said, then. Now this gives me an idea for a expanded test case. If my picture of how such a solver would work is now more correct, then I think by expanding the kinds in my example a bit, we can get a case where the solver would need not just to ''build'' new kind reps, but also to take the kind rep inside its provided `Typeable` instance further apart. And for good measure let's include a data kind as well: {{{ {-# LANGUAGE PolyKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE AutoDeriveTypeable #-} import Data.Typeable newtype C a b = C () step :: Proxy (a :: [k] -> *) -> Proxy (C a :: [k -> *] -> *) step Proxy = Proxy nest :: Typeable (a :: [k] -> *) => Int -> Proxy a -> TypeRep nest 0 x = typeRep x nest n x = nest (n-1) (step x) main = print $ nest 10 (Proxy :: Proxy (C () :: [()] -> *)) }}} Assuming you would want to support this kind of code. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9858#comment:46 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler