[Git][ghc/ghc][wip/spj-apporv-Oct24] Fix for error contexts when the expression has a signature. Fix notes
Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC Commits: 91dc2a73 by Apoorv Ingle at 2025-11-23T18:13:51-06:00 Fix for error contexts when the expression has a signature. Fix notes - - - - - 5 changed files: - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Types/LclEnv.hs - compiler/GHC/Tc/Utils/Monad.hs Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -426,7 +426,6 @@ tcApp rn_expr exp_res_ty -- If it is generated code location span, blame it on the -- source code origin stored in the lclEnv. -- See Note [Error contexts in generated code] - -- See Note [Error Context Stack] ; code_orig <- getSrcCodeOrigin ; let fun_orig | not (isGeneratedSrcSpan fun_lspan) = exprCtOrigin rn_fun ===================================== compiler/GHC/Tc/Gen/Do.hs ===================================== @@ -445,7 +445,7 @@ It stores the original statement (with location) and the expanded expression as precise as possible, and not just blame the complete `do`-block. Thus, when we typecheck the application `(>>) e1`, we push the "In the stmt of do block e1" with the source location of `e1` in the error context stack as we walk inside an `ExpandedThingRn`. - See also Note [splitHsApps] and Note [Error Context Stack] + See also Note [splitHsApps] * After the expanded expression of a `do`-statement is typechecked and before moving to the next statement of the `do`-block, we need to first pop the top ===================================== compiler/GHC/Tc/Gen/Head.hs ===================================== @@ -1090,14 +1090,26 @@ add_expr_ctxt e thing_inside -- f x = _ -- when we don't want to say "In the expression: _", -- because it is mentioned in the error message itself + HsPar _ e -> add_expr_ctxt (unLoc e) thing_inside - -- We don't want to say 'In the expression (e)', - -- we just want to say 'In the expression, 'e' - -- which will be handeled by the recursive call in thing_inside - -- This may be a little inefficient with nested parens exprs, eg. (((e))) - -- But it should be okay as I do not expect too many parens to be nested consecutively + -- We don't want to say 'In the expression (e)', + -- we just want to say 'In the expression, 'e' + -- which will be handeled by the recursive call in thing_inside + -- This may be a little inefficient with nested parens exprs, eg. (((e))) + -- But it should be okay as I do not expect too many parens to be nested consecutively + + ExprWithTySig _ (L _ e') _ + | XExpr (ExpandedThingRn o _) <- e' -> addExpansionErrCtxt o (ExprCtxt e) + thing_inside + -- There is a special case for expressions with signatures to avoid having too verbose + -- error context. So here we flip the ErrCtxt state to expanded if the expression is expanded. + -- c.f. RecordDotSyntaxFail9 + XExpr (ExpandedThingRn o _) -> addExpansionErrCtxt o (srcCodeOriginErrCtxMsg o) thing_inside - _ -> addErrCtxt (ExprCtxt e) thing_inside -- no op in generated code + -- Flip error ctxt into expansion mode + + _ -> addErrCtxt (ExprCtxt e) thing_inside + -- no op in generated code addLExprCtxt :: SrcSpan -> HsExpr GhcRn -> TcRn a -> TcRn a ===================================== compiler/GHC/Tc/Types/LclEnv.hs ===================================== @@ -112,7 +112,7 @@ This data structure keeps track of two things: -} --- See Note [Error Context Stack] +-- See Note [ErrCtxtStack Manipulation] type ErrCtxtStack = [ErrCtxt] -- | Get the original source code @@ -125,7 +125,7 @@ get_src_code_origin _ = Nothing data TcLclCtxt = TcLclCtxt { tcl_loc :: RealSrcSpan, -- Source span - tcl_err_ctxt :: ErrCtxtStack, -- See Note [Error Context Stack] + tcl_err_ctxt :: ErrCtxtStack, -- See Note [ErrCtxtStack Manipulation] tcl_tclvl :: TcLevel, tcl_bndrs :: TcBinderStack, -- Used for reporting relevant bindings, -- and for tidying type @@ -204,7 +204,7 @@ getLclEnvSrcCodeOrigin = get_src_code_origin . tcl_err_ctxt . tcl_lcl_ctxt setLclEnvSrcCodeOrigin :: ErrCtxt -> TcLclEnv -> TcLclEnv setLclEnvSrcCodeOrigin ec = modifyLclCtxt (setLclCtxtSrcCodeOrigin ec) --- See Note [ErrCtxt Stack Manipulation] +-- See Note [ErrCtxtStack Manipulation] setLclCtxtSrcCodeOrigin :: ErrCtxt -> TcLclCtxt -> TcLclCtxt setLclCtxtSrcCodeOrigin ec lclCtxt | MkErrCtxt (ExpansionCodeCtxt _) _ : ecs <- tcl_err_ctxt lclCtxt ===================================== compiler/GHC/Tc/Utils/Monad.hs ===================================== @@ -1089,20 +1089,9 @@ getSrcCodeOrigin = then getLclEnvSrcCodeOrigin <$> getLclEnv else return Nothing - --- | Mark the inner computation as being done inside generated code. --- --- See Note [Error contexts in generated code] --- See Note [Error Context Stack] --- setInGeneratedCode :: SrcCodeOrigin -> TcRn a -> TcRn a --- setInGeneratedCode sco thing_inside = --- -- updLclCtxt setLclCtxtInGenCode $ --- updLclCtxt (setLclCtxtSrcCodeOrigin sco) thing_inside - setSrcSpanA :: EpAnn ann -> TcRn a -> TcRn a setSrcSpanA l = setSrcSpan (locA l) - addLocM :: (HasLoc t) => (a -> TcM b) -> GenLocated t a -> TcM b addLocM fn (L loc a) = setSrcSpan (getHasLoc loc) $ fn a @@ -1327,7 +1316,7 @@ So, it's better to do a `setSrcSpan` /before/ `addErrCtxt`. more discussion of this fancy footwork - See Note [Generated code and pattern-match checking] in `GHC.Types.Basic` for the relation with pattern-match checks -- See Note [Error Context Stack] in `GHC.Tc.Types.LclEnv` for info about `ErrCtxtStack` +- See Note [ErrCtxtStack Manipulation] in `GHC.Tc.Types.LclEnv` for info about `ErrCtxtStack` -} getErrCtxt :: TcM [ErrCtxt] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/91dc2a737182c0511e6ebf0492b953cc... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/91dc2a737182c0511e6ebf0492b953cc... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Apoorv Ingle (@ani)