Wait, isn't call arity analysis meant to do this by itself now?

On 7 October 2014 17:05, David Feuer <david.feuer@gmail.com> wrote:
Just for the heck of it, I tried out an implementation of scanl using
Joachim Breitner's magical oneShot primitive. Using the test

scanlA :: (b -> a -> b) -> b -> [a] -> [b]
scanlA f a bs = build $ \c n ->
    a `c`
    foldr (\b g x -> let b' = f x b in (b' `c` g b'))
          (const n)
          bs
          a

scanlB :: (b -> a -> b) -> b -> [a] -> [b]
scanlB f a bs = build $ \c n ->
    a `c`
    foldr (\b g -> oneShot (\x -> let b' = f x b in (b' `c` g b')))
          (const n)
          bs
          a

f :: Int -> Bool
f 0 = True
f 1 = False
{-# NOINLINE f #-}

barA = scanlA (+) 0 . filter f
barB = foldlB (+) 0 . filter f


with -O2 (NOT disabling Call Arity) the Core from barB is really,
really beautiful: it's small, there are no lets or local lambdas, and
everything is completely unboxed. This is much better than the result
of barA, which has a local let, and which doesn't seem to manage to
unbox anything. It looks to me like this could be a pretty good tool
to have around. It certainly has its limits—it doesn't do anything
nice with reverse . reverse  or  reverse . scanl f b . reverse, but it
doesn't need to be perfect to be useful. More evaluation, of course,
is necessary.to make sure it doesn't go wrong when used sanely.

David
_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs