[commit: ghc] wip/ttypeable: TcTypeable: Look through type synonyms (8bd1218)

git at git.haskell.org git at git.haskell.org
Sun Jan 29 20:21:39 UTC 2017


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

On branch  : wip/ttypeable
Link       : http://ghc.haskell.org/trac/ghc/changeset/8bd12185e0319ff7fed468c5357332b5ce18e33b/ghc

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

commit 8bd12185e0319ff7fed468c5357332b5ce18e33b
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Sat Jan 28 00:22:39 2017 -0500

    TcTypeable: Look through type synonyms


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

8bd12185e0319ff7fed468c5357332b5ce18e33b
 compiler/typecheck/TcTypeable.hs | 5 ++++-
 1 file changed, 4 insertions(+), 1 deletion(-)

diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs
index 99a7e5b..c3e9b21 100644
--- a/compiler/typecheck/TcTypeable.hs
+++ b/compiler/typecheck/TcTypeable.hs
@@ -434,6 +434,9 @@ mkTyConKindRep (Stuff {..}) tycon = do
   where
     -- Compute RHS
     go :: VarEnv Int -> Kind -> TcRn (LHsExpr Id)
+    go bndrs ty
+      | Just ty' <- coreView ty
+      = go bndrs ty'
     go bndrs (TyVarTy v)
       | Just idx <- lookupVarEnv bndrs v
       = return $ nlHsDataCon kindRepVarDataCon
@@ -456,7 +459,7 @@ mkTyConKindRep (Stuff {..}) tycon = do
                     `nlHsApp` nlHsVar rep_id
                     `nlHsApp` mkList (mkTyConTy kindRepTyCon) tys'
       | otherwise
-      = pprPanic "UnrepresentableThingy" empty
+      = pprPanic "UnrepresentableThingy" (ppr tycon)
     go _bndrs (ForAllTy (TvBndr var _) ty)
       = pprPanic "mkTyConKeyRepBinds(forall)" (ppr var $$ ppr ty)
     --  = let bndrs' = extendVarEnv (mapVarEnv (+1) bndrs) var 0



More information about the ghc-commits mailing list