<div dir="ltr">Yes. Forgive the strange names below. The zip version is 3 times as slow on 7.8.3. I did some horrible hacks to convince 7.8.3 to compile it more like 7.9 would (I don't have Criterion set up for 7.9), and I got it down to only twice as slow. Still, that does not seem so wonderful.<br><br>{-# LANGUAGE BangPatterns #-}<br>module Main where<br>import Criterion.Main<br><br>foldlWithIndex :: (Int -> b -> el -> b) -> b -> [el] -> b<br>foldlWithIndex f init xs = foldr go snd xs (0, init)<br>  where<br>    go x r (!n, a) = r (n+1, f n a x)<br><br>{-# INLINE zippily #-}  -- Taking this out makes it slower<br>zippily :: (Int -> b -> el -> b) -> b -> [el] -> b<br>zippily f init xs = foldl (\acc (!n,x) -> f n acc x) init (zip [0..] xs)<br><br>sumspecialevens = foldlWithIndex (\n a x -> if even n then a+3*x else a+x) (0::Int)<br>weirdspecialevens=foldlWithIndex (\n a x -> if x `rem` 16 == 0 then a+3*n else a + x) (0::Int)<br><br>stupidsum = zippily (\n a x -> if even n then a+3*x else a+x) (0::Int)<br>weirdstupidsum=zippily (\n a x -> if x `rem` 16 == 0 then a+3*n else a + x) (0::Int)<br><br>main = defaultMain $<br>  [<br>  bgroup "useAll"<br>   [<br>    bench "fwi" $ nf (\n -> sumspecialevens [1..n]) 1000000<br>   ,bench "zip" $ nf (\n -> stupidsum [1..n])       1000000<br>   ]<br>  ,bgroup "useSome"<br>   [<br>    bench "fwi" $ nf (\n -> weirdspecialevens [1..n]) 1000000<br>   ,bench "zip" $ nf (\n -> weirdstupidsum [1..n])    1000000<br>   ]<br>  ]<br></div><div class="gmail_extra"><br><div class="gmail_quote">On Thu, Oct 23, 2014 at 1:32 AM, Carter Schonwald <span dir="ltr"><<a href="mailto:carter.schonwald@gmail.com" target="_blank">carter.schonwald@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr">i hate always asking this question: but do we have an example benchmark illustrating there being a substantial difference in peformance if fold(l/r)withIndex is defined directly rather than via the more "naive" composition?<br></div><div class="gmail_extra"><br><div class="gmail_quote"><div><div class="h5">On Wed, Oct 22, 2014 at 6:13 PM, David Feuer <span dir="ltr"><<a href="mailto:david.feuer@gmail.com" target="_blank">david.feuer@gmail.com</a>></span> wrote:<br></div></div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div><div class="h5"><p dir="ltr">I think the answer is almost certainly no. The zipWith will turn into a foldr2, and there's no vaguely sure way of snatching that before it fuses with a build form and is lost forever. You'd end up with some very complicated rules that only did something useful when the phase of the moon was right. I'm pretty sure it's not worth trying.</p><div><div>
<div class="gmail_quote">On Oct 22, 2014 4:40 PM, "Ganesh Sittampalam" <<a href="mailto:ganesh@earth.li" target="_blank">ganesh@earth.li</a>> wrote:<br type="attribution"><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">I see, thanks. Could this be done via a rewrite rule from that idiom to<br>
an internal implementation function instead?<br>
<br>
On 22/10/2014 20:19, David Feuer wrote:<br>
> Yes, they do. In particular, the zip can only fuse with one of the two<br>
> lists so the Ints could be unboxed, or fusion optimizations could happen<br>
> with the list folded over, but not both. The fold_WithIndex function can<br>
> manage both at once. That said, I think there have been some pretty good<br>
> arguments against adding these, or at least against adding them with<br>
> these names.<br>
><br>
> On Oct 22, 2014 3:13 PM, "Ganesh Sittampalam" <<a href="mailto:ganesh@earth.li" target="_blank">ganesh@earth.li</a><br>
> <mailto:<a href="mailto:ganesh@earth.li" target="_blank">ganesh@earth.li</a>>> wrote:<br>
><br>
>     On 16/10/2014 18:14, David Feuer wrote:<br>
><br>
>         These functions can be lifted pretty much straight out of<br>
>         Data.Sequence.<br>
>         In particular, foldrWithIndex makes for a particularly nice<br>
>         expression<br>
>         of a fusing findIndices function, as is present in Data.Sequence.<br>
><br>
><br>
>     Do these do anything better than just adding indicies first with the<br>
>     standard zip [0..] idiom?<br>
><br>
>     Cheers,<br>
><br>
>     Ganesh<br>
><br>
>     _________________________________________________<br>
>     Libraries mailing list<br>
>     <a href="mailto:Libraries@haskell.org" target="_blank">Libraries@haskell.org</a> <mailto:<a href="mailto:Libraries@haskell.org" target="_blank">Libraries@haskell.org</a>><br>
>     <a href="http://www.haskell.org/__mailman/listinfo/libraries" target="_blank">http://www.haskell.org/__mailman/listinfo/libraries</a><br>
>     <<a href="http://www.haskell.org/mailman/listinfo/libraries" target="_blank">http://www.haskell.org/mailman/listinfo/libraries</a>><br>
><br>
<br>
</blockquote></div>
</div></div><br></div></div><span class="">_______________________________________________<br>
Libraries mailing list<br>
<a href="mailto:Libraries@haskell.org" target="_blank">Libraries@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/libraries" target="_blank">http://www.haskell.org/mailman/listinfo/libraries</a><br>
<br></span></blockquote></div><br></div>
</blockquote></div><br></div>