[Haskell-beginners] Difference of time execution times when measuring with time and profiling

Javier de Vega Ruiz javier.devega.ruiz at gmail.com
Thu Oct 22 16:00:11 UTC 2015


HI all,

I am messing around with bang patterns and noticed some huge differences
between the total time as reported by the time tool and the .prof file.
Below is the code used.
Without bang patterns:
module Main where

import Data.List

fastFibs =
  unfoldr nextFib (1, 1)
  where nextFib (x, y) = Just $ (x, (y, (x + y)))

main =
  putStrLn $ (show n) ++ "th fib is: " ++ (show $ fastFibs !! (n - 1))
  where n = 1000000

With bang patterns:
{-# LANGUAGE BangPatterns #-}

module Main where

import Data.List

fastFibs =
  unfoldr nextFib (1, 1)
  where nextFib (!x, !y) = Just $ (x, (y, (x + y)))

main =
  putStrLn $ (show n) ++ "th fib is: " ++ (show $ fastFibs !! (n - 1))
  where n = 1000000

when looking at the first through time and prof I get the following.
Without:
real    0m53.501s
user    0m0.015s
sys     0m0.328s
        Thu Oct 22 16:46 2015 Time and Allocation Profiling Report  (Final)

           fast-fib.exe +RTS -p -RTS

        total time  =        9.52 secs   (9520 ticks @ 1000 us, 1 processor)
        total alloc = 43,500,223,152 bytes  (excludes profiling overheads)

Please note the huge difference 53 vs 9 seconds.

With:
real    0m10.095s
user    0m0.031s
sys     0m0.344s
        Thu Oct 22 16:50 2015 Time and Allocation Profiling Report  (Final)

           fast-fib.exe +RTS -p -RTS

        total time  =        8.97 secs   (8971 ticks @ 1000 us, 1 processor)
        total alloc = 43,500,309,960 bytes  (excludes profiling overheads)

Here differences seem to be much smaller.

I am using Windows 8.1 64 bit, GHC 7.8.3 and measuring with the following
line:
ghc Main.hs -o fast-fib.exe -O2 -prof && time ./fast-fib.exe +RTS -p && cat
fast-fib.prof

Could someone please explain where the big difference is coming from and
how to change the measuring approach to get more consistent results?

Best regards,
Javier de Vega Ruiz.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/beginners/attachments/20151022/39c7119d/attachment.html>


More information about the Beginners mailing list