criterion-0.1.4: Robust, reliable performance measurement and analysisSource codeContentsIndex
Criterion.Main
PortabilityGHC
Stabilityexperimental
Maintainerbos@serpentine.com
Contents
Benchmarking pure code
Let-floating
Worker-wrapper transformation
Types
Constructing benchmarks
Running benchmarks
Other useful code
Description
Wrappers for compiling and running benchmarks quickly and easily. See defaultMain below for an example.
Synopsis
class Benchmarkable b where
run :: b -> Int -> IO ()
data Benchmark
bench :: Benchmarkable b => String -> b -> Benchmark
bgroup :: String -> [Benchmark] -> Benchmark
defaultMain :: [Benchmark] -> IO ()
defaultMainWith :: Config -> [Benchmark] -> IO ()
defaultOptions :: [OptDescr (IO Config)]
parseArgs :: Config -> [OptDescr (IO Config)] -> [String] -> IO (Config, [String])
Benchmarking pure code

Because GHC optimises aggressively when compiling with -O, it is easy to write innocent-looking benchmark code that will only be evaluated once, for which all but the first iteration of the timing loop will be timing the cost of doing nothing.

The Int parameter that is passed into your benchmark function is important: you'll almost certainly need to use it somehow in order to ensure that your code will not get optimised away.

Let-floating

The following is an example of innocent-looking code that will not benchmark correctly:

 b = bench "fib 10" $ \(_::Int) -> fib 10

GHC will notice that the body is constant, and use let-floating to transform the function into a form more like this:

 lvl = fib 10
 b = bench "fib 10" $ \(::_Int) -> lvl

Here, it is obvious that the CAF lvl only needs to be evaluated once, and this is indeed what happens. The first iteration in the timing loop will measure a realistic time. All other iterations will take a few dozen nanoseconds, since the original thunk for lvl has already been overwritten with the result of its first evaluation.

One somewhat unreliable way to defeat let-floating is to disable it:

 {-# OPTIONS_GHC -fno-full-laziness #-}

If you are trying to benchmark an inlined function, turning off the let-floating transformation may end up causing slower code to be generated.

A much more reliable way to defeat let-floating is to find a way to make use of the Int that the benchmarking code passes in.

 bench "fib 10" $ \n -> fib (10+n-n)

GHC is not yet smart enough to see that adding and subtracting n amounts to a no-op. This trick is enough to convince it not to let-float the function's body out, since the body is no longer constant.

Worker-wrapper transformation

Another GHC optimisation is worker-wrapper transformation. Suppose you want to time insertion of key/value pairs into a map. You might perform the insertion via a (strict!) fold:

 import qualified Data.IntMap as I
 import Data.List (foldl')

 intmap :: Int -> I.IntMap Int
 intmap n = foldl' (\m k -> I.insert k k m) I.empty [0..n]

 b = bench "intmap 10k" $ \(_::Int) -> intmap 10000

Compile this without -fno-full-laziness, and the body of the anonymous function we're benchmarking gets let-floated out to the top level.

 lvl = intmap 10000
 b = bench "intmap 10k" $ \(_::Int) -> lvl

Compile it with -fno-full-laziness, and let-floating occurs anyway, this time due to GHC's worker-wrapper transformation.

Once again, the response is to use the parameter that the benchmarking code passes in.

 intmap :: Int -> Int -> I.IntMap Int
 intmap n i = foldl' (\m k -> I.insert k k m) I.empty [0..n+i-i]

 b = bench "intmap 10k" $ intmap 10000
Types
class Benchmarkable b whereSource
A benchmarkable function or action.
Methods
run :: b -> Int -> IO ()Source
show/hide Instances
data Benchmark Source
A benchmark may consist of either a single Benchmarkable item with a name, created with bench, or a (possibly nested) group of Benchmarks, created with bgroup.
show/hide Instances
Constructing benchmarks
benchSource
:: Benchmarkable b
=> String
-> b
-> Benchmark
Create a single benchmark.
bgroupSource
:: StringA name to identify the group of benchmarks.
-> [Benchmark]Benchmarks to group under this name.
-> Benchmark
Group several benchmarks together under a common name.
Running benchmarks
defaultMain :: [Benchmark] -> IO ()Source

An entry point that can be used as a main function.

 import Criterion.Main

 fib :: Int -> Int
 fib 0 = 0
 fib 1 = 1
 fib n = fib (n-1) + fib (n-2)

 main = defaultMain [
        bgroup "fib" [ bench "fib 10" $ \n -> fib (10+n-n))
                     , bench "fib 35" $ \n -> fib (35+n-n))
                     , bench "fib 37" $ \n -> fib (37+n-n))
                     ]
                    ]
defaultMainWith :: Config -> [Benchmark] -> IO ()Source

An entry point that can be used as a main function, with configurable defaults.

Example:

 import Criterion.Config
 import qualified Criterion.MultiMap as M

 myConfig = defaultConfig {
              -- Always display an 800x600 window with curves.
              cfgPlot = M.singleton KernelDensity (Window 800 600)
            }
 
 main = defaultMainWith myConfig [
          bench "fib 30" $ \(n::Int) -> fib (30+n-n)
        ]

If you save the above example as "Fib.hs", you should be able to compile it as follows:

 ghc -O --make Fib

Run "Fib --help" on the command line to get a list of command line options.

Other useful code
defaultOptions :: [OptDescr (IO Config)]Source
The standard options accepted on the command line.
parseArgs :: Config -> [OptDescr (IO Config)] -> [String] -> IO (Config, [String])Source
Parse command line options.
Produced by Haddock version 2.6.0