Skip to content
GitLab
Explore
Sign in
Register
Primary navigation
Search or go to…
Project
GHC
Manage
Activity
Members
Labels
Plan
Issues
Issue boards
Milestones
Wiki
Requirements
Code
Merge requests
Repository
Branches
Commits
Tags
Repository graph
Compare revisions
Snippets
Locked files
Build
Pipelines
Jobs
Pipeline schedules
Test cases
Artifacts
Deploy
Releases
Package Registry
Model registry
Operate
Environments
Terraform modules
Monitor
Incidents
Analyze
Value stream analytics
Contributor analytics
CI/CD analytics
Repository analytics
Code review analytics
Issue analytics
Insights
Model experiments
Help
Help
Support
GitLab documentation
Compare GitLab plans
Community forum
Contribute to GitLab
Provide feedback
Terms and privacy
Keyboard shortcuts
?
Snippets
Groups
Projects
Show more breadcrumbs
Alexander Kaznacheev
GHC
Commits
07185e47
Commit
07185e47
authored
13 years ago
by
Simon Peyton Jones
Committed by
Ian Lynagh
13 years ago
Browse files
Options
Downloads
Patches
Plain Diff
Further simplification to OccurAnal, concerning "weak loop breakers"
Fixes Trac #5359.
parent
04236444
No related branches found
No related tags found
No related merge requests found
Changes
1
Hide whitespace changes
Inline
Side-by-side
Showing
1 changed file
compiler/simplCore/OccurAnal.lhs
+50
-34
50 additions, 34 deletions
compiler/simplCore/OccurAnal.lhs
with
50 additions
and
34 deletions
compiler/simplCore/OccurAnal.lhs
+
50
−
34
View file @
07185e47
...
@@ -290,8 +290,9 @@ And indeed both can be inlined safely.
...
@@ -290,8 +290,9 @@ And indeed both can be inlined safely.
Note again that the edges of the graph we use for computing loop breakers
Note again that the edges of the graph we use for computing loop breakers
are not the same as the edges we use for computing the Rec blocks.
are not the same as the edges we use for computing the Rec blocks.
That's why we compute
That's why we compute
rec_edges for the Rec block analysis
loop_breaker_edges for the loop breaker analysis
- rec_edges for the Rec block analysis
- loop_breaker_edges for the loop breaker analysis
* Note [Finding rule RHS free vars]
* Note [Finding rule RHS free vars]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
...
@@ -307,12 +308,8 @@ That's why we compute
...
@@ -307,12 +308,8 @@ That's why we compute
the RULE is only active *before* phase 1. So there's no problem.
the RULE is only active *before* phase 1. So there's no problem.
To make this work, we look for the RHS free vars only for
To make this work, we look for the RHS free vars only for
*active* rules. More precisely, in the rules that are active now
*active* rules. That's the reason for the occ_rule_act field
or might *become* active in a later phase. We need the latter
of the OccEnv.
because (curently) we don't
That's the reason for the is_active argument
to idRhsRuleVars, and the occ_rule_act field of the OccEnv.
* Note [Weak loop breakers]
* Note [Weak loop breakers]
~~~~~~~~~~~~~~~~~~~~~~~~~
~~~~~~~~~~~~~~~~~~~~~~~~~
...
@@ -341,16 +338,20 @@ That's why we compute
...
@@ -341,16 +338,20 @@ That's why we compute
; f = f_rhs
; f = f_rhs
RULE f [] = g }
RULE f [] = g }
Here the RULE is "below" g, but we *still* can't postInlineUnconditionally
Here the RULE is "below" g, but we *still* can't postInlineUnconditionally
because the RULE for f is active throughout. So the RHS of h
g,
because the RULE for f is active throughout. So the RHS of h
might rewrite to h = ...g...
might rewrite to h = ...g...
So g must remain in scope in the output program!
So g must remain in scope in the output program!
We "solve" this by:
We "solve" this by:
Make g a "weak" loop breaker (OccInfo = IAmLoopBreaker True)
Make g a "weak" loop breaker (OccInfo = IAmLoopBreaker True)
iff g appears in the LHS or RHS of any rule for the Rec
iff g is a "missing free variable" of the Rec group
whether or not the rule is active
A "missing free variable" x is one that is mentioned in an RHS or
INLINE or RULE of a binding in the Rec group, but where the
dependency on x may not show up in the loop_breaker_edges (see
note [Choosing loop breakers} above).
A normal "strong" loop breaker has IAmLoopBreaker False. So
A normal "strong" loop breaker has IAmLoopBreaker False. So
Inline postInlineUnconditionally
Inline postInlineUnconditionally
...
@@ -539,23 +540,29 @@ data Details
...
@@ -539,23 +540,29 @@ data Details
-- but excluding any RULES
-- but excluding any RULES
-- This is the IdSet that may be used if the Id is inlined
-- This is the IdSet that may be used if the Id is inlined
, nd_rule_fvs :: IdSet -- Free variables of LHS or RHS of all RULES
, nd_weak :: IdSet -- Binders of this Rec that are mentioned in nd_uds
-- whether active or not
-- but are *not* in nd_inl. These are the ones whose
-- dependencies might not be respected by loop_breaker_edges
-- See Note [Weak loop breakers]
, nd_active_rule_fvs :: IdSet -- Free variables of the RHS of active RULES
, nd_active_rule_fvs :: IdSet -- Free variables of the RHS of active RULES
-- In the last two fields, we haev already expanded occurrences
-- of imported Ids for which we have local RULES, to their local-id sets
}
}
instance Outputable Details where
ppr (ND { nd_bndr = bndr, nd_uds = uds })
= ptext (sLit "ND") <> braces
(sep [ ptext (sLit "bndr =") <+> ppr bndr
, ptext (sLit "uds =") <+> ppr uds ])
makeNode :: OccEnv -> VarSet -> (Var, CoreExpr) -> Node Details
makeNode :: OccEnv -> VarSet -> (Var, CoreExpr) -> Node Details
makeNode env bndr_set (bndr, rhs)
makeNode env bndr_set (bndr, rhs)
= (details, varUnique bndr, keysUFM
(udFreeVars bndr_set rhs_usage3)
)
= (details, varUnique bndr, keysUFM
node_fvs
)
where
where
details = ND { nd_bndr = bndr
details = ND { nd_bndr = bndr
, nd_rhs = rhs'
, nd_rhs = rhs'
, nd_uds = rhs_usage3
, nd_uds = rhs_usage3
, nd_weak = node_fvs `minusVarSet` inl_fvs
, nd_inl = inl_fvs
, nd_inl = inl_fvs
, nd_rule_fvs = all_rule_fvs
, nd_active_rule_fvs = active_rule_fvs }
, nd_active_rule_fvs = active_rule_fvs }
-- Constructing the edges for the main Rec computation
-- Constructing the edges for the main Rec computation
...
@@ -566,6 +573,7 @@ makeNode env bndr_set (bndr, rhs)
...
@@ -566,6 +573,7 @@ makeNode env bndr_set (bndr, rhs)
rhs_usage3 = case mb_unf_fvs of
rhs_usage3 = case mb_unf_fvs of
Just unf_fvs -> addIdOccs rhs_usage2 unf_fvs
Just unf_fvs -> addIdOccs rhs_usage2 unf_fvs
Nothing -> rhs_usage2
Nothing -> rhs_usage2
node_fvs = udFreeVars bndr_set rhs_usage3
-- Finding the free variables of the rules
-- Finding the free variables of the rules
is_active = occ_rule_act env :: Activation -> Bool
is_active = occ_rule_act env :: Activation -> Bool
...
@@ -619,7 +627,11 @@ occAnalRec (CyclicSCC nodes) (body_uds, binds)
...
@@ -619,7 +627,11 @@ occAnalRec (CyclicSCC nodes) (body_uds, binds)
= (body_uds, binds) -- Dead code
= (body_uds, binds) -- Dead code
| otherwise -- At this point we always build a single Rec
| otherwise -- At this point we always build a single Rec
= (final_uds, Rec pairs : binds)
= -- pprTrace "occAnalRec" (vcat
-- [ text "tagged nodes" <+> ppr tagged_nodes
-- , text "non_boring" <+> ppr (any non_boring bndrs)
-- , text "lb edges" <+> ppr loop_breaker_edges])
(final_uds, Rec pairs : binds)
where
where
bndrs = [b | (ND { nd_bndr = b }, _, _) <- nodes]
bndrs = [b | (ND { nd_bndr = b }, _, _) <- nodes]
...
@@ -639,11 +651,14 @@ occAnalRec (CyclicSCC nodes) (body_uds, binds)
...
@@ -639,11 +651,14 @@ occAnalRec (CyclicSCC nodes) (body_uds, binds)
---------------------------
---------------------------
-- Now reconstruct the cycle
-- Now reconstruct the cycle
pairs :: [(Id,CoreExpr)]
pairs :: [(Id,CoreExpr)]
pairs | any non_boring bndrs = loopBreakNodes 0 bndr_set rule_fvs loop_breaker_edges []
pairs | isEmptyVarSet weak_fvs = loopBreakNodes 0 bndr_set weak_fvs loop_breaker_edges []
| otherwise = reOrderNodes 0 bndr_set rule_fvs tagged_nodes []
| otherwise = reOrderNodes 0 bndr_set weak_fvs tagged_nodes []
non_boring bndr = isId bndr &&
-- If weak_fvs is empty, the loop_breaker_edges will include all
(isStableUnfolding (realIdUnfolding bndr) || idHasRules bndr)
-- the edges in tagged_nodes, so there isn't any point in doing
-- If all are boring, the loop_breaker_edges will be a single Cyclic SCC
-- a fresh SCC computation that will yield a single CyclicSCC result.
weak_fvs :: VarSet
weak_fvs = foldr (unionVarSet . nd_weak . fstOf3) emptyVarSet nodes
-- See Note [Choosing loop breakers] for loop_breaker_edges
-- See Note [Choosing loop breakers] for loop_breaker_edges
loop_breaker_edges = map mk_node tagged_nodes
loop_breaker_edges = map mk_node tagged_nodes
...
@@ -651,9 +666,6 @@ occAnalRec (CyclicSCC nodes) (body_uds, binds)
...
@@ -651,9 +666,6 @@ occAnalRec (CyclicSCC nodes) (body_uds, binds)
= (details, k, keysUFM (extendFvs_ rule_fv_env inl_fvs))
= (details, k, keysUFM (extendFvs_ rule_fv_env inl_fvs))
------------------------------------
------------------------------------
rule_fvs :: VarSet
rule_fvs = foldr (unionVarSet . nd_rule_fvs . fstOf3) emptyVarSet nodes
rule_fv_env :: IdEnv IdSet
rule_fv_env :: IdEnv IdSet
-- Maps a variable f to the variables from this group
-- Maps a variable f to the variables from this group
-- mentioned in RHS of active rules for f
-- mentioned in RHS of active rules for f
...
@@ -699,12 +711,14 @@ udFreeVars :: VarSet -> UsageDetails -> VarSet
...
@@ -699,12 +711,14 @@ udFreeVars :: VarSet -> UsageDetails -> VarSet
udFreeVars bndrs uds = intersectUFM_C (\b _ -> b) bndrs uds
udFreeVars bndrs uds = intersectUFM_C (\b _ -> b) bndrs uds
loopBreakNodes :: Int
loopBreakNodes :: Int
-> VarSet -> VarSet -- All binders, and binders used in RULES
-> VarSet -- All binders
-> VarSet -- Binders whose dependencies may be "missing"
-- See Note [Weak loop breakers]
-> [Node Details]
-> [Node Details]
-> [Binding] -- Append these to the end
-> [Binding] -- Append these to the end
-> [Binding]
-> [Binding]
-- Return the bindings sorted into a plausible order, and marked with loop breakers.
-- Return the bindings sorted into a plausible order, and marked with loop breakers.
loopBreakNodes depth bndr_set
used_in_rule
s nodes binds
loopBreakNodes depth bndr_set
weak_fv
s nodes binds
= go (stronglyConnCompFromEdgedVerticesR nodes) binds
= go (stronglyConnCompFromEdgedVerticesR nodes) binds
where
where
go [] binds = binds
go [] binds = binds
...
@@ -712,16 +726,18 @@ loopBreakNodes depth bndr_set used_in_rules nodes binds
...
@@ -712,16 +726,18 @@ loopBreakNodes depth bndr_set used_in_rules nodes binds
loop_break_scc scc binds
loop_break_scc scc binds
= case scc of
= case scc of
AcyclicSCC node -> mk_non_loop_breaker
used_in_rule
s node : binds
AcyclicSCC node -> mk_non_loop_breaker
weak_fv
s node : binds
CyclicSCC [node] -> mk_loop_breaker node : binds
CyclicSCC [node] -> mk_loop_breaker node : binds
CyclicSCC nodes -> reOrderNodes depth bndr_set
used_in_rule
s nodes binds
CyclicSCC nodes -> reOrderNodes depth bndr_set
weak_fv
s nodes binds
reOrderNodes :: Int -> VarSet -> VarSet -> [Node Details] -> [Binding] -> [Binding]
reOrderNodes :: Int -> VarSet -> VarSet -> [Node Details] -> [Binding] -> [Binding]
-- Choose a loop breaker, mark it no-inline,
-- Choose a loop breaker, mark it no-inline,
-- do SCC analysis on the rest, and recursively sort them out
-- do SCC analysis on the rest, and recursively sort them out
reOrderNodes _ _ _ [] _ = panic "reOrderNodes"
reOrderNodes _ _ _ [] _ = panic "reOrderNodes"
reOrderNodes depth bndr_set used_in_rules (node : nodes) binds
reOrderNodes depth bndr_set weak_fvs (node : nodes) binds
= loopBreakNodes new_depth bndr_set used_in_rules unchosen $
= -- pprTrace "reOrderNodes" (text "unchosen" <+> ppr unchosen $$
-- text "chosen" <+> ppr chosen_nodes) $
loopBreakNodes new_depth bndr_set weak_fvs unchosen $
(map mk_loop_breaker chosen_nodes ++ binds)
(map mk_loop_breaker chosen_nodes ++ binds)
where
where
(chosen_nodes, unchosen) = choose_loop_breaker (score node) [node] [] nodes
(chosen_nodes, unchosen) = choose_loop_breaker (score node) [node] [] nodes
...
...
This diff is collapsed.
Click to expand it.
Preview
0%
Loading
Try again
or
attach a new file
.
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Save comment
Cancel
Please
register
or
sign in
to comment