Simon Peyton Jones pushed to branch wip/T26615 at Glasgow Haskell Compiler / GHC Commits: a47e6e22 by Simon Peyton Jones at 2026-01-11T23:22:44+00:00 Wibbles - - - - - 5 changed files: - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/WorkWrap.hs - compiler/GHC/Core/Rules.hs - testsuite/tests/simplCore/should_compile/spec-inline.stderr Changes: ===================================== compiler/GHC/Core/Opt/SpecConstr.hs ===================================== @@ -1864,7 +1864,7 @@ specialise env bind_calls (RI { ri_fn = fn, ri_lam_bndrs = arg_bndrs return (nullUsage, spec_info, []) | not (isNeverActive (idInlineActivation fn)) - -- See Note [Transfer activation] + -- See (SCRA1) in Note [SpecConstr: rule activation] -- Don't specialise OPAQUE things, see Note [OPAQUE pragma]. -- Since OPAQUE things are always never-active (see -- GHC.Parser.PostProcess.mkOpaquePragma) this guard never fires for @@ -2075,7 +2075,7 @@ mkSeqs seqees res_ty rhs = = rhs specConstrRuleActivation :: InlinePragmaInfo -> ActivationGhc --- See Note [SpecConstr rule activation] +-- See Note [SpecConstr: rule activation] specConstrRuleActivation fn_prag = activeAfter $ nextPhase $ beginPhase $ inlinePragmaActivation fn_prag @@ -2129,7 +2129,7 @@ The void argument must follow the foralls, lest the forall be ill-kinded. See Note [Worker/wrapper needs to add void arg last] in GHC.Core.Opt.WorkWrap.Utils. -Note [SpecConstr rule activation] +Note [SpecConstr: rule activation] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When should the RULE generated by SpecConstr be activated? See the function `specConstrRuleActivation`. @@ -2163,15 +2163,13 @@ Goal 1: "SC:1" won't fire in f's unfolding; see Note [What is active in the RHS of a RULE or unfolding?] Goal 2: "SPEC:f" has the same activation as `f`; - see Note [Auto-specialisation and RULES]). So "SPEC:f" will fire + see Note [Specialise: rule activation]. So "SPEC:f" will fire before "SC:1" -Other points: - -* c.f. Note [Auto-specialisation and RULES] in GHC.Core.Opt.Specialise. -* his in turn means there is no point in specialising NOINLINE things, -so we test for that. +Wrinkles +(SCRA1) If `f` is NOINLINE we arguably don't want a specialisation at all. + See (SRA1) in GHC.Core.Opt.Specialise. At least that's the choice for now. Note [generaliseDictPats] ~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Core/Opt/Specialise.hs ===================================== @@ -1588,7 +1588,7 @@ specCalls spec_imp env existing_rules calls_for_me fn rhs | notNull calls_for_me -- And there are some calls to specialise && not (isNeverActive (idInlineActivation fn)) -- Don't specialise NOINLINE things - -- See Note [Auto-specialisation and RULES] + -- See (SRA1) in Note [Specialise: rule activation] -- -- Don't specialise OPAQUE things, see Note [OPAQUE pragma]. -- Since OPAQUE things are always never-active (see @@ -1619,7 +1619,7 @@ specCalls spec_imp env existing_rules calls_for_me fn rhs fn_unf = realIdUnfolding fn -- Ignore loop-breaker-ness here fn_prag = idInlinePragma fn rule_act = inlinePragmaActivation fn_prag - -- rule_act: see Note [Auto-specialisation and RULES] + -- rule_act: see Note [Specialise: rule activation] is_active :: ActivationGhc -> Bool is_active = isActive (SimplPhaseRange (beginPhase rule_act) (endPhase rule_act)) -- is_active: rule_act is the activation we are going to put in the new @@ -2361,8 +2361,8 @@ argument pattern. Wrinkles (SC3) Annoyingly, we /also/ eliminate duplicates in `filterCalls`. See (MP3) in Note [Specialising polymorphic dictionaries] -Note [Auto-specialisation and RULES] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Note [Specialise: rule activation] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider: g :: Num a => a -> a g = ... @@ -2383,15 +2383,22 @@ also add RULE f g_spec = 0 But that's a bit complicated. For now we lean on the programmer: - * Set the activation of the RULE is the same as the activation of the Id, + + * Make the activation of the RULE be the same as the activation of the Id, i.e. (idInlineActivation g) So if `g` says {-# NOINLINE[2] g #-}, then the auto-spec rule will also not be active until phase 2. And that's what programmers should jolly well do anyway, even aside from specialisation, to ensure that `g` doesn't inline too early. -This in turn means that the RULE would never fire for a NOINLINE -thing so not much point in generating a specialisation at all. +Wrinkles + +(SRA1) This in turn means that the RULE would never fire for a NOINLINE thing + so not much point in generating a specialisation at all. This is a + bit moot: it's not unreasonable to have a (NOINLINE) specialisation for a + NOINLINE function. But currently we don't. And hence we don't create + a specialisation for an OPAQUE function either (see Note [OPAQUE pragma] + in Language.Haskell.Syntax.Binds.InlinePragma. Note [Specialisation shape] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Core/Opt/WorkWrap.hs ===================================== @@ -499,7 +499,7 @@ When should the wrapper inlining be active? {-# SPECIALISE foo :: (Int,Int) -> Bool -> Int #-} {-# NOINLINE [n] foo #-} then specialisation will generate a SPEC rule active from Phase n. - See Note [Auto-specialisation and RULES] in GHC.Core.Opt.Specialise + See Note [Specialise: rule activation] in GHC.Core.Opt.Specialise This SPEC specialisation rule will compete with inlining, but we don't mind that, because if inlining succeeds, it should be better. ===================================== compiler/GHC/Core/Rules.hs ===================================== @@ -231,7 +231,7 @@ mkSpecRule dflags this_mod is_auto inl_act herald fn bndrs args rhs where rule = mkRule this_mod is_auto is_local rule_name - inl_act -- Note [Auto-specialisation and RULES] + inl_act -- Note [Specialise: rule activation] (idName fn) bndrs args rhs ===================================== testsuite/tests/simplCore/should_compile/spec-inline.stderr ===================================== @@ -17,7 +17,7 @@ Roman.foo3 Rec { -- RHS size: {terms: 40, types: 5, coercions: 0, joins: 0/0} -Roman.foo_$s$wgo [Occ=LoopBreaker] +Roman.foo_$s$wgo [InlPrag=[2], Occ=LoopBreaker] :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# [GblId, Arity=2, Str=<A><L>, Unf=OtherCon []] @@ -141,7 +141,7 @@ foo ------ Local rules for imported ids -------- -"SC:$wgo0" [2] +"SC:$wgo0" [1] forall (sc :: GHC.Internal.Prim.Int#) (sc1 :: GHC.Internal.Prim.Int#). Roman.$wgo (GHC.Internal.Maybe.Just View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a47e6e2285bc44eb3d5fbbd1fc21b979b4757253 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a47e6e2285bc44eb3d5fbbd1fc21b979b4757253 You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Simon Peyton Jones (@simonpj)