[commit: ghc] wip/ttypeable: Fix kind instantiation (132fddc)

git at git.haskell.org git at git.haskell.org
Sun Jan 29 20:22:09 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/ttypeable
Link       : http://ghc.haskell.org/trac/ghc/changeset/132fddc0dfc721d43ed12235df501a24d7cb3004/ghc

>---------------------------------------------------------------

commit 132fddc0dfc721d43ed12235df501a24d7cb3004
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Sat Jan 28 13:18:39 2017 -0500

    Fix kind instantiation


>---------------------------------------------------------------

132fddc0dfc721d43ed12235df501a24d7cb3004
 libraries/base/Data/Typeable/Internal.hs | 8 ++++++--
 1 file changed, 6 insertions(+), 2 deletions(-)

diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs
index aa04030..72079b1 100644
--- a/libraries/base/Data/Typeable/Internal.hs
+++ b/libraries/base/Data/Typeable/Internal.hs
@@ -326,8 +326,10 @@ typeRepKind (TrTyCon _ tc args)
 typeRepKind (TrApp _ f _)
   | TRFun _ res <- typeRepKind f
   = res
+  | otherwise
+  = error ("Ill-kinded type application: " ++ show (typeRepKind f))
 typeRepKind (TrFun _ _ _) = typeRep @Type
-typeRepKind _ = error "Ill-kinded type representation"
+typeRepKind t = error ("Ill-kinded type representation: "++show t)
 
 tyConKind :: TyCon -> [SomeTypeRep] -> SomeTypeRep
 tyConKind (TyCon _ _ _ _ nKindVars# kindRep) kindVars =
@@ -347,7 +349,9 @@ instantiateKindRep vars = go
       = SomeTypeRep $ TRApp (unsafeCoerceRep $ go f) (unsafeCoerceRep $ go a)
     go (KindRepFun a b)
       = SomeTypeRep $ TRFun (unsafeCoerceRep $ go a) (unsafeCoerceRep $ go b)
-    go (KindRepTYPE r) = unkindedTypeRep $ runtimeRepTypeRep r
+    go (KindRepTYPE r) = unkindedTypeRep $ tYPE `kApp` runtimeRepTypeRep r
+
+    tYPE = kindedTypeRep @(RuntimeRep -> Type) @TYPE
 
 unsafeCoerceRep :: SomeTypeRep -> TypeRep a
 unsafeCoerceRep (SomeTypeRep r) = unsafeCoerce r



More information about the ghc-commits mailing list