[GHC] #9344: takeWhile does not participate in list fusion
GHC
ghc-devs at haskell.org
Tue Jul 22 05:24:27 UTC 2014
#9344: takeWhile does not participate in list fusion
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: libraries/base | Version: 7.8.3
Keywords: | Differential Revisions:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+-------------------------------------
`takeWhile` doesn't do the list fusion thing. This alternative definition
seems to fix that, at least to a great extent. It fused completely in a
simple test, and incompletely but still usefully in a more complex one. I
don't know how to write the appropriate translate/untranslate RULES for it
yet.
{{{
#!haskell
{-# LANGUAGE ScopedTypeVariables #-}
takeWhileFB :: forall a . (a -> Bool) -> [a] -> [a]
takeWhileFB p xs = build tw'
where
tw' :: forall b . (a -> b -> b) -> b -> b
tw' kons knil = foldr go knil xs
where
go x rest | p x = x `kons` rest
| otherwise = knil
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9344>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list