[Git][ghc/ghc][wip/T25647] add and use HM_FamSig for (a :: _) in type family
Patrick (@soulomoon)
gitlab at gitlab.haskell.org
Sat Feb 15 00:08:46 UTC 2025
Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC
Commits:
9ab780da by Patrick at 2025-02-15T08:08:37+08:00
add and use HM_FamSig for (a :: _) in type family
- - - - -
1 changed file:
- compiler/GHC/Tc/Gen/HsType.hs
Changes:
=====================================
compiler/GHC/Tc/Gen/HsType.hs
=====================================
@@ -977,6 +977,7 @@ type HoleInfo = Maybe (TcLevel, HoleMode)
-- of anonymous wildcards; see tcAnonWildCardOcc
data HoleMode = HM_Sig -- Partial type signatures: f :: _ -> Int
| HM_FamPat FamArgType -- Family instances: F _ Int = Bool
+ | HM_FamSig -- Family instances: F (a :: _) Int = Bool
| HM_VTA -- Visible type and kind application:
-- f @(Maybe _)
-- Maybe @(_ -> _)
@@ -1017,6 +1018,7 @@ updateFamArgType fam_arg m at TcTyMode { mode_tyki = tyki, mode_holes = mh }
instance Outputable HoleMode where
ppr HM_Sig = text "HM_Sig"
ppr (HM_FamPat artType) = text ("HM_FamPat " ++ show artType)
+ ppr HM_FamSig = text "HM_FamSig"
ppr HM_VTA = text "HM_VTA"
ppr HM_TyAppPat = text "HM_TyAppPat"
@@ -1293,7 +1295,7 @@ tcHsType mode rn_ty@(HsAppKindTy{}) exp_kind = tc_app_ty mode rn_ty exp_kind
tcHsType mode rn_ty@(HsOpTy{}) exp_kind = tc_app_ty mode rn_ty exp_kind
tcHsType mode rn_ty@(HsKindSig _ ty sig) exp_kind
- = do { let mode' = (updateHoleMode HM_Sig $ mode { mode_tyki = KindLevel})
+ = do { let mode' = (updateHoleMode HM_FamSig $ mode { mode_tyki = KindLevel})
; sig' <- tc_lhs_kind_sig mode' KindSigCtxt sig
-- We must typecheck the kind signature, and solve all
-- its equalities etc; from this point on we may do
@@ -2262,6 +2264,7 @@ tcAnonWildCardOcc is_extra (TcTyMode { mode_holes = Just (hole_lvl, hole_mode) }
wc_nm = case hole_mode of
HM_Sig -> fsLit "w"
HM_FamPat _ -> fsLit "_"
+ HM_FamSig -> fsLit "_"
HM_VTA -> fsLit "w"
HM_TyAppPat -> fsLit "_"
newSkolemTvDetailsAtLevel tclvl =
@@ -2273,6 +2276,7 @@ tcAnonWildCardOcc is_extra (TcTyMode { mode_holes = Just (hole_lvl, hole_mode) }
emit_holes = case hole_mode of
HM_Sig -> True
HM_FamPat _ -> False
+ HM_FamSig -> False
HM_VTA -> False
HM_TyAppPat -> False
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9ab780da39c2afbce2411c2b96fef4108d6b8b70
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9ab780da39c2afbce2411c2b96fef4108d6b8b70
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/20250214/69987efc/attachment-0001.html>
More information about the ghc-commits
mailing list