
Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: c5cd0302 by Apoorv Ingle at 2025-06-08T22:45:10-05:00 remove addHeadCtxt - - - - - 2 changed files: - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Head.hs Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -408,6 +408,7 @@ tcApp fun_orig rn_expr exp_res_ty vcat [ text "rn_expr:" <+> ppr rn_expr , text "rn_fun:" <+> ppr rn_fun , text "fun_ctxt:" <+> ppr fun_ctxt + , text "orig:" <+> ppr fun_orig , text "rn_args:" <+> ppr rn_args ] -- Step 2: Infer the type of `fun`, the head of the application @@ -769,7 +770,7 @@ tcInstFun do_ql inst_final fun_orig (tc_fun, rn_fun, fun_ctxt) fun_sigma rn_args = do { (_inst_tvs, wrap, fun_rho) <- -- addHeadCtxt: important for the class constraints -- that may be emitted from instantiating fun_sigma - addHeadCtxt fun_ctxt $ + setSrcSpan fun_ctxt $ instantiateSigma fun_orig fun_conc_tvs tvs theta body2 -- See Note [Representation-polymorphism checking built-ins] -- in GHC.Tc.Utils.Concrete. ===================================== compiler/GHC/Tc/Gen/Head.hs ===================================== @@ -26,7 +26,7 @@ module GHC.Tc.Gen.Head , nonBidirectionalErr , pprArgInst - , addHeadCtxt, addExprCtxt, addFunResCtxt ) where + , addExprCtxt, addFunResCtxt ) where import {-# SOURCE #-} GHC.Tc.Gen.Expr( tcExpr, tcCheckPolyExprNC, tcPolyLExprSig ) import {-# SOURCE #-} GHC.Tc.Gen.Splice( getUntypedSpliceBody ) @@ -458,8 +458,8 @@ tcInferAppHead :: (HsExpr GhcRn, SrcSpan) -- cases are dealt with by splitHsApps. -- -- See Note [tcApp: typechecking applications] in GHC.Tc.Gen.App -tcInferAppHead (fun,ctxt) - = addHeadCtxt ctxt $ +tcInferAppHead (fun,fun_loc) + = setSrcSpan fun_loc $ do { mb_tc_fun <- tcInferAppHead_maybe fun ; case mb_tc_fun of Just (fun', fun_sigma) -> return (fun', fun_sigma) @@ -480,13 +480,6 @@ tcInferAppHead_maybe fun = HsOverLit _ lit -> Just <$> tcInferOverLit lit _ -> return Nothing -addHeadCtxt :: SrcSpan -> TcM a -> TcM a --TODO ANI: Why not just setSrcSpan? -addHeadCtxt fun_loc thing_inside - | not (isGoodSrcSpan fun_loc) -- noSrcSpan => no arguments - = thing_inside -- => context is already set - | otherwise - = setSrcSpan fun_loc thing_inside - {- ********************************************************************* * * View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c5cd030283615b7c070e376433c4ed66... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c5cd030283615b7c070e376433c4ed66... You're receiving this email because of your account on gitlab.haskell.org.