| Portability | portable |
|---|---|
| Stability | experimental |
| Maintainer | johan.tibell@gmail.com |
Test.BenchPress
Description
Benchmarks actions and produces statistics such as min, mean, median, standard deviation, and max execution time. Also computes execution time percentiles. There are functions to pretty-print the results.
Here's an example showing a benchmark of copying a file:
import Control.Monad.Trans
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
if numRead > 0
then B.hPut outf bs >> go
else return ()
main :: IO ()
main = bench 100 $ liftIO $ do
inf <- openBinaryFile inpath ReadMode
outf <- openBinaryFile outpath WriteMode
copyUsingByteString inf outf
hClose outf
hClose inf
The Benchmark type
Running a benchmark
benchmark :: Int -> Benchmark a -> IO StatsSource
benchmark iters bm runs the action bm iters times measuring
the execution time of each run.
bench :: Int -> Benchmark a -> IO ()Source
Convenience function that runs a benchmark using benchmark and
prints timing statistics.
benchMany :: Int -> [(String, Benchmark a)] -> IO ()Source
Convenience function that runs several benchmarks using
benchmark and prints a timing statistics summary. Each benchmark
has an associated label that is used to identify the benchmark in
the printed results.
Benchmark stats
Timing statistics for the benchmark. All measured times are given in milliseconds.
Constructors
| Stats | |
Fields
| |