
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