Gratuitous eta-expansion over non-cheap work
Consider the following code:
module Test where
mySum :: [Int] -> Int
mySum [] = 0
mySum (x:xs) = x + mySum xs
f :: Int -> (Int -> Int) -> Int -> Int
f k z =
if even (mySum [0..k])
then \n -> n + 1
else \n -> z n
We should not eta-expand f
, because that will duplicate work for call sites like let g = f 1000 id in g 10 + g 20
.
Yet, with -fno-worker-wrapper
(after writing this down, I double-checked and it appears we also do the same to $wf
with -fworker-wrapper
), I get after post-worker-wrapper Simplification
f :: Int -> (Int -> Int) -> Int -> Int
[LclIdX,
Arity=3,
Str=<1!P(L)><LCS(L)>,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [20 60 0] 315 0}]
f = \ (k_ayP [Dmd=1!P(L)] :: Int)
(z_ayQ [Dmd=LCS(L)] :: Int -> Int)
(eta_B0 :: Int) ->
case k_ayP of { I# y_aWY ->
case ># 0# y_aWY of {
__DEFAULT ->
letrec {
go3_aXd [Occ=LoopBreaker] :: Int# -> [Int]
[LclId,
Arity=1,
Str=<L>,
Unf=Unf{Src=<vanilla>, TopLvl=False, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [0] 62 10}]
go3_aXd
= \ (x_aXe :: Int#) ->
GHC.Types.:
@Int
(GHC.Types.I# x_aXe)
(case ==# x_aXe y_aWY of {
__DEFAULT -> go3_aXd (+# x_aXe 1#);
1# -> GHC.Types.[] @Int
}); } in
case mySum (go3_aXd 0#) of { I# ipv_aWJ -> ...
whereas we just had the following after CPR:
f :: Int -> (Int -> Int) -> Int -> Int
[LclIdX,
Arity=2,
Str=<1!P(L)><LCS(L)>,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [20 60] 121 120}]
f = \ (k_ayP [Dmd=1!P(L)] :: Int)
(z_ayQ [Dmd=LCS(L)] :: Int -> Int) ->
case mySum (case k_ayP of { I# y_aWY -> GHC.Enum.eftInt 0# y_aWY })
of
{ I# ipv_aWJ ->
case remInt# ipv_aWJ 2# of {
__DEFAULT -> \ (n_aDL :: Int) -> z_ayQ n_aDL;
0# -> lvl_sX3
}
}
I suspect it has to do with inlining eftInt
somehow, but I'm not quite sure.