[GHC] #8326: Place heap checks common in case alternatives before the case
GHC
ghc-devs at haskell.org
Fri Oct 17 07:59:47 UTC 2014
#8326: Place heap checks common in case alternatives before the case
-------------------------------------+-------------------------------------
Reporter: jstolarek | Owner: jstolarek
Type: task | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Operating System: | Architecture: Unknown/Multiple
Unknown/Multiple | Difficulty: Unknown
Type of failure: | Blocked By:
None/Unknown | Related Tickets: #1498
Test Case: |
Blocking: 8317 |
Differential Revisions: Phab:D343 |
-------------------------------------+-------------------------------------
Comment (by simonpj):
Responding to the writeup on Phab:D343.
Before running off to make special cases for comparisons, look at the
relevant code for `cgCase`:
{{{
cgCase scrut bndr alt_type alts
= -- the general case
do { dflags <- getDynFlags
; up_hp_usg <- getVirtHp -- Upstream heap usage
; let ret_bndrs = chooseReturnBndrs bndr alt_type alts
alt_regs = map (idToReg dflags) ret_bndrs
; simple_scrut <- isSimpleScrut scrut alt_type
; let do_gc | not simple_scrut = True
| isSingleton alts = False
| up_hp_usg > 0 = False
| otherwise = True
-- cf Note [Compiling case expressions]
gc_plan = if do_gc then GcInAlts alt_regs else NoGcInAlts
; mb_cc <- maybeSaveCostCentre simple_scrut
; let sequel = AssignTo alt_regs do_gc{- Note [scrut sequel] -}
; ret_kind <- withSequel sequel (cgExpr scrut)
; restoreCurrentCostCentre mb_cc
; _ <- bindArgsToRegs ret_bndrs
; cgAlts (gc_plan,ret_kind) (NonVoid bndr) alt_type alts
}
}}}
If `do_gc` is true, we put heap checks at the start of each branch. If
`do_gc` is false, we take the max of the branches, and do the heap check
before the `case`.
I'll use a running example like this:
{{{
f = \x -> let y = blah
in case <scrut> of
0# -> <rhs1>
DEFAULT -> <rhs2>
}}}
Things that affect the `do_gc` decision:
* If the scrutinee `<scrut>` requires any non-trivial work, we MUST have
`do_gc = True`. For example if `<scrut>` was `(g x)`, then calling `g`
might result in lots of allocation, so any heap check done at the start of
`f` is irrelevant to the branches. They must do their own checks. This
is the `simple_scrut` check. It succeeds on simple finite computations
like `x +# 1` or `x` (if `x` is unboxed).
The other cases are all for the simple-srut situation:
* If there is just one alternative, then it's always good to amalgamate
* If there is heap allocation in the code before the case (`up_hp_usg >
0`), then we are going to do a heap-check upstream anyway. In that case,
don't do one in the alterantives too. (The single check might allocate
too much space, but the alterantives that use less space simply move `Hp`
back down again, which only costs one instruction.)
* Otherwise, if there no heap alloation upstream, put heap checks in each
alternative. The resoning here was that if one alternative needs heap and
the other one doesn't we don't want to pay the runtime for the heap check
in the case where the heap-free alternative is taken.
Now, what is happening in your example is that
* There is no upstream heap usage
* Both alternatives allocate
Result: you get two heap checks instead of one. But if only ''one''
branch allocated, you'd probably ''want'' to have the heap check in that
branch!
So I think the criterion should be that (assuming no upstream allocation)
* If all the branches allocate, do the heap check before the case
* Otherwise pay the price of a heap check in each branch
Or alterantively (less code size, slightly slower)
* If more than one branch allocates, do the heap check before the case
* If only one allocates, do it in the brcnch
The difficulty here is that it's hard to find out whether the branches
allocate without running the code generator on them, and that's now how
the current setup is structured. (When you run the code generator on
some code, the monad keeps track of how much allocation is done; see
`StgCmmMonad.getHeapUsage`.) It might well be possible to move things
around a bit, but it would need a little care.
But before doing that, the first thing is to decide what the criteria
should be.
Simon
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8326#comment:13>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list