[Git][ghc/ghc][wip/T21623-faster] Wibbles

Simon Peyton Jones (@simonpj) gitlab at gitlab.haskell.org
Mon Nov 14 14:04:11 UTC 2022



Simon Peyton Jones pushed to branch wip/T21623-faster at Glasgow Haskell Compiler / GHC


Commits:
a72901a2 by Simon Peyton Jones at 2022-11-14T14:05:38+00:00
Wibbles

- - - - -


2 changed files:

- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs


Changes:

=====================================
compiler/GHC/Core/TyCon.hs
=====================================
@@ -2455,15 +2455,25 @@ isTcTyCon :: TyCon -> Bool
 isTcTyCon (TcTyCon {}) = True
 isTcTyCon _            = False
 
-tyConTypeKindPieces :: TyCon -> ([TyConBinder], Kind, Bool)
+tyConTypeKindPieces :: TyCon -> (Kind, [TyConBinder], Kind, Bool)
 -- This rather specialised function returns the bits needed for typeKind
 tyConTypeKindPieces tc
-  | TcTyCon { tyConKind = kind, tcTyConIsPoly = False } <- tc
-  = -- For MonoTcTyCons we must use the tyConKind
-    -- because only that is zonked.  See setTcTyConKind
-    ([], kind, False)
-  | otherwise
-  = (tyConBinders tc, tyConResKind tc, tyConHasClosedResKind tc)
+  | AlgTyCon { tyConKind = k, tyConBinders = bs, tyConResKind = rk, tyConHasClosedResKind = cl } <- tc
+  = (k, bs, rk, cl)
+  | SynonymTyCon { tyConKind = k, tyConBinders = bs, tyConResKind = rk, tyConHasClosedResKind = cl } <- tc
+  = (k, bs, rk, cl)
+  | FamilyTyCon { tyConKind = k, tyConBinders = bs, tyConResKind = rk, tyConHasClosedResKind = cl } <- tc
+  = (k, bs, rk, cl)
+  | PrimTyCon { tyConKind = k, tyConBinders = bs, tyConResKind = rk, tyConHasClosedResKind = cl } <- tc
+  = (k, bs, rk, cl)
+  | PromotedDataCon { tyConKind = k, tyConBinders = bs, tyConResKind = rk, tyConHasClosedResKind = cl } <- tc
+  = (k, bs, rk, cl)
+  | TcTyCon { tyConKind = k, tyConBinders = bs, tyConResKind = rk, tyConHasClosedResKind = cl
+            , tcTyConIsPoly = is_poly } <- tc
+  = if is_poly             -- For MonoTcTyCons we must use the tyConKind
+    then (k, bs, rk, cl)   -- because only that is zonked.  See setTcTyConKind
+    else (k, [], k, False) -- is_closed = False because kind k has free unification variables
+                           --           but actually will is_closed will never be looked at
 
 setTcTyConKind :: TyCon -> Kind -> TyCon
 -- Update the Kind of a TcTyCon


=====================================
compiler/GHC/Core/Type.hs
=====================================
@@ -1482,11 +1482,11 @@ tyConAppResKind :: TyCon -> [Type] -> Kind
 -- Its specification is:
 --   tyConAppResKind tc tys = piResultTys (tyConKind tc) tys
 tyConAppResKind tc args
-  | null args = tyConKind tc
+  | null args = tc_kind
   | otherwise
   = go1 tc_bndrs args
   where
-    !(tc_bndrs, tc_res_kind, closed_res_kind) = tyConTypeKindPieces tc
+    !(tc_kind, tc_bndrs, !tc_res_kind, closed_res_kind) = tyConTypeKindPieces tc
     init_subst = mkEmptySubst $ mkInScopeSet (tyCoVarsOfTypes args)
 
     go1 :: [TyConBinder] -> [Type] -> Type



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a72901a23706212f6d99251b0a993278b5d3171b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a72901a23706212f6d99251b0a993278b5d3171b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20221114/a3131472/attachment-0001.html>


More information about the ghc-commits mailing list