[GHC] #10626: Missed opportunity for SpecConstr

#10626: Missed opportunity for SpecConstr
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple | Blocked By:
Test Case: | Related Tickets:
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Look at `perf/should_run/T4830`. After `SpecConstr` and optimisation we
finally get
{{{
Rec {
Main.foo_$s$wfoo1 [Occ=LoopBreaker]
:: Int# -> Double -> Double -> Double#
[GblId, Arity=3, Caf=NoCafRefs, Str=DmdType

#10626: Missed opportunity for SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: nomeata, bgamari (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10626#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10626: Missed opportunity for SpecConstr
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by dsc):
* cc: dsc (added)
Comment:
(Not sure if my problem is different enough from this one to warrant a
separate ticket.)
I also have a problem where SpecConstr apparently gets stuck and doesn't
converge to a fixed point: If I translate the Core back into Haskell and
compile that again, I get great code with all state constructors
eliminated.
The code in question is TH-generated stream fusion code. I suppose that
only the dump-splices result is relevant here, so I made it compilable and
attached that (Input.hs).
The Core (also attached) contains lots of seemingly obvious SpecConstr
opportunities:
{{{
test_$s$wgfold_loop =
\ (sc
:: FlattenState
Int (ParamAndState Int (ConcatState YieldState ()
YieldState)))
(sc1 :: Int)
(sc2 :: Int#) ->
case sc1 of _ [Occ=Dead] { I# y ->
case sc of _ [Occ=Dead] {
[...]
Flatten_RunningInner so_agux si_aguy ->
[...]
test_$s$wgfold_loop
(Flatten_RunningInner
so_agux (ParamAndState a_aguz (CS_First
AfterYielding)))
a_aguz
(+# (+# sc2 y) 42#);
[...]
test_$s$wgfold_loop
(Flatten_RunningInner
so_agux (ParamAndState a_aguz (CS_Second ()
AfterYielding)))
a_aguz
(+# (+# sc2 y) 42#)
[...]
}}}
This is the second-round Core after retranslating the first Core into
Haskell (hopefully without changing semantics) and compiling again:
{{{
test_$s$wgfold_loop =
\ (sc :: Int#)
(sc1 :: Int#)
(sc2 :: Int#)
_ [Occ=Dead]
_ [Occ=Dead] ->
case tagToEnum# (># sc2 1000000#) of _ [Occ=Dead] {
False ->
test_$s$wgfold_loop
(+# (+# (+# (+# sc sc1) 42#) sc2) 42#) sc2 (+# sc2 1#) sc2 ();
True -> +# sc sc1
}
}}}
I noticed that in the first core, GHC thinks that `test_$s$wgfold_loop` is
lazy (`Str=DmdType

#10626: Missed opportunity for SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dsc): * Attachment "Input.hs" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10626 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10626: Missed opportunity for SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dsc): * Attachment "Input.dump-simpl" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10626 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10626: Missed opportunity for SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dsc): * Attachment "ReHaskelledCore.hs" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10626 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10626: Missed opportunity for SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dsc): * Attachment "ReHaskelledCore.dump-simpl" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10626 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10626: Missed opportunity for SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dsc): Just tried with GHC 8.0.2 and 7.10.3; similar problem. By the way, the original source looks like this: {{{ intersperseTest = $$(maybeSimplify $ S.enumFromToNum [|| 1 ||] [|| 1000000 :: Int ||] & S.concatMap (\a -> yield a S.++ yield a) & S.intersperse [|| 42 ||] & S.concatMap yield & S.sum_ & runIdentityE_static ) }}} (WIP library/experiment, trying for something like the [https://hackage.haskell.org/package/streaming streaming] package with robust fusion using typed TH :)) If I change the first `concatMap` to just `concatMap yield` or remove either the `intersperse` or the second `concatMap`, the problem is not present. I've had similar instances where the problem disappears after removing a random part of the pipeline (with that part fusing correctly if I remove a different part). Feels like I'm hitting some size limit rather than a fundamental problem (?) But as mentioned above, I already tried setting various GHC flags to large numbers. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10626#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10626: Missed opportunity for SpecConstr
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by simonpj):
I had a look. There are two things.
'''Problem 1'''. With the grotesque (GHC's fault not yours) `SPEC`
argument to force specialisation, GHC does not want to generate an
infinite number of specialisations; e.g.
{{{
f (a:b) = f (a::b)
...
}}}
This is limited by the (probably un-documented) flag `-fspec-constr-
recurisive=N` flag. Its default value is far too low: 3. Set it to 20.
The relevant bit in `SpecConstr` is
{{{
is_too_recursive :: ScEnv -> (CallPat, ValueEnv) -> Bool
-- Count the number of recursive constructors in a call pattern,
-- filter out if there are more than the maximum.
-- This is only necessary if ForceSpecConstr is in effect:
-- otherwise specConstrCount will cause specialisation to terminate.
-- See Note [Limit recursive specialisation]
-- TODO: make me more accurate
}}}
And indeed it simply counts data constructors, not even recursive ones.
That will seriously limit specialisation in precisely the case where you
wanted a lot!
At least we could count nesting depth rather than just counting
constructors in total.
'''Problem 2'''. Your code has
{{{
(InterspersesState_Running (snd
stored_fs_aguH))
}}}
That use of `snd` is fatal, because it's not inlined before `SpecConstr`
(since it is applied to an uninformative variable). So `SpecConstr`
doesn't "see" the case inside `snd` and that means it generate too few
specialisations. If you instead write
{{{
-- InterspersesState_YieldedInterspersee
stored_fs_aguH
InterspersesState_YieldedInterspersee (fs1,fs2)
-> gfold_loop
sPEC_aguh
acc_agui
(Flatten_RunningInner
-- (InterspersesState_Running (snd
stored_fs_aguH))
(InterspersesState_Running fs2)
-- (ParamAndState (fst stored_fs_aguH)
BeforeYielding))
(ParamAndState fs1 BeforeYielding))
}}}
where the old line is commented out, and replaced by the line below, then
good things happen, and a single run gives
{{{
Rec {
-- RHS size: {terms: 33, types: 6, coercions: 0, joins: 0/0}
Input.test_$s$wgfold_loop [Occ=LoopBreaker]
:: Int# -> Int# -> Int# -> Int# -> Int#
[GblId, Arity=4, Caf=NoCafRefs, Str=]
Input.test_$s$wgfold_loop =
\ (sc_s5hq :: Int#)
(sc1_s5hr :: Int#)
(sc2_s5hs :: Int#)
(sc3_s5hp :: Int#) ->
case tagToEnum# @ Bool (># sc_s5hq 1000000#) of {
False ->
Input.test_$s$wgfold_loop
(+# sc_s5hq 1#)
sc_s5hq
sc_s5hq
(+# (+# (+# (+# sc3_s5hp sc2_s5hs) 42#) sc1_s5hr) 42#);
True -> +# (+# (+# sc3_s5hp sc2_s5hs) 42#) sc1_s5hr
}
end Rec }
}}}
--
Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10626#comment:5
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

#10626: Missed opportunity for SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dsc): Thank you very much! Avoiding the `snd` indeed fixes it in this case, and I'll also keep problem 1 in mind. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10626#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10626: Missed opportunity for SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => SpecConstr -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10626#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC