[GHC] #9858: Typeable instances should be kind-aware

GHC ghc-devs at haskell.org
Mon Apr 20 23:47:17 UTC 2015


#9858: Typeable instances should be kind-aware
-------------------------------------+-------------------------------------
        Reporter:  dreixel           |                   Owner:
            Type:  bug               |                  Status:  merge
        Priority:  highest           |               Milestone:  7.10.2
       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:                    |  typecheck/should_fail/T9858a,
                                     |  should_run/T9858b
                                     |                Blocking:
                                     |  Differential Revisions:  Phab:D652
-------------------------------------+-------------------------------------

Comment (by oerjan):

 Replying to [comment:100 simonpj]:
 > Under the fix of comment:96, the line
 > {{{
 > g = f (Proxy :: Proxy (Eq Int => Int))
 > }}}
 > would be rejected because there is no `Typeable (Eq Int => Int)`.  So I
 think it looks fine as-is, don't you?

 That example wasn't using `Typeable`, it was just to demonstrate
 decomposing and rebuilding, which then can be used to ''circumvent'' the
 lack of literal `Typeable (Eq Int => Int)` (Thanks to int-e for help in
 testing this with HEAD):

 {{{
 {-# LANGUAGE ImpredicativeTypes #-}
 {-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE FlexibleContexts #-}

 module ConTyp where

 import Data.Typeable

 f :: Proxy (a b) -> Proxy a
 f _ = Proxy

 g = f (Proxy :: Proxy (Eq Int => Int))

 h :: Proxy a -> Proxy (a Bool)
 h _ = Proxy

 i :: (Typeable a, Typeable b) => Proxy (a b) -> TypeRep
 i p = typeRep p

 j = i (h g)
 }}}

 Which in GHCi gives:

 {{{
 > j
 Eq Int -> Bool
 }}}

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


More information about the ghc-tickets mailing list