[Git][ghc/ghc][wip/T24553] Wibbles
Simon Peyton Jones (@simonpj)
gitlab at gitlab.haskell.org
Wed Mar 20 17:49:14 UTC 2024
Simon Peyton Jones pushed to branch wip/T24553 at Glasgow Haskell Compiler / GHC
Commits:
da67e176 by Simon Peyton Jones at 2024-03-20T17:48:58+00:00
Wibbles
- - - - -
3 changed files:
- compiler/GHC/Core/TyCo/Compare.hs
- compiler/GHC/Core/TyCo/Ppr.hs
- compiler/GHC/Iface/Type.hs
Changes:
=====================================
compiler/GHC/Core/TyCo/Compare.hs
=====================================
@@ -22,7 +22,8 @@ module GHC.Core.TyCo.Compare (
import GHC.Prelude
-import GHC.Core.Type( typeKind, coreView, tcSplitAppTyNoView_maybe, splitAppTyNoView_maybe )
+import GHC.Core.Type( typeKind, coreView, tcSplitAppTyNoView_maybe, splitAppTyNoView_maybe
+ , isLevityTy, isRuntimeRepTy, isMultiplicityTy )
import GHC.Core.TyCo.Rep
import GHC.Core.TyCo.FVs
@@ -153,6 +154,7 @@ tc_eq_type :: Bool -- ^ True <=> do not expand type synonyms
-> Bool
-- Flags False, False is the usual setting for tc_eq_type
-- See Note [Computing equality on types] in Type
+{-# INLINE tc_eq_type #-} -- See Note [Specialising tc_eq_type].
tc_eq_type keep_syns vis_only orig_ty1 orig_ty2
= go orig_env orig_ty1 orig_ty2
where
@@ -181,8 +183,8 @@ tc_eq_type keep_syns vis_only orig_ty1 orig_ty2
-- with True; that result makes GHC print the type with all foralls and
-- kinds. See Note [Showing invisible bits of types in error messages]
-- in GHC.Tc.Errors.Ppr
- go _ (ForAllTy {}) _ | vis_only = True
- go _ _ (ForAllTy {})| vis_only = True
+ go _ (ForAllTy b _) _ | vis_only, isDefaultableBndr b = True
+ go _ _ (ForAllTy b _) | vis_only, isDefaultableBndr b = True
-- Make sure we handle all FunTy cases since falling through to the
-- AppTy case means that tcSplitAppTyNoView_maybe may see an unzonked
@@ -229,8 +231,13 @@ tc_eq_type keep_syns vis_only orig_ty1 orig_ty2
orig_env = mkRnEnv2 $ mkInScopeSet $ tyCoVarsOfTypes [orig_ty1, orig_ty2]
-{-# INLINE tc_eq_type #-} -- See Note [Specialising tc_eq_type].
-
+isDefaultableBndr :: ForAllTyBinder -> Bool
+-- This should line up with the defaulting done
+-- by GHC.Iface.Type.deafultIfaceTyVarsOfKind
+isDefaultableBndr (Bndr tv vis)
+ = isInvisibleForAllTyFlag vis && is_defaultable (tyVarKind tv)
+ where
+ is_defaultable ki = isLevityTy ki || isRuntimeRepTy ki || isMultiplicityTy ki
-- | Do these denote the same level of visibility? 'Required'
-- arguments are visible, others are not. So this function
=====================================
compiler/GHC/Core/TyCo/Ppr.hs
=====================================
@@ -336,8 +336,7 @@ pprTypeApp tc tys
pprWithInvisibleBitsWhen :: Bool -> SDoc -> SDoc
pprWithInvisibleBitsWhen b
= updSDocContext $ \ctx ->
- if b then ctx { sdocPrintExplicitForalls = True
- , sdocPrintExplicitKinds = True
+ if b then ctx { sdocPrintExplicitKinds = True
, sdocPrintExplicitRuntimeReps = True }
else ctx
=====================================
compiler/GHC/Iface/Type.hs
=====================================
@@ -1189,7 +1189,7 @@ defaultIfaceTyVarsOfKind def_rep def_mult ty = go emptyFsEnv True ty
-> IfaceType
go subs True (IfaceForAllTy (Bndr (IfaceTvBndr (var, var_kind)) argf) ty)
| isInvisibleForAllTyFlag argf -- Don't default *visible* quantification
- -- or we get the mess in #13963
+ -- or we get the mess in #13963
, Just substituted_ty <- check_substitution var_kind
= let subs' = extendFsEnv subs var substituted_ty
-- Record that we should replace it with LiftedRep/Lifted/Many,
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/da67e1766b2eeaa819ec84ab226f0874820e73bc
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/da67e1766b2eeaa819ec84ab226f0874820e73bc
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/20240320/e34866b3/attachment-0001.html>
More information about the ghc-commits
mailing list