[Haskell-cafe] Timing pure functions?

2009-05-27 Thread Magnus Therning
Yesterday I spent about 5 minutes trying to time a single function in
haskell (after having spent about 30 minutes on the timeit module in
Python).  I found timeit[1] on Hackage but it only times an IO
computation once, what I'd like to do is time a pure function several
times.  Timing it once was no problem, passing `return $! myPureFunc`
to `timeIt` did that[2].  My feeble attempt at collecting several
timings failed though.

  import System.CPUTime
  import qualified Codec.Binary.Base64 as B64
  import System.IO
  import qualified Data.ByteString as BS
  import Control.Monad


  timeIt times ioa = let
  timeOnce = do
  t1 - getCPUTime
  a - ioa
  t2 - getCPUTime
  let t = fromIntegral (t2-t1) * 1e-12
  return t
  in sequence $ take times $ repeat timeOnce

  main = do
  fh - openBinaryFile /dev/urandom ReadMode
  d - liftM BS.unpack $ BS.hGet fh 10
  t - timeIt 10 $ return $! B64.encode d
  print t

Running this on my machine produces the output
[2.3331e-2,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0].  I.e. the first time
the data is encoded, but the following 9 times it's not.

I suspect that it all comes from `B64.encode d` being pure, hence the
encoding happens only once.  Now I _really_ want the encoding to
happen 10 times, is there some easy way to achieve this?

/M

[1]: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/timeit
[2]:
-- 
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Timing pure functions?

2009-05-27 Thread Andrew Butterfield

Magnus Therning wrote:

  timeIt times ioa = let
  timeOnce = do
  t1 - getCPUTime
  a - ioa
  t2 - getCPUTime
  let t = fromIntegral (t2-t1) * 1e-12
  return t
  in sequence $ take times $ repeat timeOnce

  main = do
  fh - openBinaryFile /dev/urandom ReadMode
  d - liftM BS.unpack $ BS.hGet fh 10
  t - timeIt 10 $ return $! B64.encode d
  print t


I suspect that it all comes from `B64.encode d` being pure, hence the
encoding happens only once.  Now I _really_ want the encoding to
happen 10 times, is there some easy way to achieve this?

  
A quick answer - not a lot of thought - pass function *and* argument 
separately into timeIt ?


 timeIt times ioaf ioaarg
    a - ioaf ioaarg

As it stands you pass the thunk (B64.encode d) in so it only gets 
evaluated once
If you pass the function and argument in then a new thunk is built each 
time around

(unless the optimiser nabbles it...)

/M

[1]: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/timeit
[2]:
  



--

Andrew Butterfield Tel: +353-1-896-2517 Fax: +353-1-677-2204
Foundations and Methods Research Group Director.
School of Computer Science and Statistics,
Room F.13, O'Reilly Institute, Trinity College, University of Dublin
   http://www.cs.tcd.ie/Andrew.Butterfield/


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


Re: [Haskell-cafe] Timing pure functions?

2009-05-27 Thread Magnus Therning
On Wed, May 27, 2009 at 9:59 AM, Andrew Butterfield
andrew.butterfi...@cs.tcd.ie wrote:
 Magnus Therning wrote:

  timeIt times ioa = let
          timeOnce = do
              t1 - getCPUTime
              a - ioa
              t2 - getCPUTime
              let t = fromIntegral (t2-t1) * 1e-12
              return t
          in sequence $ take times $ repeat timeOnce

  main = do
      fh - openBinaryFile /dev/urandom ReadMode
      d - liftM BS.unpack $ BS.hGet fh 10
      t - timeIt 10 $ return $! B64.encode d
      print t


 I suspect that it all comes from `B64.encode d` being pure, hence the
 encoding happens only once.  Now I _really_ want the encoding to
 happen 10 times, is there some easy way to achieve this?



 A quick answer - not a lot of thought - pass function *and* argument
 separately into timeIt ?

  timeIt times ioaf ioaarg
        a - ioaf ioaarg

 As it stands you pass the thunk (B64.encode d) in so it only gets evaluated
 once
 If you pass the function and argument in then a new thunk is built each time
 around
 (unless the optimiser nabbles it...)

Hmm, my naive implementation of that didn't improve the situation, `t
- timeIt 10 (\ x - return $! B64.encode x) d` still results in only
one measurement /= 0.

Of course that also makes `timeIt` less general.

/M

-- 
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Timing pure functions?

2009-05-27 Thread austin s
Excerpts from Magnus Therning's message of Wed May 27 03:51:19 -0500 2009:
 Yesterday I spent about 5 minutes trying to time a single function in
 haskell (after having spent about 30 minutes on the timeit module in
 Python).  I found timeit[1] on Hackage but it only times an IO
 computation once, what I'd like to do is time a pure function several
 times.  Timing it once was no problem, passing `return $! myPureFunc`
 to `timeIt` did that[2].  My feeble attempt at collecting several
 timings failed though.
 
   import System.CPUTime
   import qualified Codec.Binary.Base64 as B64
   import System.IO
   import qualified Data.ByteString as BS
   import Control.Monad
 
 
   timeIt times ioa = let
   timeOnce = do
   t1 - getCPUTime
   a - ioa
   t2 - getCPUTime
   let t = fromIntegral (t2-t1) * 1e-12
   return t
   in sequence $ take times $ repeat timeOnce
 
   main = do
   fh - openBinaryFile /dev/urandom ReadMode
   d - liftM BS.unpack $ BS.hGet fh 10
   t - timeIt 10 $ return $! B64.encode d
   print t
 
 Running this on my machine produces the output
 [2.3331e-2,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0].  I.e. the first time
 the data is encoded, but the following 9 times it's not.
 
 I suspect that it all comes from `B64.encode d` being pure, hence the
 encoding happens only once.  Now I _really_ want the encoding to
 happen 10 times, is there some easy way to achieve this?
 
 /M
 
 [1]: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/timeit
 [2]:

Perhaps benchpress would be more to your liking:

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/benchpress

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


Re: [Haskell-cafe] Timing pure functions?

2009-05-27 Thread Johan Tibell
On Wed, May 27, 2009 at 12:02 PM, austin s a...@nijoruj.org wrote:

  Perhaps benchpress would be more to your liking:

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/benchpress


Note that since benchpress measures every single invocation of the provided
IO action in order to compute percentiles it's not good at measuring the
execution times of small functions as the timing overhead dominates in those
cases.

Cheers,

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


Re: [Haskell-cafe] Timing pure functions?

2009-05-27 Thread wren ng thornton

Johan Tibell wrote:

austin s wrote:
  Perhaps benchpress would be more to your liking:

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/benchpress

Note that since benchpress measures every single invocation of the provided
IO action in order to compute percentiles it's not good at measuring the
execution times of small functions as the timing overhead dominates in those
cases.



For small functions, microbench is another good option:

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/microbench


When comparing functions with large multiplicative discrepancies in 
runtime, it can give erroneous answers due to Int overflow. Modifying it 
to use Integers instead fixes the bug a some overhead cost. (Perhaps 
both versions could be offered by the package?)


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe