oneShot (was Re: FoldrW/buildW issues)

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

Wait, isn't call arity analysis meant to do this by itself now?
On 7 October 2014 17:05, David Feuer
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

Yes, and it does a very good job in many cases. In other cases, it's
not as good.
On Tue, Oct 7, 2014 at 7:59 AM, Sophie Taylor
Wait, isn't call arity analysis meant to do this by itself now?
On 7 October 2014 17:05, David Feuer
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

Hi, Am Dienstag, den 07.10.2014, 03:05 -0400 schrieb David Feuer:
Just for the heck of it, I tried out an implementation of scanl using Joachim Breitner's magical oneShot primitive. Using the test
[..]
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.
I cannot reproduce this here. In fact, I get identical core in both cases. Only when I do pass -fno-call-arity, A gets bad code, while B is still good. Maybe your example is too small? Greetings, Joachim -- Joachim “nomeata” Breitner mail@joachim-breitner.de • http://www.joachim-breitner.de/ Jabber: nomeata@joachim-breitner.de • GPG-Key: 0xF0FBF51F Debian Developer: nomeata@debian.org
participants (3)
-
David Feuer
-
Joachim Breitner
-
Sophie Taylor