[GHC] #9369: Data.List.unfoldr does not fuse and is not inlined.
GHC
ghc-devs at haskell.org
Sun Jul 27 05:52:35 UTC 2014
#9369: Data.List.unfoldr does not fuse and is not inlined.
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 7.8.4
Component: libraries/base | Version: 7.8.3
Keywords: | Operating System:
Architecture: Unknown/Multiple | Unknown/Multiple
Difficulty: Easy (less than 1 | Type of failure: Runtime
hour) | performance bug
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
`Data.List.unfoldr` is not a good producer for foldr/build fusion, and
it's not wrapped to enable inlining. I don't know how often people
explicitly fold over an unfold, but this of course also affects map and
filter. The inlining issue is also serious: inlining `unfoldr` can often
allow the `Maybe` to be erased altogether. I'm not sure this fix is
perfect, but it seems a lot better than the current situation:
{{{#!hs
import GHC.Exts (build)
{-# NOINLINE [1] unfoldr #-}
unfoldr :: (b -> Maybe (a, b)) -> b -> [a]
unfoldr f b = go b
where
go b = case f b of
Just (a,new_b) -> a : go new_b
Nothing -> []
{-# INLINE [0] unfoldrB #-}
unfoldrB :: (b -> Maybe (a, b)) -> b -> (a -> c -> c) -> c -> c
unfoldrB f b' c n = go b'
where
go b = case f b of
Just (a,new_b) -> a `c` go new_b
Nothing -> n
{-# RULES
"unfoldr" [~1] forall f b . unfoldr f b = build (unfoldrB f b)
#-}
}}}
As a simple example, consider the code
{{{#!hs
hello :: Double -> Double -> [Double]
hello x n = map (* 3) $ L.unfoldr f x
where
f x | x < n = Just (x, x**1.2)
| otherwise = Nothing
}}}
With `Data.List.unfoldr` and the latest bleeding-edge GHC, this produces
{{{#!hs
hello1
hello1 =
\ ds_d1ZF -> case ds_d1ZF of _ { D# x_a21W -> D# (*## x_a21W 3.0) }
$whello
$whello =
\ w_s266 ww_s26a ->
map
hello1
(unfoldr
(\ x_X1Hx ->
case x_X1Hx of wild_a20E { D# x1_a20G ->
case tagToEnum# (<## x1_a20G ww_s26a) of _ {
False -> Nothing;
True -> Just (wild_a20E, D# (**## x1_a20G 1.2))
}
})
w_s266)
hello
hello =
\ w_s266 w1_s267 ->
case w1_s267 of _ { D# ww1_s26a -> $whello w_s266 ww1_s26a }
}}}
Using the above implementation (and renaming the function from `hello` to
`bye`) yields
{{{#!hs
$wbye
$wbye =
\ ww_s25Z ww1_s263 ->
letrec {
$wgo_s25U
$wgo_s25U =
\ ww2_s25S ->
case tagToEnum# (<## ww2_s25S ww1_s263) of _ {
False -> [];
True -> : (D# (*## ww2_s25S 3.0)) ($wgo_s25U (**## ww2_s25S
1.2))
}; } in
$wgo_s25U ww_s25Z
bye
bye =
\ w_s25V w1_s25W ->
case w_s25V of _ { D# ww1_s25Z ->
case w1_s25W of _ { D# ww3_s263 -> $wbye ww1_s25Z ww3_s263 }
}
}}}
I don't think there can be any doubt which is better. Yes, some fine
tuning may be needed to make the rules apply in all appropriate cases. I
don't understand things like the comment on the definition of `map`
drawing attention to eta expansion.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9369>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list