[GHC] #10260: last uses too much space with optimizations disabled
GHC
ghc-devs at haskell.org
Thu Apr 16 10:59:14 UTC 2015
#10260: last uses too much space with optimizations disabled
-------------------------------------+-------------------------------------
Reporter: rwbarton | Owner: nomeata
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Core Libraries | 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 Revisions: Phab:D844
-------------------------------------+-------------------------------------
Comment (by nomeata):
I had a closer look, and the problem is the following:
When we added the implementation
{{{
last = foldl (\_ x -> x) (error "..."))
}}}
to `GHC.List` in #9339, we assumed (and I thought we checked, but maybe
that not true) that GHC would optimize the core will look something like
this:
{{{
last :: forall a_ask. [a_ask] -> a_ask
[GblId,
Arity=1,
Str=DmdType,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 60}
Tmpl=\ (@ a_aTE) -> foldl @ a_aTE @ a_aTE (GHC.List.last2 @
a_aTE) (GHC.List.last1 @ a_aTE)]
last = .. efficient implementation derived from foldl ... ..
}}}
This way, when using `last` in code compiled without `-O`, the efficient
variant would be called, while with `-O` the unfolding would be used and
optimized on the spot, possibly fusing, and producing good code if Call
Arity kicks in.
Unfortunately, this is what we see:
{{{
last :: forall a_ask. [a_ask] -> a_ask
[GblId,
Arity=1,
Str=DmdType,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 60}]
last =
\ (@ a_aTE) ->
foldl
@ a_aTE @ a_aTE (GHC.List.last2 @ a_aTE) (GHC.List.last1 @ a_aTE)
}}}
Now the question is: Why is the code not optimized in `GHC.List`? My guess
is that we should have written
{{{
last xs = foldl (\_ x -> x) (error "...")) xs
}}}
And indeed, this way, we get:
{{{
Rec {
GHC.List.last2 [Occ=LoopBreaker]
:: forall a_aTF. [a_aTF] -> a_aTF -> a_aTF
[GblId, Arity=2, Caf=NoCafRefs, Str=DmdType <S,1*U><L,1*U>]
GHC.List.last2 =
\ (@ a_aTF) (ds_a1Es :: [a_aTF]) (eta_B1 :: a_aTF) ->
case ds_a1Es of _ [Occ=Dead] {
[] -> eta_B1;
: y_a1Ex ys_a1Ey -> GHC.List.last2 @ a_aTF ys_a1Ey y_a1Ex
}
end Rec }
last :: forall a_ask. [a_ask] -> a_ask
[GblId,
Arity=1,
Str=DmdType <S,1*U>,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [0] 30 0}]
last =
\ (@ a_aTF) (xs_ast :: [a_aTF]) ->
GHC.List.last2 @ a_aTF xs_ast (GHC.List.last1 @ a_aTF)
}}}
which his nice, but now we lost the original definition.
Next try, also adding `{-# INLINEABLE last #-}`, which yields.
{{{
Rec {
poly_go_r2F3 :: forall a_aTF. [a_aTF] -> a_aTF -> a_aTF
[GblId, Arity=2, Caf=NoCafRefs, Str=DmdType <S,1*U><L,1*U>]
poly_go_r2F3 =
\ (@ a_aTF) (ds_a1Es :: [a_aTF]) (eta_B1 :: a_aTF) ->
case ds_a1Es of _ [Occ=Dead] {
[] -> eta_B1;
: y_a1Ex ys_a1Ey -> poly_go_r2F3 @ a_aTF ys_a1Ey y_a1Ex
}
end Rec }
last [InlPrag=INLINABLE[ALWAYS]] :: forall a_ask. [a_ask] -> a_ask
[GblId,
Arity=1,
Str=DmdType <S,1*U>,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [0] 160 0
Tmpl= \ (@ a_aTF) (xs_ast [Occ=Once] :: [a_aTF]) ->
foldr
@ a_aTF
@ (a_aTF -> a_aTF)
(\ (ds_d1DA [Occ=Once] :: a_aTF)
(ds1_d1DB [Occ=Once!, OS=OneShot] :: a_aTF -> a_aTF)
_ [Occ=Dead, OS=OneShot] ->
ds1_d1DB ds_d1DA)
(id @ a_aTF)
xs_ast
(errorEmptyList
@ a_aTF
(build
@ Char (\ (@ b_a1Fd) -> unpackFoldrCString# @
b_a1Fd "last"#)))}]
last =
\ (@ a_aTF) (xs_ast :: [a_aTF]) ->
poly_go_r2F3 @ a_aTF xs_ast (lvl8_r2F2 @ a_aTF)
}}}
That looks better. The unfolding is a bit more complicated, as `foldl` is
being lined, but that is presumably ok.
I’ll create a pull request with this in a small while, for review and
discussion.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10260#comment:6>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list