Copyright | (c) Johan Tibell 2008 |
---|---|
License | BSD3-style (see LICENSE) |
Maintainer | me@willsewell.com |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Benchmarks actions and produces statistics such as min, mean, median, standard deviation, and max execution time. Also computes execution time percentiles. Comes with functions to pretty-print the results.
Here's an example showing a benchmark of copying a file:
import Control.Monad (when) import qualified Data.ByteString as B import System.IO import Test.BenchPress inpath, outpath :: String inpath = "/tmp/infile" outpath = "/tmp/outfile" blockSize :: Int blockSize = 4 * 1024 copyUsingByteString :: Handle -> Handle -> IO () copyUsingByteString inf outf = go where go = do bs <- B.hGet inf blockSize let numRead = B.length bs when (numRead > 0) $ B.hPut outf bs >> go main :: IO () main = bench 100 $ do inf <- openBinaryFile inpath ReadMode outf <- openBinaryFile outpath WriteMode copyUsingByteString inf outf hClose outf hClose inf
Running a benchmark
benchmark :: Int -> IO a -> (a -> IO b) -> (a -> IO c) -> IO (Stats, Stats) Source #
benchmark iters setup teardown action
runs action
iters
times measuring the execution time of each run. setup
and
teardown
are run before and after each run respectively.
teardown
is run even if action
raises an exception. Returns
statistics for both the measured CPU times and wall clock times, in
that order.
bench :: Int -> IO a -> IO () Source #
Convenience function that runs a benchmark using benchmark
and
prints timing statistics using printDetailedStats
. The
statistics are computed from the measured CPU times. Writes output
to standard output.
benchMany :: Int -> [(String, IO a)] -> IO () Source #
Convenience function that runs several benchmarks using
benchmark
and prints a timing statistics summary using
printStatsSummaries
. The statistics are computed from the
measured CPU times. Each benchmark has an associated label that is
used to identify the benchmark in the printed results. Writes
output to standard output.
Benchmark stats
Execution time statistics for a benchmark. All measured times are given in milliseconds.
Stats | |
|
Pretty-printing stats
printDetailedStats :: Stats -> IO () Source #
Prints detailed statistics. Printed statistics include min, mean, standard deviation, median, and max execution time. Also prints execution time percentiles. Writes output to standard output.
printStatsSummaries :: [(String, Stats)] -> IO () Source #
Prints a summary row for each benchmark with an associated label.
The summary contains the same statistics as in printDetailedStats
except for the execution time percentiles. Writes output to
standard output.