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
Container 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
Guillaume Duboc
GHC
Commits
69ae10c3
Commit
69ae10c3
authored
4 years ago
by
Andreas Klebinger
Committed by
Marge Bot
4 years ago
Browse files
Options
Downloads
Patches
Plain Diff
CmmSink: Force inlining of foldRegsDefd
Helps avoid allocating the folding function. Improves perf for T3294 by about 1%.
parent
51e3bb6d
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/GHC/Cmm/Sink.hs
+45
-6
45 additions, 6 deletions
compiler/GHC/Cmm/Sink.hs
with
45 additions
and
6 deletions
compiler/GHC/Cmm/Sink.hs
+
45
−
6
View file @
69ae10c3
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
module
GHC.Cmm.Sink
(
module
GHC.Cmm.Sink
(
cmmSink
cmmSink
)
where
)
where
...
@@ -24,6 +25,8 @@ import Data.List (partition)
...
@@ -24,6 +25,8 @@ import Data.List (partition)
import
qualified
Data.Set
as
Set
import
qualified
Data.Set
as
Set
import
Data.Maybe
import
Data.Maybe
import
GHC.Exts
(
inline
)
-- Compact sets for membership tests of local variables.
-- Compact sets for membership tests of local variables.
type
LRegSet
=
IntSet
.
IntSet
type
LRegSet
=
IntSet
.
IntSet
...
@@ -403,7 +406,7 @@ dropAssignments platform should_drop state assigs
...
@@ -403,7 +406,7 @@ dropAssignments platform should_drop state assigs
-- inlining opens up opportunities for doing so.
-- inlining opens up opportunities for doing so.
tryToInline
tryToInline
::
Platform
::
forall
x
.
Platform
->
LocalRegSet
-- set of registers live after this
->
LocalRegSet
-- set of registers live after this
-- node. We cannot inline anything
-- node. We cannot inline anything
-- that is live after the node, unless
-- that is live after the node, unless
...
@@ -437,13 +440,14 @@ tryToInline platform live node assigs = go usages node emptyLRegSet assigs
...
@@ -437,13 +440,14 @@ tryToInline platform live node assigs = go usages node emptyLRegSet assigs
dont_inline
=
keep
node
-- don't inline the assignment, keep it
dont_inline
=
keep
node
-- don't inline the assignment, keep it
inline_and_keep
=
keep
inl_node
-- inline the assignment, keep it
inline_and_keep
=
keep
inl_node
-- inline the assignment, keep it
keep
::
CmmNode
O
x
->
(
CmmNode
O
x
,
Assignments
)
keep
node'
=
(
final_node
,
a
:
rest'
)
keep
node'
=
(
final_node
,
a
:
rest'
)
where
(
final_node
,
rest'
)
=
go
usages'
node'
(
insertLRegSet
l
skipped
)
rest
where
(
final_node
,
rest'
)
=
go
usages'
node'
(
insertLRegSet
l
skipped
)
rest
-- Avoid discarding of assignments to vars on the rhs.
-- See Note [Keeping assignemnts mentioned in skipped RHSs]
usages'
=
foldLocalRegsUsed
platform
(
\
m
r
->
addToUFM
m
r
2
)
usages'
=
foldLocalRegsUsed
platform
(
\
m
r
->
addToUFM
m
r
2
)
usages
rhs
usages
rhs
-- we must not inline anything that is mentioned in the RHS
-- of a binding that we have already skipped, so we set the
-- usages of the regs on the RHS to 2.
cannot_inline
=
skipped
`
regsUsedIn
`
rhs
-- Note [dependent assignments]
cannot_inline
=
skipped
`
regsUsedIn
`
rhs
-- Note [dependent assignments]
||
l
`
elemLRegSet
`
skipped
||
l
`
elemLRegSet
`
skipped
...
@@ -467,6 +471,25 @@ tryToInline platform live node assigs = go usages node emptyLRegSet assigs
...
@@ -467,6 +471,25 @@ tryToInline platform live node assigs = go usages node emptyLRegSet assigs
inl_exp
(
CmmMachOp
op
args
)
=
cmmMachOpFold
platform
op
args
inl_exp
(
CmmMachOp
op
args
)
=
cmmMachOpFold
platform
op
args
inl_exp
other
=
other
inl_exp
other
=
other
{- Note [Keeping assignemnts mentioned in skipped RHSs]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
If we have to assignments: [z = y, y = e1] and we skip
z we *must* retain the assignment y = e1. This is because
we might inline "z = y" into another node later on so we
must ensure y is still defined at this point.
If we dropped the assignment of "y = e1" then we would end up
referencing a variable which hasn't been mentioned after
inlining.
We use a hack to do this, which is setting all regs used on the
RHS to two uses. Since we only discard assignments to variables
which are used once or never this prevents discarding of the
assignment. It still allows inlining should e1 be a trivial rhs
however.
-}
{- Note [improveConditional]
{- Note [improveConditional]
...
@@ -610,18 +633,34 @@ conflicts platform (r, rhs, addr) node
...
@@ -610,18 +633,34 @@ conflicts platform (r, rhs, addr) node
-- (7) otherwise, no conflict
-- (7) otherwise, no conflict
|
otherwise
=
False
|
otherwise
=
False
{- Note [Inlining foldRegsDefd]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~
foldRegsDefd is, after optimization, *not* a small function so
it's only marked INLINEABLE, but not INLINE.
However in some specific cases we call it *very* often making it
important to avoid the overhead of allocating the folding function.
So we simply force inlining via the magic inline function.
For T3294 this improves allocation with -O by ~1%.
-}
-- Returns True if node defines any global registers that are used in the
-- Returns True if node defines any global registers that are used in the
-- Cmm expression
-- Cmm expression
globalRegistersConflict
::
Platform
->
CmmExpr
->
CmmNode
e
x
->
Bool
globalRegistersConflict
::
Platform
->
CmmExpr
->
CmmNode
e
x
->
Bool
globalRegistersConflict
platform
expr
node
=
globalRegistersConflict
platform
expr
node
=
foldRegsDefd
platform
(
\
b
r
->
b
||
regUsedIn
platform
(
CmmGlobal
r
)
expr
)
-- See Note [Inlining foldRegsDefd]
inline
foldRegsDefd
platform
(
\
b
r
->
b
||
regUsedIn
platform
(
CmmGlobal
r
)
expr
)
False
node
False
node
-- Returns True if node defines any local registers that are used in the
-- Returns True if node defines any local registers that are used in the
-- Cmm expression
-- Cmm expression
localRegistersConflict
::
Platform
->
CmmExpr
->
CmmNode
e
x
->
Bool
localRegistersConflict
::
Platform
->
CmmExpr
->
CmmNode
e
x
->
Bool
localRegistersConflict
platform
expr
node
=
localRegistersConflict
platform
expr
node
=
foldRegsDefd
platform
(
\
b
r
->
b
||
regUsedIn
platform
(
CmmLocal
r
)
expr
)
-- See Note [Inlining foldRegsDefd]
inline
foldRegsDefd
platform
(
\
b
r
->
b
||
regUsedIn
platform
(
CmmLocal
r
)
expr
)
False
node
False
node
-- Note [Sinking and calls]
-- Note [Sinking and calls]
...
...
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