testbench-0.1.0.0: Create tests and benchmarks together

Copyright(c) Ivan Lazar Miljenovic
LicenseMIT
MaintainerIvan.Miljenovic@gmail.com
Safe HaskellNone
LanguageHaskell2010

TestBench

Contents

Description

Make it easier to compare benchmarks and to test that benchmarks are indeed valid.

At the top level you will probably run the testBench function, and create comparisons using compareFunc or compareFuncConstraint.

For example:

main :: IO ()
main = testBench $ do
  -- Compare how long it takes to make a list of the specified length.
  compareFunc "List length"
              (\n -> length (replicate n ()) == n)
              (testWith (@? "Not as long as specified") `mappend` benchNormalForm)
              (mapM_ (\n -> comp ("len == " ++ show n) n) [1..5])

  -- Polymorphic comparisons.
  --
  -- Currently it isn't possible to use a Proxy as the argument to
  -- the function (this will probably require Injective Type Families
  -- in GHC 8.0), so we're using 'undefined' to specify the type.
  compareFuncConstraint (Proxy :: Proxy (CUnion Eq Num))
                        "Number type equality"
                        (join (==) . (0`asTypeOf`))
                        (baseline "Integer" (undefined :: Integer) `mappend` benchNormalForm)
                        $ do comp "Int"     (undefined :: Int)
                             comp "Double"  (undefined :: Double)

When run, the output will look something like:

Cases: 7  Tried: 7  Errors: 0  Failures: 0
                          Mean    MeanLB    MeanUB    Stddev  StddevLB  StddevUB  OutlierVariance
List length
  len == 1            323.8 ns  318.6 ns  335.9 ns  23.86 ns  5.834 ns  40.90 ns              83%
  len == 2            352.8 ns  349.1 ns  358.1 ns  15.05 ns  11.76 ns  19.62 ns              61%
  len == 3            372.4 ns  358.4 ns  393.8 ns  62.50 ns  39.83 ns  90.85 ns              96%
  len == 4            396.3 ns  378.4 ns  419.2 ns  67.83 ns  46.71 ns  94.74 ns              96%
  len == 5            426.0 ns  407.0 ns  459.5 ns  82.23 ns  53.37 ns  110.2 ns              97%
Number type equality
  Integer             75.43 ns  74.48 ns  76.71 ns  3.615 ns  2.748 ns  5.524 ns              69%
  Int                 74.39 ns  73.48 ns  76.24 ns  3.964 ns  2.500 ns  7.235 ns              74%
  Double              78.05 ns  75.84 ns  82.50 ns  9.790 ns  6.133 ns  16.99 ns              94%

Synopsis

Specification and running

type TestBench = TestBenchM () Source

An environment for combining testing and benchmarking.

testBench :: TestBench -> IO () Source

Run the specified benchmarks if and only if all tests pass, using a comparison-based format for benchmarking output.

Please note that this is currently very simplistic: no parameters, configuration, etc. Also, benchmark results will not be shown until all benchmarks are complete.

For more control, use getTestBenches.

Running manually

getTestBenches :: TestBench -> IO (Test, BenchForest) Source

Obtain the resulting tests and benchmarks from the specified TestBench.

type BenchTree = LabelTree (String, Benchmarkable) Source

A more explicit tree-like structure for benchmarks than using Criterion's Benchmark type.

flattenBenchForest :: BenchForest -> [Benchmark] Source

Remove the explicit tree-like structure into the implicit one used by Criterion.

Useful for embedding the results into an existing benchmark suite.

benchmarkForest :: Config -> BenchForest -> IO () Source

Run the specified benchmarks, printing the results (once they're all complete) to stdout in a tabular format for easier comparisons.

Lower-level types

type OpTree = LabelTree Operation Source

A tree of operations.

data Operation Source

An individual operation potentially consisting of a benchmark and/or test.

data LabelTree a Source

A simple labelled rose-tree data structure.

Constructors

Leaf a 
Branch String [LabelTree a] 

Grouping

collection :: String -> TestBench -> TestBench Source

Label a sub-part of a TestBench.

Direct benchmarks/tests

nfEq :: (NFData b, Show b, Eq b) => b -> (a -> b) -> String -> a -> TestBench Source

Create a single benchmark evaluated to normal form, where the results should equal the value specified.

whnfEq :: (Show b, Eq b) => b -> (a -> b) -> String -> a -> TestBench Source

Create a single benchmark evaluated to weak head normal form, where the results should equal the value specified.

mkTestBench :: ((a -> b) -> a -> Maybe Benchmarkable) -> (b -> Maybe Assertion) -> (a -> b) -> String -> a -> TestBench Source

A way of writing custom testing/benchmarking statements. You will probably want to use one of the pre-defined versions instead.

Comparisons

compareFunc :: forall a b. String -> (a -> b) -> CompParams (SameAs a) b -> Comparison (SameAs a) b -> TestBench Source

Compare how various input values (of the same type) behave for a specific function.

By default:

  • Results are only evaluated to Weak Head Normal Form. To fully evaluate results, use benchNormalForm.
  • No tests are performed by default; use either baseline or testWith to specify one.

compareFuncConstraint :: forall ca b. Proxy ca -> String -> (forall a. ca a => a -> b) -> CompParams ca b -> Comparison ca b -> TestBench Source

As with compareFunc but allow for polymorphic inputs by specifying the constraint to be used.

Specifying constraints

class (c1 a, c2 a) => CUnion c1 c2 a Source

The union of two (* -> Constraint) values.

Whilst type EqNum a = (Eq a, Num a) is a valid specification of a Constraint when using the ConstraintKinds extension, it cannot be used with compareFuncConstraint as type aliases cannot be partially applied.

As such, you can use type EqNum = CUnion Eq Num instead.

Instances

(c1 a, c2 a) => CUnion c1 c2 a Source 

Comparison parameters

data CompParams ca b Source

Monoidally build up the parameters used to control a Comparison environment.

This will typically be a combination of benchNormalForm with either baseline or testWith.

Instances

Control benchmarking

benchNormalForm :: NFData b => CompParams ca b Source

Evaluate all benchmarks to normal form.

withBenchMode :: (forall a. ca a => (a -> b) -> a -> Benchmarkable) -> CompParams ca b Source

Allow specifying how benchmarks should be evaluated. This may allow usage of methods such as nfIO, but this has not been tested as yet.

noBenchmarks :: CompParams ca b Source

Don't run any benchmarks. I'm not sure why you'd want to do this as there's surely easier/better testing environments available, but this way it's possible.

Control testing

baseline :: (ca a, Eq b, Show b) => String -> a -> CompParams ca b Source

Specify a sample baseline value to benchmark and test against (such that the result of applying the function to this a is what everything should match).

You shouldn't specify this more than once, nor mix it with noTests or testWith.

testWith :: (b -> Assertion) -> CompParams ca b Source

Specify a predicate that all results should satisfy.

Note that the last statement between testWith, baseline and noTests "wins" in specifying which testing (if any) to do.

noTests :: CompParams ca b Source

Don't run any tests. This isn't recommended, but could be useful if all you want to do is run comparisons (potentially because no meaningful tests are possible).

Specify comparisons

type Comparison ca b = ComparisonM ca b () Source

A specialised monad used solely for running comparisons.

No lifting is permitted; the only operations permitted are comp, compBench and compTest.

comp :: ca a => String -> a -> Comparison ca b Source

Benchmark and test (if specified) this value against the specified function.

compBench :: ca a => String -> a -> Comparison ca b Source

Only benchmark (but do not test) this value against the specified function.

compTest :: ca a => String -> a -> Comparison ca b Source

Only test (but do not benchmark) this value against the specified function.

Lower-level types

type SameAs a = (~) a Source

An alias for readability.