
Simon Peyton Jones pushed to branch wip/T26115 at Glasgow Haskell Compiler / GHC Commits: 4cca8e5e by Simon Peyton Jones at 2025-06-16T09:53:00+01:00 Fix inverted test - - - - - a0406056 by Simon Peyton Jones at 2025-06-16T10:22:16+01:00 Missing close paren in tc-trace - - - - - 24cc2a81 by Simon Peyton Jones at 2025-06-16T10:22:34+01:00 A bit more tc-tracing for record updates - - - - - c9c848ad by Simon Peyton Jones at 2025-06-16T10:22:51+01:00 Don't create implications for FunSigCtxt unless we have to - - - - - 4 changed files: - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Utils/Unify.hs Changes: ===================================== compiler/GHC/Core/Opt/Specialise.hs ===================================== @@ -2965,15 +2965,14 @@ singleCall spec_env id args unitBag (CI { ci_key = args , ci_fvs = fvVarSet call_fvs }) } where - call_fvs | gopt Opt_PolymorphicSpecialisation (se_dflags spec_env) - = specArgsFVs isLocalVar args - | otherwise - = specArgsFVs isLocalId args + poly_spec = gopt Opt_PolymorphicSpecialisation (se_dflags spec_env) - -- specArgFreeIds: we specifically look for free Ids, not TyVars - -- see (MP1) in Note [Specialising polymorphic dictionaries] - -- - -- We don't include the 'id' itself. + -- With -fpolymorphic-specialisation, keep just local /Ids/ + -- Otherwise, keep /all/ free vars including TyVars + -- See (MP1) in Note [Specialising polymorphic dictionaries] + -- But NB: we don't include the 'id' itself. + call_fvs | poly_spec = specArgsFVs isLocalId args + | otherwise = specArgsFVs isLocalVar args mkCallUDs :: SpecEnv -> OutExpr -> [OutExpr] -> UsageDetails mkCallUDs env fun args @@ -3504,7 +3503,7 @@ What should we do when a value is specialised to a *strict* unboxed value? in h:t Could convert let to case: - + map_*_Int# f (x:xs) = case f x of h# -> let t = map f xs in h#:t ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -460,6 +460,7 @@ finishApp tc_head@(tc_fun,_) tc_args app_res_rho res_wrap ; res_expr <- if isTagToEnum tc_fun then tcTagToEnum tc_head tc_args app_res_rho else return (rebuildHsApps tc_head tc_args) + ; traceTc "End tcApp }" (ppr tc_fun) ; return (mkHsWrap res_wrap res_expr) } checkResultTy :: HsExpr GhcRn ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -1481,6 +1481,7 @@ expandRecordUpd record_expr possible_parents rbnds res_ty vcat [ text "relevant_con:" <+> ppr relevant_con , text "res_ty:" <+> ppr res_ty , text "ds_res_ty:" <+> ppr ds_res_ty + , text "ds_expr:" <+> ppr ds_expr ] ; return (ds_expr, ds_res_ty, RecordUpdCtxt relevant_cons upd_fld_names ex_tvs) } ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -583,7 +583,6 @@ alwaysBuildImplication :: SkolemInfoAnon -> Bool -- See Note [When to build an implication] alwaysBuildImplication (SigSkol ctxt _ _) = case ctxt of - FunSigCtxt {} -> True -- RHS of a binding with a signature SpecInstCtxt -> True -- SpecInstCtxt: this is rather delicate _ -> False alwaysBuildImplication _ = False @@ -591,6 +590,10 @@ alwaysBuildImplication _ = False {- Commmented out for now while I figure out about error messages. See #14185 +Caution: we get some duplication of errors if we build more implications. +Because we get one error for each function RHS, even if it's for +the same class constraint. + alwaysBuildImplication (SigSkol ctxt _ _) = case ctxt of FunSigCtxt {} -> True -- RHS of a binding with a signature View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/13a1fcecf95a5809d4dc9d84ac8dfb5... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/13a1fcecf95a5809d4dc9d84ac8dfb5... You're receiving this email because of your account on gitlab.haskell.org.