[Git][ghc/ghc][wip/ani/ctorig-stuff] fix suggestion in error message for record field and modify herald everywhere

Apoorv Ingle pushed to branch wip/ani/ctorig-stuff at Glasgow Haskell Compiler / GHC Commits: 8fa065e5 by Apoorv Ingle at 2025-07-14T08:47:52-05:00 fix suggestion in error message for record field and modify herald everywhere - - - - - 4 changed files: - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Unify.hs - + compiler/hie.yaml Changes: ===================================== compiler/GHC/Tc/Errors.hs ===================================== @@ -24,6 +24,10 @@ import GHC.Driver.Config.Diagnostic import GHC.Rename.Unbound +import Language.Haskell.Syntax (DotFieldOcc (..)) +import Language.Haskell.Syntax.Basic (FieldLabelString (..)) +import GHC.Hs.Expr (SrcCodeOrigin (..), HsExpr (..)) + import GHC.Tc.Types import GHC.Tc.Utils.Monad import GHC.Tc.Errors.Types @@ -2349,7 +2353,7 @@ mk_dict_err ctxt (item, (matches, pot_unifiers, unsafe_overlapped)) isNothing (lookupLocalRdrOcc lcl_env occ_name) record_field = case orig of - GetFieldOrigin name -> Just (mkVarOccFS name) + ExpansionOrigin (OrigExpr (HsGetField _ _ (L _ name))) -> Just (mkVarOccFS (field_label $ unLoc $ dfoLabel name)) _ -> Nothing {- Note [Report candidate instances] ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -788,7 +788,8 @@ lexprCtOrigin (L _ e) = exprCtOrigin e exprCtOrigin :: HsExpr GhcRn -> CtOrigin exprCtOrigin (HsVar _ (L _ (WithUserRdr _ name))) = OccurrenceOf name -exprCtOrigin (HsGetField _ _ (L _ f)) = GetFieldOrigin (field_label $ unLoc $ dfoLabel f) +exprCtOrigin e@(HsGetField _ _ (L _ _)) = ExpansionOrigin (OrigExpr e) + -- GetFieldOrigin (field_label $ unLoc $ dfoLabel f) exprCtOrigin (HsOverLabel _ l) = OverLabelOrigin l exprCtOrigin (ExplicitList {}) = ListOrigin exprCtOrigin (HsIPVar _ ip) = IPOccOrigin ip @@ -1081,6 +1082,7 @@ pprCtO (ImpedanceMatching {}) = text "combining required constraints" pprCtO (NonLinearPatternOrigin _ pat) = hsep [text "a non-linear pattern" <+> quotes (ppr pat)] pprCtO (ExpansionOrigin (OrigPat p)) = hsep [text "a pattern" <+> quotes (ppr p)] pprCtO (ExpansionOrigin (OrigStmt{})) = text "a do statement" +pprCtO (ExpansionOrigin (OrigExpr (HsGetField _ _ (L _ f)))) = hsep [text "selecting the field", quotes (ppr f)] pprCtO (ExpansionOrigin (OrigExpr e)) = text "an expression" <+> ppr e pprCtO (ExpectedFunTySyntaxOp{}) = text "a rebindable syntax operator" pprCtO (ExpectedFunTyViewPat{}) = text "a view pattern" ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -174,7 +174,7 @@ matchActualFunTy herald mb_thing err_info fun_ty go (FunTy { ft_af = af, ft_mult = w, ft_arg = arg_ty, ft_res = res_ty }) = assert (isVisibleFunArg af) $ - do { hasFixedRuntimeRep_syntactic (FRRExpectedFunTy herald 1) arg_ty + do { hasFixedRuntimeRep_syntactic (FRRExpectedFunTy (updatePositionCtOrigin 1 herald) 1) arg_ty ; return (idHsWrapper, Scaled w arg_ty, res_ty) } go ty@(TyVarTy tv) @@ -852,7 +852,7 @@ matchExpectedFunTys herald ctx arity (Check top_ty) thing_inside , ft_arg = arg_ty, ft_res = res_ty }) = assert (isVisibleFunArg af) $ do { let arg_pos = arity - n_req + 1 -- 1 for the first argument etc - ; (arg_co, arg_ty) <- hasFixedRuntimeRep (FRRExpectedFunTy herald arg_pos) arg_ty + ; (arg_co, arg_ty) <- hasFixedRuntimeRep (FRRExpectedFunTy (updatePositionCtOrigin arg_pos herald) arg_pos) arg_ty ; (wrap_res, result) <- check (n_req - 1) (mkCheckExpFunPatTy (Scaled mult arg_ty) : rev_pat_tys) res_ty ===================================== compiler/hie.yaml ===================================== @@ -0,0 +1,9 @@ +# This is a IDE configuration file which tells IDEs such as `ghcide` how +# to set up a GHC API session for this project. +# +# To use it in windows systems replace the config with +# cradle: {bios: {program: "./hadrian/hie-bios.bat"}} +# +# The format is documented here - https://github.com/mpickering/hie-bios +cradle: {bios: {program: "./hadrian/hie-bios", + with-ghc: "~/.ghcup/bin/ghc"}} View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8fa065e50b36cd9e8df3fc3ead631ad9... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8fa065e50b36cd9e8df3fc3ead631ad9... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Apoorv Ingle (@ani)