[Haskell-cafe] Why does not zipWith' exist

Andres Löh andres.loeh at gmail.com
Fri Feb 1 13:43:59 CET 2013


> Well, it took a little bit of persuasion to let GHC not cache the list(s), but
> with
>
>
> fibs :: Int -> Integer
> fibs k = igo i !! k
>   where
>     i | k < 1000000 = 1
>       | otherwise   = 2
>     igo :: Integer -> [Integer]
>     igo i = let go = 0 : i : zipWith (+) go (tail go) in go
>
> etc., benchmarking
>
> main :: IO ()
> main = defaultMain $ [
>     bench "fibs " (whnf fibs 20000)
>   , bench "fibsP" (whnf fibsP 20000)
>   , bench "fibs'" (whnf fibs' 20000)
>   ]
>
> shows a clear difference:
>
> benchmarking fibs
> mean: 14.50178 ms, lb 14.27410 ms, ub 14.78909 ms, ci 0.950
> benchmarking fibsP
> mean: 13.69060 ms, lb 13.59516 ms, ub 13.81583 ms, ci 0.950
> benchmarking fibs'
> mean: 3.155886 ms, lb 3.137776 ms, ub 3.177367 ms, ci 0.950

Right, I'm not arguing that it's impossible to produce a difference,
but I think that if you're defining the sequence of fibs, the most
likely scenario might be that you're actually interested in a prefix,
and more importantly, you can still, from the outside, force the
prefix even if you're only interested in a particular element. The
second point, imho, is what makes zipWith inherently different from a
function such as foldl'. You can equivalently define zipWith' as a
wrapper around zipWith:

zipWith' :: (a -> b -> c) -> [a] -> [b] -> [c]
zipWith' f xs ys = strictify (zipWith f xs ys)
  where
    strictify :: [a] -> [a]
    strictify []       = []
    strictify (x : xs) = x `seq` x : strictify xs

You cannot easily do the same for foldl and foldl'.

Cheers,
  Andres



More information about the Haskell-Cafe mailing list