[GHC] #9132: takeWhile&C. still not fusible

GHC ghc-devs at haskell.org
Thu May 22 13:03:57 UTC 2014


#9132: takeWhile&C. still not fusible
-------------------------------------+-------------------------------------
        Reporter:  Blaisorblade      |            Owner:
            Type:  bug               |           Status:  new
        Priority:  normal            |        Milestone:
       Component:  libraries/base    |          Version:  7.8.2
      Resolution:                    |         Keywords:  fusion
Operating System:  Unknown/Multiple  |     Architecture:  Unknown/Multiple
 Type of failure:  Runtime           |       Difficulty:  Moderate (less
  performance bug                    |  than a day)
       Test Case:                    |       Blocked By:
        Blocking:                    |  Related Tickets:
-------------------------------------+-------------------------------------

Comment (by Blaisorblade):

 Thanks for your answer! And sorry if I complained.

  I hope having a ticket already helps, but I've also given a try at
 "reproducing the (++) scheme" (following also map, where the scheme is
 clearer). For now I hacked it in a separate file, and I could verify that
 fusion still happens in my example. (And that tweaking even small things
 has nontrivial effects).

 Does the below make enough sense to go on? If so, the next main step (for
 me, or anybody who beats me) is just learning how to rebuild GHC and run
 nofib.

 {{{
 module IntToString where

 import Prelude hiding (takeWhile)
 import GHC.Exts

 --takeWhile' :: (a -> Bool) -> [a] -> [a]
 --takeWhile' p xs = build $ \c n -> foldr (takeWhileFB p c n) n xs
 --{-# INLINE takeWhile' #-}

 -- But this is a foldr, while takeWhile should be a foldl!
 takeWhileFB p c n x xs = if p x then x `c` xs else n
 {-# INLINE [0] takeWhileFB #-}

 {-# NOINLINE [1] takeWhile #-} -- We want the RULE to fire first.
 takeWhile               :: (a -> Bool) -> [a] -> [a]
 takeWhile _ []          =  []
 takeWhile p (x:xs)
             | p x       =  x : takeWhile p xs
             | otherwise =  []

 {-
 -- STUPID
 "takeWhile/backBad"    [1] forall p xs. takeWhile' p xs = takeWhile p xs
 -}

 -- Why can't I use, on the RHS, a function I mark with INLINE such as
 takeWhile' above? If I do that, the final program contains takeWhile.
 Probably just a phase ordering problem.
 {-# RULES
 "takeWhile/fuse"    [~1] forall p xs. takeWhile p xs = build $ \c n ->
 foldr (takeWhileFB p c n) n xs
 "takeWhile/back"   [1] forall p xs. foldr (takeWhileFB p (:) []) [] xs =
 takeWhile p xs
   #-}


 toChar digit = toEnum $ digit + fromEnum '0'


 intToString i =
   if i < 0 then
      '-' : digits
    else
      digits
   where
     digits =
       reverse . map (toChar . (`mod` 10)) . takeWhile (/=0) . iterate
 (`div` 10) . abs $ i
 }}}

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9132#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list