
#11770: Demand analysis: Wrong one-shot annotation due to fixed-point iteration
-------------------------------------+-------------------------------------
Reporter: nomeata | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
After quite a while of staring at the core of nofib’s `fft2` benchmark,
where my dynamic entry counting code (#10613), I found the problem. Here
is a small example:
{{{
foo :: Int -> Int -> Int
foo 10 c = 0
foo n c =
let bar :: Int -> Int
bar n = n + c
{-# NOINLINE bar #-}
in bar n + foo (bar (n+1)) c
}}}
Clearly, `bar` is not single-entry. But the demand analyzer believes it
is:
{{{
Rec {
-- RHS size: {terms: 32, types: 12, coercions: 0}
foo [Occ=LoopBreaker] :: Int -> Int -> Int
[LclIdX,
Arity=2,
Str=] :: Int) (c [Dmd=] ->
case ds of ds {
__DEFAULT ->
let {
bar [InlPrag=NOINLINE, Dmd=m {axl->},
Unf=Unf{Src=<vanilla>, TopLvl=False, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [0] 30
0}]
bar =
\ (n [Dmd=, OS=OneShot] :: Int) ->
$fNumInt_$c+ n c } in
case bar wild of _ [Occ=Dead, Dmd=] ->
case foo (bar (I# (+# ds 1#))) c
of _ [Occ=Dead, Dmd=] ->
I# (+# x y)
}
};
10# -> lvl
}
}
end Rec }
}}}
The reason is that during the first fixed-point iteration for `foo`, `foo`
itself is assumed to not put any demand on its arguments. Under this
assumption, it is correct to find that `bar` is called at most once. This
is then noted in the lambda binder. The second iteration corrects the
demand, but not the one-shot annotation, because that is only added by the
demand analyzer, never dropped:
{{{#!hs
setOneShotness :: Count -> Id -> Id
setOneShotness One bndr = setOneShotLambda bndr
setOneShotness Many bndr = bndr
}}}
This can be fixed by changing that code (from `DmdAnal.hs`) to
{{{#!hs
setOneShotness :: Count -> Id -> Id
setOneShotness One bndr = setOneShotLambda bndr
setOneShotness Many bndr = clearOneShotLambda bndr
}}}
But this would have other consequences, e.g. erasing any possible manual
one-shot annotations using `oneShot`.
Or maybe `setOneShotness` should not be set by the demand analyzer during
its work, but once at the end, or maybe even the next simplifier pass
should take care of that.
--
Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11770
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler