Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: 302422b4 by Apoorv Ingle at 2025-11-25T17:42:57-06:00 hopefully fixes all the error messages - - - - - 3 changed files: - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -536,7 +536,7 @@ checkResultTy :: DeepSubsumptionFlag -- expose foralls, but maybe not /deeply/ instantiated -> ExpRhoType -- Expected type; this is deeply skolemised -> TcM HsWrapper -checkResultTy ds_flag rn_expr (fun, _) _inst_args app_res_rho (Infer inf_res) +checkResultTy ds_flag rn_expr _ _ app_res_rho (Infer inf_res) = fillInferResult ds_flag (exprCtOrigin rn_expr) app_res_rho inf_res checkResultTy ds_flag rn_expr (tc_fun, fun_loc) inst_args app_res_rho (Check res_ty) ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -335,7 +335,7 @@ tcExpr e@(HsLit x lit) res_ty ; tcWrapResult e (HsLit x (convertLit lit)) lit_ty res_ty } tcExpr (HsPar x expr) res_ty - = do { expr' <- tcMonoLExpr expr res_ty + = do { expr' <- tcMonoLExprNC expr res_ty ; return (HsPar x expr') } tcExpr (HsPragE x prag expr) res_ty ===================================== compiler/GHC/Tc/Gen/Match.hs ===================================== @@ -42,7 +42,7 @@ import GHC.Prelude import {-# SOURCE #-} GHC.Tc.Gen.Expr( tcSyntaxOp, tcInferRho, tcInferRhoFRRNC , tcMonoLExprNC, tcMonoLExpr, tcExpr , tcCheckMonoExpr, tcCheckMonoExprNC - , tcCheckPolyExpr, tcPolyExpr ) + , tcCheckPolyExpr, tcPolyLExpr ) import GHC.Rename.Utils ( bindLocalNames ) import GHC.Tc.Errors.Types @@ -420,15 +420,10 @@ tcDoStmts mDoExpr ss@(L _ stmts) res_ty } tcBody :: LHsExpr GhcRn -> ExpRhoType -> TcM (LHsExpr GhcTc) -tcBody (L lspan e) res_ty - = L lspan <$> - do { traceTc "tcBody" (ppr res_ty) - ; setSrcSpanA lspan $ - addErrCtxt (ExprCtxt e) $ - -- We want the right hand side of a match or an equation - -- to always get printed in the error context - tcPolyExpr e res_ty - } +tcBody body res_ty + = do { traceTc "tcBody" (ppr res_ty) + ; tcPolyLExpr body res_ty + } {- ************************************************************************ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/302422b43e271908fd6c3ebb3ea59f85... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/302422b43e271908fd6c3ebb3ea59f85... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Apoorv Ingle (@ani)