Skip to content
Snippets Groups Projects
Commit db1f41ac authored by Simon Peyton Jones's avatar Simon Peyton Jones Committed by Ian Lynagh
Browse files

Remove now-unnecessary hack in CoreFVs.ruleRhsFVS

parent c4e54f9a
No related branches found
No related tags found
No related merge requests found
......@@ -278,18 +278,16 @@ exprsOrphNames es = foldr (unionNameSets . exprOrphNames) emptyNameSet es
-- | Those variables free in the right hand side of a rule
ruleRhsFreeVars :: CoreRule -> VarSet
ruleRhsFreeVars (BuiltinRule {}) = noFVs
ruleRhsFreeVars (Rule { ru_fn = fn, ru_bndrs = bndrs, ru_rhs = rhs })
= delFromUFM fvs fn -- Note [Rule free var hack]
where
fvs = addBndrs bndrs (expr_fvs rhs) isLocalVar emptyVarSet
ruleRhsFreeVars (Rule { ru_fn = _, ru_bndrs = bndrs, ru_rhs = rhs })
= addBndrs bndrs (expr_fvs rhs) isLocalVar emptyVarSet
-- See Note [Rule free var hack]
-- | Those variables free in the both the left right hand sides of a rule
ruleFreeVars :: CoreRule -> VarSet
ruleFreeVars (BuiltinRule {}) = noFVs
ruleFreeVars (Rule { ru_fn = fn, ru_bndrs = bndrs, ru_rhs = rhs, ru_args = args })
= delFromUFM fvs fn -- Note [Rule free var hack]
where
fvs = addBndrs bndrs (exprs_fvs (rhs:args)) isLocalVar emptyVarSet
ruleFreeVars (Rule { ru_fn = _, ru_bndrs = bndrs, ru_rhs = rhs, ru_args = args })
= addBndrs bndrs (exprs_fvs (rhs:args)) isLocalVar emptyVarSet
-- See Note [Rule free var hack]
idRuleRhsVars :: (Activation -> Bool) -> Id -> VarSet
-- Just the variables free on the *rhs* of a rule
......@@ -316,16 +314,16 @@ ruleLhsFreeIds (Rule { ru_bndrs = bndrs, ru_args = args })
= addBndrs bndrs (exprs_fvs args) isLocalId emptyVarSet
\end{code}
Note [Rule free var hack]
Note [Rule free var hack] (Not a hack any more)
~~~~~~~~~~~~~~~~~~~~~~~~~
Don't include the Id in its own rhs free-var set.
Otherwise the occurrence analyser makes bindings recursive
that shoudn't be. E.g.
We used not to include the Id in its own rhs free-var set.
Otherwise the occurrence analyser makes bindings recursive:
f x y = x+y
RULE: f (f x y) z ==> f x (f y z)
Also since rule_fn is a Name, not a Var, we have to use the grungy delUFM.
However, the occurrence analyser distinguishes "non-rule loop breakers"
from "rule-only loop breakers" (see BasicTypes.OccInfo). So it will
put this 'f' in a Rec block, but will mark the binding as a non-rule loop
breaker, which is perfectly inlinable.
\begin{code}
-- |Free variables of a vectorisation declaration
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment