
#10343: Make Typeable track kind information better -------------------------------------+------------------------------------- Reporter: oerjan | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: typeOf :: | Typeable (a::k) => Proxy a -> | TypeRep Blocked By: | Blocking: Related Tickets: #9858, #11011 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by oerjan): From the discussion I've seen, I am purely guessing that all the necessary internal ''representations'' are now available, but the solver part is not. I.e. with `PolyKinds` enabled, the definition {{{ {-# LANGUAGE PolyKinds #-} import Data.Typeable f :: Typeable a => Proxy a -> TypeRep f = typeOf }}} still won't compile, but you ''probably'' can now use the new `TypeRep` mechanisms do write an ''equivalent'' function by hand. On the other hand, since 8.0 with `TypeInType` you can write {{{ f :: (Typeable (a::k), Typeable k) => Proxy a -> TypeRep f = typeOf }}} which means the actual ''need'' for this improvement is less than it was in 7.10. At the time I wrote this ticket, I was somewhat thinking about preserving backwards compatibility, which got broken in 7.10 anyhow. (And until recent trouble with the `constraints` package, I thought no one had been affected in practice - but the last version of that package actually now restricts the kind of the `Deferrable (a ~ b)` instance to `*` in just 7.10, because of this, see discussion at end of https://github.com/ekmett/constraints/issues/43.) Incidentally in GHCi 8.0.1, with `PolyKinds` but ''not'' `TypeInType` enabled: {{{ Prelude Data.Typeable> let f x@Proxy = typeOf x Prelude Data.Typeable> :t f f :: forall k (t :: k). (Typeable * k, Typeable k t) => Proxy k t -> TypeRep }}} which is convenient, but means you get an inferred type you cannot write. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10343#comment:38 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler