
Hi, I have a question about the cost of list comprehension and map function. For example, I have a list of Double and I want to do lots of calculation on it. There are two ways to do that: 1. [x ** 3 | x <- list] 2. map (flip (**) 3) list I am wondering if the cost of using them could be very different and why. Thanks.

On Thu, May 19, 2011 at 11:05 AM,
I have a question about the cost of list comprehension and map function.
For example, I have a list of Double and I want to do lots of calculation on it. There are two ways to do that: 1. [x ** 3 | x <- list] 2. map (flip (**) 3) list I am wondering if the cost of using them could be very different and why.
List comprehensions are just syntatic sugar. You should expect both (1) and (2) to be exactly the same when compiling. Cheers, =) -- Felipe.

OK, I see. Thanks a lot.
Cheers, =)
,Felipe Almeida Lessa
On Thu, May 19, 2011 at 11:05 AM, jianqiuchi@gmail.com> wrote:
I have a question about the cost of list comprehension and map function.
For example, I have a list of Double and I want to do lots of calculation on
it. There are two ways to do that:
1. [x ** 3 | x 2. map (flip (**) 3) list
I am wondering if the cost of using them could be very different and why.
List comprehensions are just syntatic sugar. You should expect both
(1) and (2) to be exactly the same when compiling.
Cheers, =)
--
Felipe.

By the way, you don't need the "flip" function.
map (** 3) [0,1..10]
[ x ** 3 | x <- [0,1..10]]
The section (** 3) will figure out on which side to put the argument/operand.
See http://www.haskell.org/haskellwiki/Section_of_an_infix_operator
2011/5/19
OK, I see. Thanks a lot.
Cheers, =)
,Felipe Almeida Lessa
撰写: On Thu, May 19, 2011 at 11:05 AM, jianqiuchi@gmail.com> wrote:
I have a question about the cost of list comprehension and map function.
1. [x ** 3 | x 2. map (flip (**) 3) list
-- -- Regards, KC

On Thursday 19 May 2011 16:05:29, jianqiuchi@gmail.com wrote:
Hi,
I have a question about the cost of list comprehension and map function.
For example, I have a list of Double and I want to do lots of calculation on it. There are two ways to do that: 1. [x ** 3 | x <- list] 2. map (flip (**) 3) list I am wondering if the cost of using them could be very different and why.
As Felipe said, they should compile to the same code. However, since you're asking about cost, which indicates that you care for performance, the above would be better written as [x*x*x | x <- list] unless you depend on the small differences in the outcome [I'm not quite sure how many bits may be affected, not many, typically none or one]. Functions like (**), exp, log, sin, cos, ... are slow, very slow. If the exponent is a small (positive) integer, specifically giving a sequence of multiplication steps is much faster, also using (^) instead of (**) is faster for small exponents (but slower than an explicit multiplication sequence). Of course, if the exponent may be a non-integer, you have to use (**), if it is an integer but not a fixed one, use (**) if the integer may be large¹, (^) or (^^) if it is sure to be small (in absolute modulus). [¹] (**) doesn't care how large the exponent is, (^) resp (^^) do.

Daniel Fischer
However, since you're asking about cost, which indicates that you care for performance, the above would be better written as
[x*x*x | x <- list]
unless you depend on the small differences in the outcome [I'm not quite sure how many bits may be affected, not many, typically none or one]. Functions like (**), exp, log, sin, cos, ... are slow, very slow. If the exponent is a small (positive) integer, specifically giving a sequence of multiplication steps is much faster, also using (^) instead of (**) is faster for small exponents (but slower than an explicit multiplication sequence).
Neither does this really match my intuition, nor can I confirm it with an experiment. Applying (** 3) a million times to a Double takes a second and gives me the expected Infinity. Applying (^3) or (\x -> x*x*x) a million times to the same value, well, I didn't want to wait for it to finish. The experiment was ran with the following codes in GHCi: iterate (** 3) 1.000000001 !! 1000000 iterate (^3) 1.000000001 !! 1000000 iterate (\x -> x*x*x) 1.000000001 !! 1000000 Note that exponentiation is a cheap operation on Double. Greets Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

x ** y = 10 ** (y * logBase 10 x)
Much easier to do base 10 exponents.
*Euler025> 25.0 ** 3.5
78125.0
*Euler025> 10 ** (3.5 * logBase 10 25.0)
78125.00000000009
On Thu, May 19, 2011 at 9:15 AM, Ertugrul Soeylemez
Daniel Fischer
wrote: However, since you're asking about cost, which indicates that you care for performance, the above would be better written as
[x*x*x | x <- list]
unless you depend on the small differences in the outcome [I'm not quite sure how many bits may be affected, not many, typically none or one]. Functions like (**), exp, log, sin, cos, ... are slow, very slow. If the exponent is a small (positive) integer, specifically giving a sequence of multiplication steps is much faster, also using (^) instead of (**) is faster for small exponents (but slower than an explicit multiplication sequence).
Neither does this really match my intuition, nor can I confirm it with an experiment. Applying (** 3) a million times to a Double takes a second and gives me the expected Infinity. Applying (^3) or (\x -> x*x*x) a million times to the same value, well, I didn't want to wait for it to finish.
The experiment was ran with the following codes in GHCi:
iterate (** 3) 1.000000001 !! 1000000 iterate (^3) 1.000000001 !! 1000000 iterate (\x -> x*x*x) 1.000000001 !! 1000000
Note that exponentiation is a cheap operation on Double.
Greets Ertugrul
-- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/
-- -- Regards, KC

You're not applying the operation 1000000 times, you're traversing to the
1000000th node in the list and applying the operation once. Laziness never
evaluates the other thunks.
On Thu, May 19, 2011 at 12:15 PM, Ertugrul Soeylemez
Daniel Fischer
wrote: However, since you're asking about cost, which indicates that you care for performance, the above would be better written as
[x*x*x | x <- list]
unless you depend on the small differences in the outcome [I'm not quite sure how many bits may be affected, not many, typically none or one]. Functions like (**), exp, log, sin, cos, ... are slow, very slow. If the exponent is a small (positive) integer, specifically giving a sequence of multiplication steps is much faster, also using (^) instead of (**) is faster for small exponents (but slower than an explicit multiplication sequence).
Neither does this really match my intuition, nor can I confirm it with an experiment. Applying (** 3) a million times to a Double takes a second and gives me the expected Infinity. Applying (^3) or (\x -> x*x*x) a million times to the same value, well, I didn't want to wait for it to finish.
The experiment was ran with the following codes in GHCi:
iterate (** 3) 1.000000001 !! 1000000 iterate (^3) 1.000000001 !! 1000000 iterate (\x -> x*x*x) 1.000000001 !! 1000000
Note that exponentiation is a cheap operation on Double.
Greets Ertugrul
-- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Alex R

Damn it... Forget my last email. I confused iterate with replicate for a
second...
On Thu, May 19, 2011 at 1:01 PM, Alex Rozenshteyn
You're not applying the operation 1000000 times, you're traversing to the 1000000th node in the list and applying the operation once. Laziness never evaluates the other thunks.
On Thu, May 19, 2011 at 12:15 PM, Ertugrul Soeylemez
wrote: Daniel Fischer
wrote: However, since you're asking about cost, which indicates that you care for performance, the above would be better written as
[x*x*x | x <- list]
unless you depend on the small differences in the outcome [I'm not quite sure how many bits may be affected, not many, typically none or one]. Functions like (**), exp, log, sin, cos, ... are slow, very slow. If the exponent is a small (positive) integer, specifically giving a sequence of multiplication steps is much faster, also using (^) instead of (**) is faster for small exponents (but slower than an explicit multiplication sequence).
Neither does this really match my intuition, nor can I confirm it with an experiment. Applying (** 3) a million times to a Double takes a second and gives me the expected Infinity. Applying (^3) or (\x -> x*x*x) a million times to the same value, well, I didn't want to wait for it to finish.
The experiment was ran with the following codes in GHCi:
iterate (** 3) 1.000000001 !! 1000000 iterate (^3) 1.000000001 !! 1000000 iterate (\x -> x*x*x) 1.000000001 !! 1000000
Note that exponentiation is a cheap operation on Double.
Greets Ertugrul
-- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Alex R
-- Alex R

On Thursday 19 May 2011 18:15:31, Ertugrul Soeylemez wrote:
Daniel Fischer
wrote: However, since you're asking about cost, which indicates that you care for performance, the above would be better written as
[x*x*x | x <- list]
unless you depend on the small differences in the outcome [I'm not quite sure how many bits may be affected, not many, typically none or one]. Functions like (**), exp, log, sin, cos, ... are slow, very slow. If the exponent is a small (positive) integer, specifically giving a sequence of multiplication steps is much faster, also using (^) instead of (**) is faster for small exponents (but slower than an explicit multiplication sequence).
Neither does this really match my intuition,
A multiplication takes ~1 clock cycle, calling out to pow takes way more (I confess, I don't know how many clock cycles a function call takes).
nor can I confirm it with an experiment. Applying (** 3) a million times to a Double takes a second and gives me the expected Infinity. Applying (^3) or (\x -> x*x*x) a million times to the same value, well, I didn't want to wait for it to finish.
The experiment was ran with the following codes in GHCi:
Don't benchmark in ghci, use compiled code.
iterate (** 3) 1.000000001 !! 1000000 iterate (^3) 1.000000001 !! 1000000 iterate (\x -> x*x*x) 1.000000001 !! 1000000
Note that exponentiation is a cheap operation on Double.
{-# LANGUAGE BangPatterns #-} module Main (main) where import Criterion.Main main :: IO () main = defaultMain [ bench "multiply" (whnf (test (\x -> x*x*x)) 10000) , bench "power" (whnf (test (\x -> x**3)) 10000) , bench "intPower" (whnf (test (^ (3 :: Int))) 10000) ] test :: (Double -> Double) -> Int -> Double test fun k = go k 0 (fromIntegral k) where go :: Int -> Double -> Double -> Double go 0 !acc !d = acc go j acc d = go (j-1) (acc + fun d) (d-1) benchmarking multiply collecting 100 samples, 20 iterations each, in estimated 727.8770 ms bootstrapping with 100000 resamples mean: 367.1096 us, lb 366.0110 us, ub 370.5876 us, ci 0.950 std dev: 11.04278 us, lb 2.089208 us, ub 22.41965 us, ci 0.950 found 5 outliers among 100 samples (5.0%) 4 (4.0%) high severe variance introduced by outliers: 0.998% variance is unaffected by outliers benchmarking power collecting 100 samples, 3 iterations each, in estimated 767.6125 ms bootstrapping with 100000 resamples mean: 2.322663 ms, lb 2.318265 ms, ub NaN s, ci 0.950 std dev: 106.4797 us, lb 52.31957 us, ub NaN s, ci 0.950 found 7 outliers among 100 samples (7.0%) 6 (6.0%) high severe variance introduced by outliers: 0.999% variance is unaffected by outliers benchmarking intPower collecting 100 samples, 8 iterations each, in estimated 775.3134 ms bootstrapping with 100000 resamples mean: 798.4662 us, lb 794.1207 us, ub 806.9849 us, ci 0.950 std dev: 31.24913 us, lb 17.17793 us, ub 59.85220 us, ci 0.950 found 7 outliers among 100 samples (7.0%) 4 (4.0%) high mild 3 (3.0%) high severe variance introduced by outliers: 0.999% variance is unaffected by outliers
Greets Ertugrul

Daniel Fischer
Neither does this really match my intuition,
A multiplication takes ~1 clock cycle, calling out to pow takes way more (I confess, I don't know how many clock cycles a function call takes).
nor can I confirm it with an experiment. Applying (** 3) a million times to a Double takes a second and gives me the expected Infinity. Applying (^3) or (\x -> x*x*x) a million times to the same value, well, I didn't want to wait for it to finish.
The experiment was ran with the following codes in GHCi:
Don't benchmark in ghci, use compiled code.
You were right, a benchmark with optimized, compiled code gave me different results. I now tested with the following function: calc :: (Double -> Double) -> Double calc f = calc' 10000000 (1 - encodeFloat 1 (-53)) where calc' :: Int -> Double -> Double calc' 0 x = x calc' n' x = let y = f x n = pred n' in y `seq` n `seq` calc' n y Running this function with (\x -> x*x*x) was the fastest, followed by (** 3) and then (^3). In conclusion, multiplication is faster than exponentiation for the special case of small exponents. Since the speed of (**) doesn't depend on the exponent (for Double), starting with an exponent of 15 (**) outperformed the other two variants. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/
participants (6)
-
Alex Rozenshteyn
-
Daniel Fischer
-
Ertugrul Soeylemez
-
Felipe Almeida Lessa
-
jianqiuchi@gmail.com
-
KC