[GHC] #11731: Demand analysis: Thunk wrongly determined single-entry
GHC
ghc-devs at haskell.org
Mon Mar 21 09:16:51 UTC 2016
#11731: Demand analysis: Thunk wrongly determined single-entry
-------------------------------------+-------------------------------------
Reporter: nomeata | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by nomeata):
It seems that on its own, the demand analysis is correct. Here is the
relevant bit from `transPort`, as the demand analysis sees it:
{{{
transPort =
\ (p_ayV
[Dmd=<S(SSLLLLL),U(1*U(U(U),U(U),U(U)),1*U(U(U),U(U),U(U)),U(U),U(U),U,U(U),1*U(U))>]
:: Particle)
(prob_ayW [Dmd=<S(LLLS(S)),1*U(U(U),A,U(U),U(U))>]
:: Probability) ->
let {
seed_s33f [Dmd=<L,U(U)>] :: Random
[LclId,
Str=DmdType {ayV-><S(LLLLLLS),A>},
Unf=Unf{Src=<vanilla>, TopLvl=False, Value=False, ConLike=False,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 0}]
seed_s33f =
case p_ayV
of _ [Occ=Dead, Dmd=<L,A>]
{ Part pos_X21Q [Dmd=<L,A>] dir_X21S [Dmd=<L,A>] w_X21U
[Dmd=<L,A>]
e_X21W [Dmd=<L,A>] eIndx_X21Y [Dmd=<L,A>] cell_X220
[Dmd=<L,A>]
seed_X22n [Dmd=<S,1*U(U)>] ->
seed_X22n
} } in
case Utils.$wgenRand seed_s33f
...
}}}
Note that the demand on `seed` is *not* one-shot (because there are two
calls to `wgenRand seed_s33f` in the body below, but the demand on the
corresponding member of `Particle` is. As long as `seed_s33f` is shared,
this is fine.
But after the next simplifier run, which includes worker-wrappering the
`Particle` argument, CSE’ing the various calls to `$wgenRand` as well as
subsequent simplifications, we get:
{{{
[LclId,
Arity=14,
Str=DmdType
<L,U(U)><L,U(U)><L,U(U)><L,U(U)><L,U(U)><L,U(U)><L,U(U)><L,U(U)><L,U><L,U(U)><L,1*U(U)><L,U(U)><L,U(U)><S,U>,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=NEVER}]
$wtransPort_s3nF =
\ (ww_s3nb :: Coord)
(ww_s3nc :: Coord)
(ww_s3nd :: Coord)
(ww_s3ni :: Coord)
(ww_s3nj :: Coord)
(ww_s3nk :: Coord)
(ww_s3nm :: Weight)
(ww_s3nn :: Energy)
(ww_s3no :: Indx)
(ww_s3np :: Int)
(ww_s3nq :: Random)
(ww_s3nu :: Prob)
(ww_s3nw :: Prob)
(ww_s3nA :: GHC.Prim.Double#) ->
case Utils.$wgenRand ww_s3nq
of _ [Occ=Dead, Dmd=<L,A>]
{ (# ww1_a2WR [Dmd=<S(S),1*U(U)>], ww2_a2WS [Dmd=<L,1*U(U)>] #) ->
}}}
and behold: The sharing-ensuring let is gone, the field member `ww_s3nq`
is passed directly to `$wgenRand` and now the strictness signature is a
lie!
Tracing the simplifier is not easy, but I expect the sequence of actions
to be roughly this: After WW we have
{{{
\ (ww_s3nb [Dmd=<L,U(U)>] :: Coord)
(ww_s3nc [Dmd=<L,U(U)>] :: Coord)
(ww_s3nd [Dmd=<L,U(U)>] :: Coord)
(ww_s3ni [Dmd=<L,U(U)>] :: Coord)
(ww_s3nj [Dmd=<L,U(U)>] :: Coord)
(ww_s3nk [Dmd=<L,U(U)>] :: Coord)
(ww_s3nm [Dmd=<L,U(U)>] :: Weight)
(ww_s3nn [Dmd=<L,U(U)>] :: Energy)
(ww_s3no :: Indx)
(ww_s3np [Dmd=<L,U(U)>] :: Int)
(ww_s3nq [Dmd=<L,1*U(U)>] :: Random)
(ww_s3nu [Dmd=<L,U(U)>] :: Prob)
(ww_s3nw [Dmd=<L,U(U)>] :: Prob)
(ww_s3nA [Dmd=<S,U>] :: GHC.Prim.Double#) ->
...
let {
w_s3n4
[Dmd=<S(SSLLLLL),U(1*U(U(U),U(U),U(U)),1*U(U(U),U(U),U(U)),U(U),U(U),U,U(U),1*U(U))>]
:: Particle
[LclId, Str=DmdType]
w_s3n4 =
GamtebType.Part
ww_s3n8 ww_s3nf ww_s3nm ww_s3nn ww_s3no ww_s3np ww_s3nq } in
...
case (\ (p_ayV
[Dmd=<S(SSLLLLL),U(1*U(U(U),U(U),U(U)),1*U(U(U),U(U),U(U)),U(U),U(U),U,U(U),1*U(U))>]
:: Particle)
(prob_ayW [Dmd=<S(LLLS(S)),1*U(U(U),A,U(U),U(U))>]
:: Probability) ->
let {
seed_s33f [Dmd=<L,U(U)>] :: Random
[LclId,
Str=DmdType,
Unf=Unf{Src=<vanilla>, TopLvl=False, Value=False,
ConLike=False,
WorkFree=True, Expandable=True, Guidance=IF_ARGS []
10 0}]
seed_s33f =
case p_ayV
of _ [Occ=Dead, Dmd=<L,A>]
{ Part pos_X21Q [Dmd=<L,A>] dir_X21S [Dmd=<L,A>] w_X21U
[Dmd=<L,A>]
e_X21W [Dmd=<L,A>] eIndx_X21Y [Dmd=<L,A>] cell_X220
[Dmd=<L,A>]
seed_X22n [Dmd=<S,1*U(U)>] ->
seed_X22n
} } in
case Utils.$wgenRand seed_s33f
...
w_s3n4 w_s3n5
}}}
and then (beta-reduction)
{{{
let {
seed_s33f [Dmd=<L,U(U)>] :: Random
[LclId,
Str=DmdType,
Unf=Unf{Src=<vanilla>, TopLvl=False, Value=False,
ConLike=False,
WorkFree=True, Expandable=True, Guidance=IF_ARGS []
10 0}]
seed_s33f =
case w_s3n4 -- ← here
of _ [Occ=Dead, Dmd=<L,A>]
{ Part pos_X21Q [Dmd=<L,A>] dir_X21S [Dmd=<L,A>] w_X21U
[Dmd=<L,A>]
e_X21W [Dmd=<L,A>] eIndx_X21Y [Dmd=<L,A>] cell_X220
[Dmd=<L,A>]
seed_X22n [Dmd=<S,1*U(U)>] ->
seed_X22n
} } in
case Utils.$wgenRand seed_s33f
}}}
and then (inlining of constructor application into interesting context,
and case of known constructor)
{{{
let {
seed_s33f [Dmd=<L,U(U)>] :: Random
seed_s33f = ww_s3nq
case Utils.$wgenRand seed_s33f
}}}
and then (inline trivial let)
{{{
case Utils.$wgenRand seed_s3nq
}}}
and there we have the salad (German idiom).
My gut feeling is that in order to fix this problem, either all trivial
lets must be preserved, or any simplification that turns a non-trivial let
into a trivial let needs to somehow mark this let as “need to be preserved
until STG”.
This is very much related to the trap that I fell into with Call Arity in
#11064. Seems to be quite a nasty trap.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11731#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list