Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread Andres Löh
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 1 . fibs ) ())
  , bench fibsP (nf (take 1 . fibsP) ())
  , bench fibs' (nf (take 1 . 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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread Daniel Fischer
On Friday 01 February 2013, 12:50:18, Andres Löh wrote:
 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':

 
 main :: IO ()
 main = defaultMain $ [
 bench fibs  (nf (take 1 . fibs ) ())
   , bench fibsP (nf (take 1 . fibsP) ())
   , bench fibs' (nf (take 1 . 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?

zipWith' would [I haven't tested, but I'm rather confident] make a difference 
if 
you benchmarked

bench name (whnf (fibs !!) 10)

etc.

The reason is that 

foo = initialValues : zipWith f foo (tail foo)

is rather a scan than a real zip, so evaluating an element depends on 
evaluating all previous elements, and thus can build a huge thunk if the 
elements aren't demanded in order.

For a real zip where an element of the result does not depend on the values of 
earlier elements, plain zipWith would perform (usually only marginally) better 
than zipWith'.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread Daniel Fischer
On Friday 01 February 2013, 13:06:09, Daniel Fischer wrote:
 
 zipWith' would [I haven't tested, but I'm rather confident] make a
 difference if you benchmarked
 
 bench name (whnf (fibs !!) 10)
 
 etc.

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  100 = 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 2)
  , bench fibsP (whnf fibsP 2)
  , bench fibs' (whnf fibs' 2)
  ]

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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread Andres Löh
 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  100 = 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 2)
   , bench fibsP (whnf fibsP 2)
   , bench fibs' (whnf fibs' 2)
   ]

 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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread Daniel Fischer
On Friday 01 February 2013, 13:43:59, Andres Löh wrote:
 
 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,

Right. If you only want one Fibonacci number with a not too small index, you 
should use a dedicated algorithm.

I was just providing a possible answer to

 Am I overlooking anything? What's your test?

to show how the desire for zipWith' might arise from the fibs example.

 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'.

Right, and as I said in my first post, the fibs example is more of a scan than 
a 
zip. And for scans it's natural to consume the list in order [if you only want 
one element, a fold is the proper function].

 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'.

I don't even see how one could do it non-easily.

Cheers,
Daniel___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread Niklas Hambüchen
I recently asked a similar question about strict scans (e.g. scanl') 
and got the same response to use a strictify function.

Although I would argue that fun' is syntactically more convenient than 
(strictList . fun), I'd agree that composition is good.

Maybe it would make sense to add to have that strictList function in 
Data.List instead?

On Fri 01 Feb 2013 13:19:08 GMT, Daniel Fischer wrote:
 On Friday 01 February 2013, 13:43:59, Andres Löh wrote:

 

  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,



 Right. If you only want one Fibonacci number with a not too small
 index, you should use a dedicated algorithm.



 I was just providing a possible answer to



  Am I overlooking anything? What's your test?



 to show how the desire for zipWith' might arise from the fibs example.



  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'.



 Right, and as I said in my first post, the fibs example is more of a
 scan than a zip. And for scans it's natural to consume the list in
 order [if you only want one element, a fold is the proper function].



  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'.



 I don't even see how one could do it non-easily.



 Cheers,

 Daniel



 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread 山本和彦
Hi,

 zipWith' would [I haven't tested, but I'm rather confident] make a difference 
 if 
 you benchmarked
 
 bench name (whnf (fibs !!) 10)
 
 etc.

Yes. fibs is slow if used with !!.

--Kazu

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread 山本和彦
 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. 

Three topics are repeatedly discussed among beginners in Japan:

1) fibs implemented with zipWith
2) simple quicksort
3) sieve of eratosthenes

Some people use 1) with !! and say it's slow, why?.

Some people say 2) is not a true quicksort because it is not in-place.

Some people say 3) is not the sieve of eratosthenes at all because,
for example, 7 is divided by 5.

These three examples are mis-leading. In my opinion, if we use them,
we should

- use them as is, but describe such opinions OR
- use better implementations

I don't know translations work well but you can find such discussions
here:

http://d.hatena.ne.jp/kazu-yamamoto/20100624
http://d.hatena.ne.jp/nishiohirokazu/20100622/1277208908
http://d.hatena.ne.jp/mkotha/20100623/1277286946

--Kazu

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Why does not zipWith' exist

2013-01-31 Thread 山本和彦
Hello,

Many texts explain the following Fibonacci code:

fibs :: [Integer]
fibs = 0 : 1 : zipWith (+) fibs (tail fibs)

But this code is very slow because evaluation of (+) is done
lazily. If we have the following strict zipWith', the code above
becomes much faster.

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

Data.List defines foldl' against foldl. But it does not define
zipWith'. I'm curious why zipWith' does not exist in the standard
libraries.

--Kazu

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe