[Haskell-cafe] Why does not zipWith' exist

Andres Löh andres.loeh at gmail.com
Fri Feb 1 12:50:18 CET 2013


Hi Kazu.

I'd be surprised if zipWith' yields significant improvements. In the
case of foldl', the strictness affects an internal value (the
accumulator). However, in the case of zipWith', you're just forcing
the result a bit more, but I guess the "normal" use pattern of fibs is
that you want to see a prefix of the result anyway. So the overall
amount of evaluation is the same.

I've tried to hack up a quick criterion test comparing my own naive
zipWith, the Prelude zipWith (which may have additional optimizations,
I haven't checked), and zipWith':

import Criterion.Main
import Prelude hiding (zipWith)
import qualified Prelude as P

zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
zipWith f (a:as) (b:bs) = f a b : zipWith f as bs
zipWith _ _      _      = []

zipWith' :: (a -> b -> c) -> [a] -> [b] -> [c]
zipWith' f (a:as) (b:bs) = x `seq` x : zipWith' f as bs
  where
    x = f a b
zipWith' _ _ _ = []

fibs :: () -> [Integer]
fibs () = go
  where
    go :: [Integer]
    go = 0 : 1 : zipWith (+) go (tail go)

fibsP :: () -> [Integer]
fibsP () = go
  where
    go :: [Integer]
    go = 0 : 1 : P.zipWith (+) go (tail go)

fibs' :: () -> [Integer]
fibs' () = go
  where
    go :: [Integer]
    go = 0 : 1 : zipWith' (+) go (tail go)

main :: IO ()
main = defaultMain $ [
    bench "fibs " (nf (take 10000 . fibs ) ())
  , bench "fibsP" (nf (take 10000 . fibsP) ())
  , bench "fibs'" (nf (take 10000 . fibs') ())
  ]

The additional () arguments are to prevent GHC from sharing the list
in between calls. I haven't tested thoroughly if GHC looks through
this hack and optimizes it anyway.

Compiling without optimization, I get 1.15ms/1.11ms/1.10ms.
With -O, I get 85us/85us/88us.

Am I overlooking anything? What's your test?

Cheers,
  Andres



More information about the Haskell-Cafe mailing list