[GHC] #9858: Typeable instances should be kind-aware
GHC
ghc-devs at haskell.org
Sat Apr 18 00:55:20 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:98 diatchki]:
> Well, `=>` is not really a type-constructor, but rather a syntactic
form. So I don't think it should ever appear alone, or partially applied,
in a Haskell program.
It doesn't have to appear literally alone. You can already extract a
partially applied form, although seemingly not the "constructor" itself.
{{{
{-# LANGUAGE ImpredicativeTypes #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE FlexibleContexts #-}
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 = h g
}}}
{{{
*Main> :t g
g :: Proxy (* -> *) ((->) (Eq Int))
*Main> :t i
i :: Proxy * (Eq Int => Bool)
}}}
Once you have a partially applied form, you can get `Typeable` instances
for the parts, and then compose them, as shown in [comment:90 comment 90].
Interestingly, GHC internally ensures (and I don't know whether this is a
bug or an intended feature) that if you try to extract the `(=>)`
*itself*, you get `(->) :: * -> * -> *` instead, and a kind matching
error. The same applies to `->` if you try to pattern match away an
unlifted argument type. But in both cases, you can pattern match away a
final *lifted* argument type to get a partially applied `(->)` with an
argument of strange kind.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9858#comment:99>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list