
#9344: takeWhile does not participate in list fusion -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 7.8.3 libraries/base | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: Runtime | Related Tickets: performance bug | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dfeuer): I messed around with RULES a bit, and the following seem to work okay for starters. Some more rules will be needed to make map/takeWhile and takeWhile/map and whatever else do the right thing. One thing I'm not too clear about: what's the advantage of the explicitly recursive default definition over `takeWhile p = foldr (\x r -> if p x then x:r else []) []`? {{{ {-# INLINE [0] takeWhileFB #-} takeWhileFB :: (elt -> lst -> lst) -> lst -> (elt -> Bool) -> elt -> lst -> lst takeWhileFB kons knil p = \x rest -> if p x then x `kons` rest else knil {-# NOINLINE [1] takeWhile #-} takeWhile :: (a -> Bool) -> [a] -> [a] takeWhile _ [] = [] takeWhile p (x:xs) | p x = x : takeWhile p xs | otherwise = [] {-# RULES "takeWhile" [~1] forall p xs. takeWhile p xs = build (\kons knil -> foldr (takeWhileFB kons knil p) knil xs) "takeWhileList" [1] forall p. foldr (takeWhileFB (:) [] p) [] = takeWhile p "takeWhileFB" forall kons knil p q. takeWhileFB (takeWhileFB kons knil p) knil q = \x rest -> if (q x && p x) then x `kons` rest else knil #-} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9344#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler