[GHC] #10626: Missed opportunity for SpecConstr
GHC
ghc-devs at haskell.org
Wed Feb 8 11:26:43 UTC 2017
#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=<S,U><S,U><S,U><S,U>]
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
More information about the ghc-tickets
mailing list