Proposal: Add foldrWithIndex and foldlWithIndex to Data.List

David Feuer david.feuer at gmail.com
Thu Oct 23 17:55:00 UTC 2014


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.

{-# LANGUAGE BangPatterns #-}
module Main where
import Criterion.Main

foldlWithIndex :: (Int -> b -> el -> b) -> b -> [el] -> b
foldlWithIndex f init xs = foldr go snd xs (0, init)
  where
    go x r (!n, a) = r (n+1, f n a x)

{-# INLINE zippily #-}  -- Taking this out makes it slower
zippily :: (Int -> b -> el -> b) -> b -> [el] -> b
zippily f init xs = foldl (\acc (!n,x) -> f n acc x) init (zip [0..] xs)

sumspecialevens = foldlWithIndex (\n a x -> if even n then a+3*x else a+x)
(0::Int)
weirdspecialevens=foldlWithIndex (\n a x -> if x `rem` 16 == 0 then a+3*n
else a + x) (0::Int)

stupidsum = zippily (\n a x -> if even n then a+3*x else a+x) (0::Int)
weirdstupidsum=zippily (\n a x -> if x `rem` 16 == 0 then a+3*n else a + x)
(0::Int)

main = defaultMain $
  [
  bgroup "useAll"
   [
    bench "fwi" $ nf (\n -> sumspecialevens [1..n]) 1000000
   ,bench "zip" $ nf (\n -> stupidsum [1..n])       1000000
   ]
  ,bgroup "useSome"
   [
    bench "fwi" $ nf (\n -> weirdspecialevens [1..n]) 1000000
   ,bench "zip" $ nf (\n -> weirdstupidsum [1..n])    1000000
   ]
  ]

On Thu, Oct 23, 2014 at 1:32 AM, Carter Schonwald <
carter.schonwald at gmail.com> wrote:

> 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?
>
> On Wed, Oct 22, 2014 at 6:13 PM, David Feuer <david.feuer at gmail.com>
> wrote:
>
>> 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.
>> On Oct 22, 2014 4:40 PM, "Ganesh Sittampalam" <ganesh at earth.li> wrote:
>>
>>> I see, thanks. Could this be done via a rewrite rule from that idiom to
>>> an internal implementation function instead?
>>>
>>> On 22/10/2014 20:19, David Feuer wrote:
>>> > Yes, they do. In particular, the zip can only fuse with one of the two
>>> > lists so the Ints could be unboxed, or fusion optimizations could
>>> happen
>>> > with the list folded over, but not both. The fold_WithIndex function
>>> can
>>> > manage both at once. That said, I think there have been some pretty
>>> good
>>> > arguments against adding these, or at least against adding them with
>>> > these names.
>>> >
>>> > On Oct 22, 2014 3:13 PM, "Ganesh Sittampalam" <ganesh at earth.li
>>> > <mailto:ganesh at earth.li>> wrote:
>>> >
>>> >     On 16/10/2014 18:14, David Feuer wrote:
>>> >
>>> >         These functions can be lifted pretty much straight out of
>>> >         Data.Sequence.
>>> >         In particular, foldrWithIndex makes for a particularly nice
>>> >         expression
>>> >         of a fusing findIndices function, as is present in
>>> Data.Sequence.
>>> >
>>> >
>>> >     Do these do anything better than just adding indicies first with
>>> the
>>> >     standard zip [0..] idiom?
>>> >
>>> >     Cheers,
>>> >
>>> >     Ganesh
>>> >
>>> >     _________________________________________________
>>> >     Libraries mailing list
>>> >     Libraries at haskell.org <mailto:Libraries at haskell.org>
>>> >     http://www.haskell.org/__mailman/listinfo/libraries
>>> >     <http://www.haskell.org/mailman/listinfo/libraries>
>>> >
>>>
>>>
>> _______________________________________________
>> Libraries mailing list
>> Libraries at haskell.org
>> http://www.haskell.org/mailman/listinfo/libraries
>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20141023/1a2432e4/attachment.html>


More information about the Libraries mailing list