{- |
Module:      Test.Tasty.Bench
Copyright:   (c) 2021 Andrew Lelechenko
License:     MIT

Featherlight benchmark framework (only one file!) for performance
measurement with API
mimicking [@criterion@](http://hackage.haskell.org/package/criterion)
and [@gauge@](http://hackage.haskell.org/package/gauge).
A prominent feature is built-in comparison against previous runs
and between benchmarks.

=== How lightweight is it?

There is only one source file "Test.Tasty.Bench" and no non-boot
dependencies except [@tasty@](http://hackage.haskell.org/package/tasty). So
if you already depend on @tasty@ for a test suite, there is nothing else
to install.

Compare this to @criterion@ (10+ modules, 50+ dependencies) and @gauge@
(40+ modules, depends on @basement@ and @vector@). A build on a clean machine is up to 16x
faster than @criterion@ and up to 4x faster than @gauge@. A build without dependencies
is up to 6x faster than @criterion@ and up to 8x faster than @gauge@.

@tasty-bench@ is a native Haskell library and works everywhere, where GHC
does. We support a full range of architectures (@i386@, @amd64@, @armhf@,
@arm64@, @ppc64le@, @s390x@) and operating systems (Linux, Windows, macOS,
FreeBSD, OpenBSD, NetBSD), plus any GHC from 7.0 to 9.6.

=== How is it possible?

Our benchmarks are literally regular @tasty@ tests, so we can leverage
all existing machinery for command-line options, resource management,
structuring, listing and filtering benchmarks, running and reporting
results. It also means that @tasty-bench@ can be used in conjunction
with other @tasty@ ingredients.

Unlike @criterion@ and @gauge@ we use a very simple statistical model
described below. This is arguably a questionable choice, but it works
pretty well in practice. A rare developer is sufficiently well-versed in
probability theory to make sense and use of all numbers generated by
@criterion@.

=== How to switch?

<https://cabal.readthedocs.io/en/3.4/cabal-package.html#pkg-field-mixins Cabal mixins>
allow to taste @tasty-bench@ instead of @criterion@ or @gauge@ without
changing a single line of code:

> cabal-version: 2.0
>
> benchmark foo
>   ...
>   build-depends:
>     tasty-bench
>   mixins:
>     tasty-bench (Test.Tasty.Bench as Criterion, Test.Tasty.Bench as Criterion.Main, Test.Tasty.Bench as Gauge, Test.Tasty.Bench as Gauge.Main)

This works vice versa as well: if you use @tasty-bench@, but at some
point need a more comprehensive statistical analysis, it is easy to
switch temporarily back to @criterion@.

=== How to write a benchmark?

Benchmarks are declared in a separate section of @cabal@ file:

> cabal-version:   2.0
> name:            bench-fibo
> version:         0.0
> build-type:      Simple
> synopsis:        Example of a benchmark
>
> benchmark bench-fibo
>   main-is:       BenchFibo.hs
>   type:          exitcode-stdio-1.0
>   build-depends: base, tasty-bench
>   ghc-options:   "-with-rtsopts=-A32m"
>   if impl(ghc >= 8.6)
>     ghc-options: -fproc-alignment=64

And here is @BenchFibo.hs@:

> import Test.Tasty.Bench
>
> fibo :: Int -> Integer
> fibo n = if n < 2 then toInteger n else fibo (n - 1) + fibo (n - 2)
>
> main :: IO ()
> main = defaultMain
>   [ bgroup "Fibonacci numbers"
>     [ bench "fifth"     $ nf fibo  5
>     , bench "tenth"     $ nf fibo 10
>     , bench "twentieth" $ nf fibo 20
>     ]
>   ]

Since @tasty-bench@ provides an API compatible with @criterion@, one can
refer to
<http://www.serpentine.com/criterion/tutorial.html#how-to-write-a-benchmark-suite its documentation>
for more examples.

=== How to read results?

Running the example above (@cabal@ @bench@ or @stack@ @bench@) results in
the following output:

> All
>   Fibonacci numbers
>     fifth:     OK (2.13s)
>        63 ns ± 3.4 ns
>     tenth:     OK (1.71s)
>       809 ns ±  73 ns
>     twentieth: OK (3.39s)
>       104 μs ± 4.9 μs
>
> All 3 tests passed (7.25s)

The output says that, for instance, the first benchmark was repeatedly
executed for 2.13 seconds (wall-clock time), its predicted mean CPU time was
63 nanoseconds and means of individual samples do not often diverge from it
further than ±3.4 nanoseconds (double standard deviation). Take standard
deviation numbers with a grain of salt; there are lies, damned lies, and
statistics.

=== Wall-clock time vs. CPU time

What time are we talking about?
Both @criterion@ and @gauge@ by default report wall-clock time, which is
affected by any other application which runs concurrently.
Ideally benchmarks are executed on a dedicated server without any other load,
but — let's face the truth — most of developers run benchmarks
on a laptop with a hundred other services and a window manager, and
watch videos while waiting for benchmarks to finish. That's the cause
of a notorious "variance introduced by outliers: 88% (severely inflated)" warning.

To alleviate this issue @tasty-bench@ measures CPU time by 'getCPUTime'
instead of wall-clock time by default.
It does not provide a perfect isolation from other processes (e. g.,
if CPU cache is spoiled by others, populating data back from RAM
is your burden), but is a bit more stable.

Caveat: this means that for multithreaded algorithms
@tasty-bench@ reports total elapsed CPU time across all cores, while
@criterion@ and @gauge@ print maximum of core's wall-clock time.
It also means that by default @tasty-bench@ does not measure time spent out of process,
e. g., calls to other executables. To work around this limitation
use @--time-mode@ command-line option or set it locally via 'TimeMode' option.

=== Statistical model

Here is a procedure used by @tasty-bench@ to measure execution time:

1.  Set \( n \leftarrow 1 \).
2.  Measure execution time \( t_n \) of \( n \) iterations and execution time
    \( t_{2n} \) of \( 2n \) iterations.
3.  Find \( t \) which minimizes deviation of \( (nt, 2nt) \) from
    \( (t_n, t_{2n}) \), namely \( t \leftarrow (t_n + 2t_{2n}) / 5n \).
4.  If deviation is small enough (see @--stdev@ below)
    or time is running out soon (see @--timeout@ below),
    return \( t \) as a mean execution time.
5.  Otherwise set \( n \leftarrow 2n \) and jump back to Step 2.

This is roughly similar to the linear regression approach which
@criterion@ takes, but we fit only two last points. This allows us to
simplify away all heavy-weight statistical analysis. More importantly,
earlier measurements, which are presumably shorter and noisier, do not
affect overall result. This is in contrast to @criterion@, which fits
all measurements and is biased to use more data points corresponding to
shorter runs (it employs \( n \leftarrow 1.05n \) progression).

Mean time and its deviation does not say much about the
distribution of individual timings. E. g., imagine a computation which
(according to a coarse system timer) takes either 0 ms or 1 ms with equal
probability. While one would be able to establish that its mean time is 0.5 ms
with a very small deviation, this does not imply that individual measurements
are anywhere near 0.5 ms. Even assuming an infinite precision of a system
timer, the distribution of individual times is not known to be
<https://en.wikipedia.org/wiki/Normal_distribution normal>.

Obligatory disclaimer: statistics is a tricky matter, there is no
one-size-fits-all approach. In the absence of a good theory simplistic
approaches are as (un)sound as obscure ones. Those who seek statistical
soundness should rather collect raw data and process it themselves using
a proper statistical toolbox. Data reported by @tasty-bench@ is only of
indicative and comparative significance.

=== Memory usage

Configuring RTS to collect GC statistics
(e. g., via @cabal@ @bench@ @--benchmark-options@ @\'+RTS@ @-T\'@ or
@stack@ @bench@ @--ba@ @\'+RTS@ @-T\'@) enables @tasty-bench@ to estimate and
report memory usage:

> All
>   Fibonacci numbers
>     fifth:     OK (2.13s)
>        63 ns ± 3.4 ns, 223 B  allocated,   0 B  copied, 2.0 MB peak memory
>     tenth:     OK (1.71s)
>       809 ns ±  73 ns, 2.3 KB allocated,   0 B  copied, 4.0 MB peak memory
>     twentieth: OK (3.39s)
>       104 μs ± 4.9 μs, 277 KB allocated,  59 B  copied, 5.0 MB peak memory
>
> All 3 tests passed (7.25s)

This data is reported as per 'RTSStats' fields: 'allocated_bytes', 'copied_bytes'
and 'max_mem_in_use_bytes'.

=== Combining tests and benchmarks

When optimizing an existing function, it is important to check that its
observable behavior remains unchanged. One can rebuild both tests and
benchmarks after each change, but it would be more convenient to run
sanity checks within benchmark itself. Since our benchmarks are
compatible with @tasty@ tests, we can easily do so.

Imagine you come up with a faster function @myFibo@ to generate
Fibonacci numbers:

> import Test.Tasty.Bench
> import Test.Tasty.QuickCheck -- from tasty-quickcheck package
>
> fibo :: Int -> Integer
> fibo n = if n < 2 then toInteger n else fibo (n - 1) + fibo (n - 2)
>
> myFibo :: Int -> Integer
> myFibo n = if n < 3 then toInteger n else myFibo (n - 1) + myFibo (n - 2)
>
> main :: IO ()
> main = Test.Tasty.Bench.defaultMain -- not Test.Tasty.defaultMain
>   [ bench "fibo   20" $ nf fibo   20
>   , bench "myFibo 20" $ nf myFibo 20
>   , testProperty "myFibo = fibo" $ \n -> fibo n === myFibo n
>   ]

This outputs:

> All
>   fibo   20:     OK (3.02s)
>     104 μs ± 4.9 μs
>   myFibo 20:     OK (1.99s)
>      71 μs ± 5.3 μs
>   myFibo = fibo: FAIL
>     *** Failed! Falsified (after 5 tests and 1 shrink):
>     2
>     1 /= 2
>     Use --quickcheck-replay=927711 to reproduce.
>
> 1 out of 3 tests failed (5.03s)

We see that @myFibo@ is indeed significantly faster than @fibo@, but
unfortunately does not do the same thing. One should probably look for
another way to speed up generation of Fibonacci numbers.

=== Troubleshooting

-   If benchmarks take too long, set @--timeout@ to limit execution time
    of individual benchmarks, and @tasty-bench@ will do its best to fit
    into a given time frame. Without @--timeout@ we rerun benchmarks until
    achieving a target precision set by @--stdev@, which in a noisy
    environment of a modern laptop with GUI may take a lot of time.

    While @criterion@ runs each benchmark at least for 5 seconds,
    @tasty-bench@ is happy to conclude earlier, if it does not
    compromise the quality of results. In our experiments @tasty-bench@
    suites tend to finish earlier, even if some individual benchmarks
    take longer than with @criterion@.

    A common source of noisiness is garbage collection. Setting a larger
    allocation area (/nursery/) is often a good idea, either via
    @cabal@ @bench@ @--benchmark-options@ @\'+RTS@ @-A32m\'@ or
    @stack@ @bench@ @--ba@ @\'+RTS@ @-A32m\'@. Alternatively bake it into @cabal@
    file as @ghc-options:@ @\"-with-rtsopts=-A32m\"@.

    For GHC ≥ 8.10 consider switching benchmarks to a non-moving garbage collector,
    because it decreases GC pauses and corresponding noise: @+RTS@ @--nonmoving-gc@.

-   Never compile benchmarks with @-fstatic-argument-transformation@, because it
    breaks a trick we use to force GHC into reevaluation of the same function application
    over and over again.

-   If benchmark results look malformed like below, make sure that you
    are invoking @Test.Tasty.Bench.@'Test.Tasty.Bench.defaultMain' and not
    @Test.Tasty.@'Test.Tasty.defaultMain' (the difference is 'consoleBenchReporter'
    vs. 'consoleTestReporter'):

    > All
    >   fibo 20:       OK (1.46s)
    >     Response {respEstimate = Estimate {estMean = Measurement {measTime = 87496728, measAllocs = 0, measCopied = 0}, estStdev = 694487}, respIfSlower = FailIfSlower Infinity, respIfFaster = FailIfFaster Infinity}

-   If benchmarks fail with an error message

    > Unhandled resource. Probably a bug in the runner you're using.

    or

    > Unexpected state of the resource (NotCreated) in getResource. Report as a tasty bug.

    this is likely caused by 'env' or 'envWithCleanup' affecting
    benchmarks structure. You can use 'env' to read test data from 'IO',
    but not to read benchmark names or affect their hierarchy in other
    way. This is a fundamental restriction of @tasty@ to list and filter
    benchmarks without launching missiles.

-   If benchmarks fail with @Test dependencies form a loop@
    or @Test dependencies have cycles@, this is likely
    because of 'bcompare', which compares a benchmark with itself.
    Locating a benchmark in a global environment may be tricky, please refer to
    [@tasty@ documentation](https://github.com/UnkindPartition/tasty#patterns) for details
    and consider using 'locateBenchmark'.

-   When seeing

    > This benchmark takes more than 100 seconds. Consider setting --timeout, if this is unexpected (or to silence this warning).

    do follow the advice: abort benchmarks and pass @-t100@ or similar. Unless you are
    benchmarking a very computationally expensive function, a single benchmark should
    stabilize after a couple of seconds. This warning is a sign that your environment
    is too noisy, in which case @tasty-bench@ will continue trying with exponentially
    longer intervals, often unproductively.

-   The following error can be thrown when benchmarks are built with
    @ghc-options: -threaded@:

    > Benchmarks must not be run concurrently. Please pass -j1 and/or avoid +RTS -N.

    The underlying cause is that @tasty@ runs tests concurrently, which is harmful
    for reliable performance measurements. Make sure to use @tasty-bench >= 0.3.4@
    and invoke @Test.Tasty.Bench.@'Test.Tasty.Bench.defaultMain' and not
    @Test.Tasty.@`Test.Tasty.defaultMain`. Note that 'localOption' ('NumThreads' 1)
    quashes the warning, but does not eliminate the cause.

=== Isolating interfering benchmarks

One difficulty of benchmarking in Haskell is that it is hard to isolate
benchmarks so that they do not interfere. Changing the order of
benchmarks or skipping some of them has an effect on heap's layout and
thus affects garbage collection. This issue is well attested in
<https://github.com/haskell/criterion/issues/166 both>
<https://github.com/haskell/criterion/issues/60 criterion> and
<https://github.com/vincenthz/hs-gauge/issues/2 gauge>.

Usually (but not always) skipping some benchmarks speeds up remaining
ones. That's because once a benchmark allocated heap which for some
reason was not promptly released afterwards (e. g., it forced a
top-level thunk in an underlying library), all further benchmarks are
slowed down by garbage collector processing this additional amount of
live data over and over again.

There are several mitigation strategies. First of all, giving garbage
collector more breathing space by @+RTS@ @-A32m@ (or more) is often good
enough.

Further, avoid using top-level bindings to store large test data. Once
such thunks are forced, they remain allocated forever, which affects
detrimentally subsequent unrelated benchmarks. Treat them as external
data, supplied via 'env': instead of

> largeData :: String
> largeData = replicate 1000000 'a'
>
> main :: IO ()
> main = defaultMain
>   [ bench "large" $ nf length largeData, ... ]

use

> import Control.DeepSeq (force)
> import Control.Exception (evaluate)
>
> main :: IO ()
> main = defaultMain
>   [ env (evaluate (force (replicate 1000000 'a'))) $ \largeData ->
>     bench "large" $ nf length largeData, ... ]

Finally, as an ultimate measure to reduce interference between
benchmarks, one can run each of them in a separate process. We do not
quite recommend this approach, but if you are desperate, here is how:

> cabal run -v0 all:benches -- -l | sed -e 's/[\"]/\\\\\\&/g' | while read -r name; do cabal run -v0 all:benches -- -p '$0 == "'"$name"'"'; done

This assumes that there is a single benchmark suite in the project
and that benchmark names do not contain newlines.

=== Comparison against baseline

One can compare benchmark results against an earlier run in an automatic way.

When using this feature, it's especially important to compile benchmarks with
@ghc-options:@ [@-fproc-alignment@](https://downloads.haskell.org/ghc/latest/docs/users_guide/debugging.html#ghc-flag--fproc-alignment)@=64@, otherwise results could be skewed by
intermittent changes in cache-line alignment.

Firstly, run @tasty-bench@ with
@--csv@ @FILE@ key to dump results to @FILE@ in CSV format
(it could be a good idea to set smaller @--stdev@, if possible):

> Name,Mean (ps),2*Stdev (ps)
> All.Fibonacci numbers.fifth,48453,4060
> All.Fibonacci numbers.tenth,637152,46744
> All.Fibonacci numbers.twentieth,81369531,3342646

Now modify implementation and rerun benchmarks with @--baseline@ @FILE@
key. This produces a report as follows:

> All
>   Fibonacci numbers
>     fifth:     OK (0.44s)
>        53 ns ± 2.7 ns,  8% more than baseline
>     tenth:     OK (0.33s)
>       641 ns ±  59 ns,       same as baseline
>     twentieth: OK (0.36s)
>        77 μs ± 6.4 μs,  5% less than baseline
>
> All 3 tests passed (1.50s)

You can also fail benchmarks, which deviate too far from baseline, using
@--fail-if-slower@ and @--fail-if-faster@ options. For example, setting
both of them to 6 will fail the first benchmark above (because it is
more than 6% slower), but the last one still succeeds (even while it is
measurably faster than baseline, deviation is less than 6%). Consider
also using @--hide-successes@ to show only problematic benchmarks, or
even [@tasty-rerun@](http://hackage.haskell.org/package/tasty-rerun)
package to focus on rerunning failing items only.

If you wish to compare two CSV reports non-interactively, here is a handy @awk@ incantation:

> awk 'BEGIN{FS=",";OFS=",";print "Name,Old,New,Ratio"}FNR==1{trueNF=NF;next}NF<trueNF{print "Benchmark names should not contain newlines";exit 1}FNR==NR{oldTime=$(NF-trueNF+2);NF-=trueNF-1;a[$0]=oldTime;next}{newTime=$(NF-trueNF+2);NF-=trueNF-1;print $0,a[$0],newTime,newTime/a[$0];gs+=log(newTime/a[$0]);gc++}END{if(gc>0)print "Geometric mean,,",exp(gs/gc)}' old.csv new.csv

Note that columns in CSV report are different from what @criterion@ or @gauge@
would produce. If names do not contain commas, missing columns can be faked this way:

> awk 'BEGIN{FS=",";OFS=",";print "Name,Mean,MeanLB,MeanUB,Stddev,StddevLB,StddevUB"}NR==1{trueNF=NF;next}NF<trueNF{print $0;next}{mean=$(NF-trueNF+2);stddev=$(NF-trueNF+3);NF-=trueNF-1;print $0,mean/1e12,mean/1e12,mean/1e12,stddev/2e12,stddev/2e12,stddev/2e12}'

To fake @gauge@ in @--csvraw@ mode use

> awk 'BEGIN{FS=",";OFS=",";print "name,iters,time,cycles,cpuTime,utime,stime,maxrss,minflt,majflt,nvcsw,nivcsw,allocated,numGcs,bytesCopied,mutatorWallSeconds,mutatorCpuSeconds,gcWallSeconds,gcCpuSeconds"}NR==1{trueNF=NF;next}NF<trueNF{print $0;next}{mean=$(NF-trueNF+2);fourth=$(NF-trueNF+4);fifth=$(NF-trueNF+5);sixth=$(NF-trueNF+6);NF-=trueNF-1;print $0,1,mean/1e12,0,mean/1e12,mean/1e12,0,sixth+0,0,0,0,0,fourth+0,0,fifth+0,0,0,0,0}'

=== Comparison between benchmarks

You can also compare benchmarks to each other without any
external tools, all in the comfort of your terminal.

> import Test.Tasty.Bench
>
> fibo :: Int -> Integer
> fibo n = if n < 2 then toInteger n else fibo (n - 1) + fibo (n - 2)
>
> main :: IO ()
> main = defaultMain
>   [ bgroup "Fibonacci numbers"
>     [ bcompare "tenth"  $ bench "fifth"     $ nf fibo  5
>     ,                     bench "tenth"     $ nf fibo 10
>     , bcompare "tenth"  $ bench "twentieth" $ nf fibo 20
>     ]
>   ]

This produces a report, comparing mean times of @fifth@ and @twentieth@
to @tenth@:

> All
>   Fibonacci numbers
>     fifth:     OK (16.56s)
>       121 ns ± 2.6 ns, 0.08x
>     tenth:     OK (6.84s)
>       1.6 μs ±  31 ns
>     twentieth: OK (6.96s)
>       203 μs ± 4.1 μs, 128.36x

To locate a baseline benchmark in a larger suite use 'locateBenchmark'.

One can leverage comparisons between benchmarks to implement portable performance
tests, expressing properties like "this algorithm must be at least twice faster
than that one" or "this operation should not be more than thrice slower than that".
This can be achieved with 'bcompareWithin', which takes an acceptable interval
of performance as an argument.

=== Plotting results

Users can dump results into CSV with @--csv@ @FILE@ and plot them using
@gnuplot@ or other software. But for convenience there is also a
built-in quick-and-dirty SVG plotting feature, which can be invoked by
passing @--svg@ @FILE@. Here is a sample of its output:

![Plotting](example.svg)

=== Build flags

Build flags are a brittle subject and users do not normally need to touch them.

* If you find yourself in an environment, where @tasty@ is not available and you
  have access to boot packages only, you can still use @tasty-bench@! Just copy
  @Test\/Tasty\/Bench.hs@ to your project (imagine it like a header-only C library).
  It will provide you with functions to build 'Benchmarkable' and run them manually
  via 'measureCpuTime'. This mode of operation can be also configured
  by disabling Cabal flag @tasty@.

* If results are amiss or oscillate wildly and adjusting @--timeout@ and @--stdev@
  does not help, you may be interested to investigate individual timings of
  successive runs by enabling Cabal flag @debug@. This will pipe raw data into @stderr@.

=== Command-line options

Use @--help@ to list all command-line options.

[@-p@, @--pattern@]:

    This is a standard @tasty@ option, which allows filtering benchmarks
    by a pattern or @awk@ expression. Please refer
    to [@tasty@ documentation](https://github.com/UnkindPartition/tasty#patterns)
    for details.

[@-t@, @--timeout@]:

    This is a standard @tasty@ option, setting timeout for individual
    benchmarks in seconds. Use it when benchmarks tend to take too long:
    @tasty-bench@ will make an effort to report results (even if of
    subpar quality) before timeout. Setting timeout too tight
    (insufficient for at least three iterations) will result in a
    benchmark failure. One can adjust it locally for a group
    of benchmarks, e. g., 'localOption' ('mkTimeout' 100000000) for 100 seconds.

[@--stdev@]:

    Target relative standard deviation of measurements in percents (5%
    by default). Large values correspond to fast and loose benchmarks,
    and small ones to long and precise.
    It can also be adjusted locally for a group of benchmarks,
    e. g., 'localOption' ('RelStDev' 0.02).
    If benchmarking takes far too long, consider setting @--timeout@,
    which will interrupt benchmarks,
    potentially before reaching the target deviation.

[@--csv@]:

    File to write results in CSV format.

[@--baseline@]:

    File to read baseline results in CSV format (as produced by
    @--csv@).

[@--fail-if-slower@, @--fail-if-faster@]:

    Upper bounds of acceptable slow down \/ speed up in percents. If a
    benchmark is unacceptably slower \/ faster than baseline (see
    @--baseline@), it will be reported as failed. Can be used in
    conjunction with a standard @tasty@ option @--hide-successes@ to
    show only problematic benchmarks.
    Both options can be adjusted locally for a group of benchmarks,
    e. g., 'localOption' ('FailIfSlower' 0.10).

[@--svg@]:

    File to plot results in SVG format.

[@--time-mode@]:

    Whether to measure CPU time (@cpu@, default) or wall-clock time (@wall@).

[@+RTS@ @-T@]:

    Estimate and report memory usage.

=== Custom command-line options

As usual with @tasty@, it is easy to extend benchmarks with custom command-line options.
Here is an example:

> import Data.Proxy
> import Test.Tasty.Bench
> import Test.Tasty.Ingredients.Basic
> import Test.Tasty.Options
> import Test.Tasty.Runners
>
> newtype RandomSeed = RandomSeed Int
>
> instance IsOption RandomSeed where
>   defaultValue = RandomSeed 42
>   parseValue = fmap RandomSeed . safeRead
>   optionName = pure "seed"
>   optionHelp = pure "Random seed used in benchmarks"
>
> main :: IO ()
> main = do
>   let customOpts  = [Option (Proxy :: Proxy RandomSeed)]
>       ingredients = includingOptions customOpts : benchIngredients
>   opts <- parseOptions ingredients benchmarks
>   let RandomSeed seed = lookupOption opts
>   defaultMainWithIngredients ingredients benchmarks
>
> benchmarks :: Benchmark
> benchmarks = bgroup "All" []

-}

{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}

module Test.Tasty.Bench
  (
#ifdef MIN_VERSION_tasty
  -- * Running 'Benchmark'
    defaultMain
  , Benchmark
  , bench
  , bgroup
  , bcompare
  , bcompareWithin
  , env
  , envWithCleanup
  ,
#endif
  -- * Creating 'Benchmarkable'
    Benchmarkable(..)
  , nf
  , whnf
  , nfIO
  , whnfIO
  , nfAppIO
  , whnfAppIO
  , measureCpuTime
  , measureCpuTimeAndStDev
#ifdef MIN_VERSION_tasty
  -- * Ingredients
  , benchIngredients
  , consoleBenchReporter
  , csvReporter
  , svgReporter
  , RelStDev(..)
  , FailIfSlower(..)
  , FailIfFaster(..)
  , CsvPath(..)
  , BaselinePath(..)
  , SvgPath(..)
  , TimeMode(..)
  -- * Utilities
  , locateBenchmark
  , mapLeafBenchmarks
#else
  , Timeout(..)
  , RelStDev(..)
#endif
  ) where

import Prelude hiding (Int, Integer)
import qualified Prelude
import Control.Applicative
import Control.Arrow (first, second)
import Control.DeepSeq (NFData, force)
import Control.Exception (bracket, evaluate)
import Control.Monad (void, unless, guard, (>=>), when)
import Data.Data (Typeable)
import Data.Foldable (foldMap, traverse_)
import Data.Int (Int64)
import Data.IORef
import Data.List (intercalate, stripPrefix, isPrefixOf, genericLength, genericDrop, foldl1')
import Data.Maybe (fromMaybe)
import Data.Monoid (All(..), Any(..))
import Data.Proxy
import Data.Traversable (forM)
import Data.Word (Word64)
import GHC.Conc
#if MIN_VERSION_base(4,5,0)
import GHC.IO.Encoding
#endif
#if MIN_VERSION_base(4,6,0)
import GHC.Stats
#endif
import System.CPUTime
import System.Exit
import System.IO
import System.IO.Unsafe
import System.Mem
import Text.Printf

#ifdef DEBUG
import Debug.Trace
#endif

#ifdef MIN_VERSION_tasty
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid (Monoid(..))
#endif
#if MIN_VERSION_base(4,9,0)
import Data.Semigroup (Semigroup(..))
#endif
#if MIN_VERSION_containers(0,5,0)
import qualified Data.IntMap.Strict as IM
#else
import qualified Data.IntMap as IM
#endif
import Data.IntMap (IntMap)
import Data.Sequence (Seq, (<|))
import qualified Data.Sequence as Seq
import qualified Data.Set as S
import Test.Tasty hiding (defaultMain)
import qualified Test.Tasty
import Test.Tasty.Ingredients
import Test.Tasty.Ingredients.ConsoleReporter
import Test.Tasty.Options
import Test.Tasty.Patterns.Eval (eval, asB, withFields)
import Test.Tasty.Patterns.Types (Expr (And, Field, IntLit, NF, StringLit, Sub))
import qualified Test.Tasty.Patterns.Types as Patterns
import Test.Tasty.Providers
import Test.Tasty.Runners
#endif

#if defined(mingw32_HOST_OS)
import Data.Word (Word32)
#endif

#if MIN_VERSION_ghc_prim(0,3,1)
import GHC.Types (SPEC(..))
#else
import GHC.Exts (SpecConstrAnnotation(..))

data SPEC = SPEC | SPEC2
{-# ANN type SPEC ForceSpecConstr #-}
#endif

#ifndef MIN_VERSION_tasty
data Timeout
  = Timeout
    Prelude.Integer -- ^ number of microseconds (e. g., 200000)
    String          -- ^ textual representation (e. g., @"0.2s"@)
  | NoTimeout
  deriving (Show)
#endif


-- | In addition to @--stdev@ command-line option,
-- one can adjust target relative standard deviation
-- for individual benchmarks and groups of benchmarks
-- using 'adjustOption' and 'localOption'.
--
-- E. g., set target relative standard deviation to 2% as follows:
--
-- > import Test.Tasty (localOption)
-- > localOption (RelStDev 0.02) (bgroup [...])
--
-- If you set 'RelStDev' to infinity,
-- a benchmark will be executed
-- only once and its standard deviation will be recorded as zero.
-- This is rather a blunt approach, but it might be a necessary evil
-- for extremely long benchmarks. If you wish to run all benchmarks
-- only once, use command-line option @--stdev@ @Infinity@.
--
-- @since 0.2
newtype RelStDev = RelStDev Double
  deriving (Int -> RelStDev -> ShowS
[RelStDev] -> ShowS
RelStDev -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RelStDev] -> ShowS
$cshowList :: [RelStDev] -> ShowS
show :: RelStDev -> String
$cshow :: RelStDev -> String
showsPrec :: Int -> RelStDev -> ShowS
$cshowsPrec :: Int -> RelStDev -> ShowS
Show, ReadPrec [RelStDev]
ReadPrec RelStDev
Int -> ReadS RelStDev
ReadS [RelStDev]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RelStDev]
$creadListPrec :: ReadPrec [RelStDev]
readPrec :: ReadPrec RelStDev
$creadPrec :: ReadPrec RelStDev
readList :: ReadS [RelStDev]
$creadList :: ReadS [RelStDev]
readsPrec :: Int -> ReadS RelStDev
$creadsPrec :: Int -> ReadS RelStDev
Read, Typeable)

-- | Whether to measure CPU time or wall-clock time.
-- Normally 'CpuTime' is a better option (and default),
-- but consider switching to 'WallTime'
-- to measure multithreaded algorithms or time spent in external processes.
--
-- One can switch the default measurement mode globally
-- using @--time-mode@ command-line option,
-- but it is usually better to adjust the mode locally:
--
-- > import Test.Tasty (localOption)
-- > localOption WallTime (bgroup [...])
--
-- section of your cabal file.
--
-- @since 0.3.2
data TimeMode = CpuTime
  -- ^ Measure CPU time.
#ifdef MIN_VERSION_tasty
  | WallTime
  -- ^ Measure wall-clock time.
#endif
  deriving (Typeable)

#ifdef MIN_VERSION_tasty
instance IsOption RelStDev where
  defaultValue :: RelStDev
defaultValue = Double -> RelStDev
RelStDev Double
0.05
  parseValue :: String -> Maybe RelStDev
parseValue = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Double -> RelStDev
RelStDev forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe Double
parsePositivePercents
  optionName :: Tagged RelStDev String
optionName = forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"stdev"
  optionHelp :: Tagged RelStDev String
optionHelp = forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"Target relative standard deviation of measurements in percents (5 by default). Large values correspond to fast and loose benchmarks, and small ones to long and precise. If it takes far too long, consider setting --timeout, which will interrupt benchmarks, potentially before reaching the target deviation."

-- | In addition to @--fail-if-slower@ command-line option,
-- one can adjust an upper bound of acceptable slow down
-- in comparison to baseline for
-- individual benchmarks and groups of benchmarks
-- using 'adjustOption' and 'localOption'.
--
-- E. g., set upper bound of acceptable slow down to 10% as follows:
--
-- > import Test.Tasty (localOption)
-- > localOption (FailIfSlower 0.10) (bgroup [...])
--
-- @since 0.2
newtype FailIfSlower = FailIfSlower Double
  deriving (Int -> FailIfSlower -> ShowS
[FailIfSlower] -> ShowS
FailIfSlower -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FailIfSlower] -> ShowS
$cshowList :: [FailIfSlower] -> ShowS
show :: FailIfSlower -> String
$cshow :: FailIfSlower -> String
showsPrec :: Int -> FailIfSlower -> ShowS
$cshowsPrec :: Int -> FailIfSlower -> ShowS
Show, ReadPrec [FailIfSlower]
ReadPrec FailIfSlower
Int -> ReadS FailIfSlower
ReadS [FailIfSlower]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FailIfSlower]
$creadListPrec :: ReadPrec [FailIfSlower]
readPrec :: ReadPrec FailIfSlower
$creadPrec :: ReadPrec FailIfSlower
readList :: ReadS [FailIfSlower]
$creadList :: ReadS [FailIfSlower]
readsPrec :: Int -> ReadS FailIfSlower
$creadsPrec :: Int -> ReadS FailIfSlower
Read, Typeable)

instance IsOption FailIfSlower where
  defaultValue :: FailIfSlower
defaultValue = Double -> FailIfSlower
FailIfSlower (Double
1.0 forall a. Fractional a => a -> a -> a
/ Double
0.0)
  parseValue :: String -> Maybe FailIfSlower
parseValue = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Double -> FailIfSlower
FailIfSlower forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe Double
parsePositivePercents
  optionName :: Tagged FailIfSlower String
optionName = forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"fail-if-slower"
  optionHelp :: Tagged FailIfSlower String
optionHelp = forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"Upper bound of acceptable slow down in percents. If a benchmark is unacceptably slower than baseline (see --baseline), it will be reported as failed."

-- | In addition to @--fail-if-faster@ command-line option,
-- one can adjust an upper bound of acceptable speed up
-- in comparison to baseline for
-- individual benchmarks and groups of benchmarks
-- using 'adjustOption' and 'localOption'.
--
-- E. g., set upper bound of acceptable speed up to 10% as follows:
--
-- > import Test.Tasty (localOption)
-- > localOption (FailIfFaster 0.10) (bgroup [...])
--
-- @since 0.2
newtype FailIfFaster = FailIfFaster Double
  deriving (Int -> FailIfFaster -> ShowS
[FailIfFaster] -> ShowS
FailIfFaster -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FailIfFaster] -> ShowS
$cshowList :: [FailIfFaster] -> ShowS
show :: FailIfFaster -> String
$cshow :: FailIfFaster -> String
showsPrec :: Int -> FailIfFaster -> ShowS
$cshowsPrec :: Int -> FailIfFaster -> ShowS
Show, ReadPrec [FailIfFaster]
ReadPrec FailIfFaster
Int -> ReadS FailIfFaster
ReadS [FailIfFaster]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FailIfFaster]
$creadListPrec :: ReadPrec [FailIfFaster]
readPrec :: ReadPrec FailIfFaster
$creadPrec :: ReadPrec FailIfFaster
readList :: ReadS [FailIfFaster]
$creadList :: ReadS [FailIfFaster]
readsPrec :: Int -> ReadS FailIfFaster
$creadsPrec :: Int -> ReadS FailIfFaster
Read, Typeable)

instance IsOption FailIfFaster where
  defaultValue :: FailIfFaster
defaultValue = Double -> FailIfFaster
FailIfFaster (Double
1.0 forall a. Fractional a => a -> a -> a
/ Double
0.0)
  parseValue :: String -> Maybe FailIfFaster
parseValue = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Double -> FailIfFaster
FailIfFaster forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe Double
parsePositivePercents
  optionName :: Tagged FailIfFaster String
optionName = forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"fail-if-faster"
  optionHelp :: Tagged FailIfFaster String
optionHelp = forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"Upper bound of acceptable speed up in percents. If a benchmark is unacceptably faster than baseline (see --baseline), it will be reported as failed."

parsePositivePercents :: String -> Maybe Double
parsePositivePercents :: String -> Maybe Double
parsePositivePercents String
xs = do
  Double
x <- forall a. Read a => String -> Maybe a
safeRead String
xs
  forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Double
x forall a. Ord a => a -> a -> Bool
> Double
0)
  forall (f :: * -> *) a. Applicative f => a -> f a
pure (Double
x forall a. Fractional a => a -> a -> a
/ Double
100)

instance IsOption TimeMode where
  defaultValue :: TimeMode
defaultValue = TimeMode
CpuTime
  parseValue :: String -> Maybe TimeMode
parseValue String
v = case String
v of
    String
"cpu" -> forall a. a -> Maybe a
Just TimeMode
CpuTime
    String
"wall" -> forall a. a -> Maybe a
Just TimeMode
WallTime
    String
_ -> forall a. Maybe a
Nothing
  optionName :: Tagged TimeMode String
optionName = forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"time-mode"
  optionHelp :: Tagged TimeMode String
optionHelp = forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"Whether to measure CPU time (\"cpu\") or wall-clock time (\"wall\")"
#if MIN_VERSION_tasty(1,3,0)
  showDefaultValue :: TimeMode -> Maybe String
showDefaultValue TimeMode
m = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ case TimeMode
m of
    TimeMode
CpuTime -> String
"cpu"
    TimeMode
WallTime -> String
"wall"
#endif
#endif

-- | Something that can be benchmarked, produced by 'nf', 'whnf', 'nfIO', 'whnfIO',
-- 'nfAppIO', 'whnfAppIO' below.
--
-- Drop-in replacement for @Criterion.@'Criterion.Benchmarkable' and
-- @Gauge.@'Gauge.Benchmarkable'.
--
-- @since 0.1
newtype Benchmarkable =
    -- | @since 0.3
    Benchmarkable
  { Benchmarkable -> Word64 -> IO ()
unBenchmarkable :: Word64 -> IO () -- ^ Run benchmark given number of times.
  } deriving (Typeable)

#ifdef MIN_VERSION_tasty

-- | 'defaultMain' forces 'setLocaleEncoding' to 'utf8', but users might
-- be running benchmarks outside of it (e. g., via 'defaultMainWithIngredients').
supportsUnicode :: Bool
#if MIN_VERSION_base(4,5,0)
supportsUnicode :: Bool
supportsUnicode = forall a. Int -> [a] -> [a]
take Int
3 (TextEncoding -> String
textEncodingName TextEncoding
enc) forall a. Eq a => a -> a -> Bool
== String
"UTF"
#if defined(mingw32_HOST_OS)
  && unsafePerformIO getConsoleOutputCP == 65001
#endif
  where
    enc :: TextEncoding
enc = forall a. IO a -> a
unsafePerformIO IO TextEncoding
getLocaleEncoding
#else
supportsUnicode = False
#endif
{-# NOINLINE supportsUnicode #-}

mu :: Char
mu :: Char
mu = if Bool
supportsUnicode then Char
'μ' else Char
'u'

pm :: String
pm :: String
pm = if Bool
supportsUnicode then String
" ± " else String
" +-"

-- | Show picoseconds, fitting number in 3 characters.
showPicos3 :: Word64 -> String
showPicos3 :: Word64 -> String
showPicos3 Word64
i
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995   = forall r. PrintfType r => String -> r
printf String
"%3.0f ps" Double
t
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995e1 = forall r. PrintfType r => String -> r
printf String
"%3.1f ns" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e3)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995e3 = forall r. PrintfType r => String -> r
printf String
"%3.0f ns" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e3)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995e4 = forall r. PrintfType r => String -> r
printf String
"%3.1f %cs" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e6) Char
mu
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995e6 = forall r. PrintfType r => String -> r
printf String
"%3.0f %cs" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e6) Char
mu
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995e7 = forall r. PrintfType r => String -> r
printf String
"%3.1f ms" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e9)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995e9 = forall r. PrintfType r => String -> r
printf String
"%3.0f ms" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e9)
  | Bool
otherwise = forall r. PrintfType r => String -> r
printf String
"%4.2f s"  (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e12)
  where
    t :: Double
t = Word64 -> Double
word64ToDouble Word64
i

-- | Show picoseconds, fitting number in 4 characters.
showPicos4 :: Word64 -> String
showPicos4 :: Word64 -> String
showPicos4 Word64
i
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995   = forall r. PrintfType r => String -> r
printf String
"%3.0f  ps"  Double
t
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995e1 = forall r. PrintfType r => String -> r
printf String
"%4.2f ns"  (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e3)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995e2 = forall r. PrintfType r => String -> r
printf String
"%4.1f ns"  (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e3)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995e3 = forall r. PrintfType r => String -> r
printf String
"%3.0f  ns" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e3)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995e4 = forall r. PrintfType r => String -> r
printf String
"%4.2f %cs"  (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e6) Char
mu
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995e5 = forall r. PrintfType r => String -> r
printf String
"%4.1f %cs"  (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e6) Char
mu
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995e6 = forall r. PrintfType r => String -> r
printf String
"%3.0f  %cs" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e6) Char
mu
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995e7 = forall r. PrintfType r => String -> r
printf String
"%4.2f ms"  (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e9)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995e8 = forall r. PrintfType r => String -> r
printf String
"%4.1f ms"  (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e9)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
995e9 = forall r. PrintfType r => String -> r
printf String
"%3.0f  ms" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e9)
  | Bool
otherwise = forall r. PrintfType r => String -> r
printf String
"%4.3f s"   (Double
t forall a. Fractional a => a -> a -> a
/ Double
1e12)
  where
    t :: Double
t = Word64 -> Double
word64ToDouble Word64
i

showBytes :: Word64 -> String
showBytes :: Word64 -> String
showBytes Word64
i
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
1000                 = forall r. PrintfType r => String -> r
printf String
"%3.0f B " Double
t
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
10189                = forall r. PrintfType r => String -> r
printf String
"%3.1f KB" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1024)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
1023488              = forall r. PrintfType r => String -> r
printf String
"%3.0f KB" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1024)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
10433332             = forall r. PrintfType r => String -> r
printf String
"%3.1f MB" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1048576)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
1048051712           = forall r. PrintfType r => String -> r
printf String
"%3.0f MB" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1048576)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
10683731149          = forall r. PrintfType r => String -> r
printf String
"%3.1f GB" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1073741824)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
1073204953088        = forall r. PrintfType r => String -> r
printf String
"%3.0f GB" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1073741824)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
10940140696372       = forall r. PrintfType r => String -> r
printf String
"%3.1f TB" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1099511627776)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
1098961871962112     = forall r. PrintfType r => String -> r
printf String
"%3.0f TB" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1099511627776)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
11202704073084108    = forall r. PrintfType r => String -> r
printf String
"%3.1f PB" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1125899906842624)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
1125336956889202624  = forall r. PrintfType r => String -> r
printf String
"%3.0f PB" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1125899906842624)
  | Double
t forall a. Ord a => a -> a -> Bool
< Double
11471568970838126592 = forall r. PrintfType r => String -> r
printf String
"%3.1f EB" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1152921504606846976)
  | Bool
otherwise                = forall r. PrintfType r => String -> r
printf String
"%3.0f EB" (Double
t forall a. Fractional a => a -> a -> a
/ Double
1152921504606846976)
  where
    t :: Double
t = Word64 -> Double
word64ToDouble Word64
i
#endif

data Measurement = Measurement
  { Measurement -> Word64
measTime   :: !Word64 -- ^ time in picoseconds
  , Measurement -> Word64
measAllocs :: !Word64 -- ^ allocations in bytes
  , Measurement -> Word64
measCopied :: !Word64 -- ^ copied bytes
  , Measurement -> Word64
measMaxMem :: !Word64 -- ^ max memory in use
  } deriving (Int -> Measurement -> ShowS
[Measurement] -> ShowS
Measurement -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Measurement] -> ShowS
$cshowList :: [Measurement] -> ShowS
show :: Measurement -> String
$cshow :: Measurement -> String
showsPrec :: Int -> Measurement -> ShowS
$cshowsPrec :: Int -> Measurement -> ShowS
Show, ReadPrec [Measurement]
ReadPrec Measurement
Int -> ReadS Measurement
ReadS [Measurement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Measurement]
$creadListPrec :: ReadPrec [Measurement]
readPrec :: ReadPrec Measurement
$creadPrec :: ReadPrec Measurement
readList :: ReadS [Measurement]
$creadList :: ReadS [Measurement]
readsPrec :: Int -> ReadS Measurement
$creadsPrec :: Int -> ReadS Measurement
Read)

data Estimate = Estimate
  { Estimate -> Measurement
estMean  :: !Measurement
  , Estimate -> Word64
estStdev :: !Word64  -- ^ standard deviation in picoseconds
  } deriving (Int -> Estimate -> ShowS
[Estimate] -> ShowS
Estimate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Estimate] -> ShowS
$cshowList :: [Estimate] -> ShowS
show :: Estimate -> String
$cshow :: Estimate -> String
showsPrec :: Int -> Estimate -> ShowS
$cshowsPrec :: Int -> Estimate -> ShowS
Show, ReadPrec [Estimate]
ReadPrec Estimate
Int -> ReadS Estimate
ReadS [Estimate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Estimate]
$creadListPrec :: ReadPrec [Estimate]
readPrec :: ReadPrec Estimate
$creadPrec :: ReadPrec Estimate
readList :: ReadS [Estimate]
$creadList :: ReadS [Estimate]
readsPrec :: Int -> ReadS Estimate
$creadsPrec :: Int -> ReadS Estimate
Read)

#ifdef MIN_VERSION_tasty

data WithLoHi a = WithLoHi
  !a      -- payload
  !Double -- lower bound (e. g., 0.9 for -10% speedup)
  !Double -- upper bound (e. g., 1.2 for +20% slowdown)
  deriving (Int -> WithLoHi a -> ShowS
forall a. Show a => Int -> WithLoHi a -> ShowS
forall a. Show a => [WithLoHi a] -> ShowS
forall a. Show a => WithLoHi a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WithLoHi a] -> ShowS
$cshowList :: forall a. Show a => [WithLoHi a] -> ShowS
show :: WithLoHi a -> String
$cshow :: forall a. Show a => WithLoHi a -> String
showsPrec :: Int -> WithLoHi a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> WithLoHi a -> ShowS
Show, ReadPrec [WithLoHi a]
ReadPrec (WithLoHi a)
ReadS [WithLoHi a]
forall a. Read a => ReadPrec [WithLoHi a]
forall a. Read a => ReadPrec (WithLoHi a)
forall a. Read a => Int -> ReadS (WithLoHi a)
forall a. Read a => ReadS [WithLoHi a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WithLoHi a]
$creadListPrec :: forall a. Read a => ReadPrec [WithLoHi a]
readPrec :: ReadPrec (WithLoHi a)
$creadPrec :: forall a. Read a => ReadPrec (WithLoHi a)
readList :: ReadS [WithLoHi a]
$creadList :: forall a. Read a => ReadS [WithLoHi a]
readsPrec :: Int -> ReadS (WithLoHi a)
$creadsPrec :: forall a. Read a => Int -> ReadS (WithLoHi a)
Read)

prettyEstimate :: Estimate -> String
prettyEstimate :: Estimate -> String
prettyEstimate (Estimate Measurement
m Word64
stdev) =
  Word64 -> String
showPicos4 (Measurement -> Word64
measTime Measurement
m)
  forall a. [a] -> [a] -> [a]
++ (if Word64
stdev forall a. Eq a => a -> a -> Bool
== Word64
0 then String
"         " else String
pm forall a. [a] -> [a] -> [a]
++ Word64 -> String
showPicos3 (Word64
2 forall a. Num a => a -> a -> a
* Word64
stdev))

prettyEstimateWithGC :: Estimate -> String
prettyEstimateWithGC :: Estimate -> String
prettyEstimateWithGC (Estimate Measurement
m Word64
stdev) =
  Word64 -> String
showPicos4 (Measurement -> Word64
measTime Measurement
m)
  forall a. [a] -> [a] -> [a]
++ (if Word64
stdev forall a. Eq a => a -> a -> Bool
== Word64
0 then String
",          " else String
pm forall a. [a] -> [a] -> [a]
++ Word64 -> String
showPicos3 (Word64
2 forall a. Num a => a -> a -> a
* Word64
stdev) forall a. [a] -> [a] -> [a]
++ String
", ")
  forall a. [a] -> [a] -> [a]
++ Word64 -> String
showBytes (Measurement -> Word64
measAllocs Measurement
m) forall a. [a] -> [a] -> [a]
++ String
" allocated, "
  forall a. [a] -> [a] -> [a]
++ Word64 -> String
showBytes (Measurement -> Word64
measCopied Measurement
m) forall a. [a] -> [a] -> [a]
++ String
" copied, "
  forall a. [a] -> [a] -> [a]
++ Word64 -> String
showBytes (Measurement -> Word64
measMaxMem Measurement
m) forall a. [a] -> [a] -> [a]
++ String
" peak memory"

csvEstimate :: Estimate -> String
csvEstimate :: Estimate -> String
csvEstimate (Estimate Measurement
m Word64
stdev) = forall a. Show a => a -> String
show (Measurement -> Word64
measTime Measurement
m) forall a. [a] -> [a] -> [a]
++ String
"," forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Word64
2 forall a. Num a => a -> a -> a
* Word64
stdev)

csvEstimateWithGC :: Estimate -> String
csvEstimateWithGC :: Estimate -> String
csvEstimateWithGC (Estimate Measurement
m Word64
stdev) = forall a. Show a => a -> String
show (Measurement -> Word64
measTime Measurement
m) forall a. [a] -> [a] -> [a]
++ String
"," forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Word64
2 forall a. Num a => a -> a -> a
* Word64
stdev)
  forall a. [a] -> [a] -> [a]
++ String
"," forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Measurement -> Word64
measAllocs Measurement
m) forall a. [a] -> [a] -> [a]
++ String
"," forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Measurement -> Word64
measCopied Measurement
m) forall a. [a] -> [a] -> [a]
++ String
"," forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Measurement -> Word64
measMaxMem Measurement
m)
#endif

predict
  :: Measurement -- ^ time for one run
  -> Measurement -- ^ time for two runs
  -> Estimate
predict :: Measurement -> Measurement -> Estimate
predict (Measurement Word64
t1 Word64
a1 Word64
c1 Word64
m1) (Measurement Word64
t2 Word64
a2 Word64
c2 Word64
m2) = Estimate
  { estMean :: Measurement
estMean  = Word64 -> Word64 -> Word64 -> Word64 -> Measurement
Measurement Word64
t (forall {a}. Integral a => a -> a -> a
fit Word64
a1 Word64
a2) (forall {a}. Integral a => a -> a -> a
fit Word64
c1 Word64
c2) (forall a. Ord a => a -> a -> a
max Word64
m1 Word64
m2)
  , estStdev :: Word64
estStdev = forall a b. (RealFrac a, Integral b) => a -> b
truncate (forall a. Floating a => a -> a
sqrt Double
d :: Double)
  }
  where
    fit :: a -> a -> a
fit a
x1 a
x2 = a
x1 forall {a}. Integral a => a -> a -> a
`quot` a
5 forall a. Num a => a -> a -> a
+ a
2 forall a. Num a => a -> a -> a
* (a
x2 forall {a}. Integral a => a -> a -> a
`quot` a
5)
    t :: Word64
t = forall {a}. Integral a => a -> a -> a
fit Word64
t1 Word64
t2
    sqr :: a -> a
sqr a
x = a
x forall a. Num a => a -> a -> a
* a
x
    d :: Double
d = forall {a}. Num a => a -> a
sqr (Word64 -> Double
word64ToDouble Word64
t1 forall a. Num a => a -> a -> a
-     Word64 -> Double
word64ToDouble Word64
t)
      forall a. Num a => a -> a -> a
+ forall {a}. Num a => a -> a
sqr (Word64 -> Double
word64ToDouble Word64
t2 forall a. Num a => a -> a -> a
- Double
2 forall a. Num a => a -> a -> a
* Word64 -> Double
word64ToDouble Word64
t)

predictPerturbed :: Measurement -> Measurement -> Estimate
predictPerturbed :: Measurement -> Measurement -> Estimate
predictPerturbed Measurement
t1 Measurement
t2 = Estimate
  { estMean :: Measurement
estMean = Estimate -> Measurement
estMean (Measurement -> Measurement -> Estimate
predict Measurement
t1 Measurement
t2)
  , estStdev :: Word64
estStdev = forall a. Ord a => a -> a -> a
max
    (Estimate -> Word64
estStdev (Measurement -> Measurement -> Estimate
predict (Measurement -> Measurement
lo Measurement
t1) (Measurement -> Measurement
hi Measurement
t2)))
    (Estimate -> Word64
estStdev (Measurement -> Measurement -> Estimate
predict (Measurement -> Measurement
hi Measurement
t1) (Measurement -> Measurement
lo Measurement
t2)))
  }
  where
    prec :: Word64
prec = forall a. Ord a => a -> a -> a
max (forall a. Num a => Integer -> a
fromInteger Integer
cpuTimePrecision) Word64
1000000000 -- 1 ms
    hi :: Measurement -> Measurement
hi Measurement
meas = Measurement
meas { measTime :: Word64
measTime = Measurement -> Word64
measTime Measurement
meas forall a. Num a => a -> a -> a
+ Word64
prec }
    lo :: Measurement -> Measurement
lo Measurement
meas = Measurement
meas { measTime :: Word64
measTime = Measurement -> Word64
measTime Measurement
meas forall a. Num a => a -> a -> a
- Word64
prec }

hasGCStats :: Bool
#if MIN_VERSION_base(4,10,0)
hasGCStats :: Bool
hasGCStats = forall a. IO a -> a
unsafePerformIO IO Bool
getRTSStatsEnabled
#elif MIN_VERSION_base(4,6,0)
hasGCStats = unsafePerformIO getGCStatsEnabled
#else
hasGCStats = False
#endif

getAllocsAndCopied :: IO (Word64, Word64, Word64)
getAllocsAndCopied :: IO (Word64, Word64, Word64)
getAllocsAndCopied = do
  if Bool -> Bool
not Bool
hasGCStats then forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word64
0, Word64
0, Word64
0) else
#if MIN_VERSION_base(4,10,0)
    (\RTSStats
s -> (RTSStats -> Word64
allocated_bytes RTSStats
s, RTSStats -> Word64
copied_bytes RTSStats
s, RTSStats -> Word64
max_mem_in_use_bytes RTSStats
s)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO RTSStats
getRTSStats
#elif MIN_VERSION_base(4,6,0)
    (\s -> (int64ToWord64 $ bytesAllocated s, int64ToWord64 $ bytesCopied s, int64ToWord64 $ peakMegabytesAllocated s * 1024 * 1024)) <$> getGCStats
#else
    pure (0, 0, 0)
#endif

getTimePicoSecs :: TimeMode -> IO Word64
getTimePicoSecs :: TimeMode -> IO Word64
getTimePicoSecs TimeMode
timeMode = case TimeMode
timeMode of
  TimeMode
CpuTime -> forall a. Num a => Integer -> a
fromInteger forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO Integer
getCPUTime
#ifdef MIN_VERSION_tasty
  TimeMode
WallTime -> forall a b. (RealFrac a, Integral b) => a -> b
round forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double
1e12 forall a. Num a => a -> a -> a
*) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO Double
getTime
#endif

measure :: TimeMode -> Word64 -> Benchmarkable -> IO Measurement
measure :: TimeMode -> Word64 -> Benchmarkable -> IO Measurement
measure TimeMode
timeMode Word64
n (Benchmarkable Word64 -> IO ()
act) = do
  let getTimePicoSecs' :: IO Word64
getTimePicoSecs' = TimeMode -> IO Word64
getTimePicoSecs TimeMode
timeMode
  IO ()
performGC
  Word64
startTime <- IO Word64
getTimePicoSecs'
  (Word64
startAllocs, Word64
startCopied, Word64
startMaxMemInUse) <- IO (Word64, Word64, Word64)
getAllocsAndCopied
  Word64 -> IO ()
act Word64
n
  Word64
endTime <- IO Word64
getTimePicoSecs'
  (Word64
endAllocs, Word64
endCopied, Word64
endMaxMemInUse) <- IO (Word64, Word64, Word64)
getAllocsAndCopied
  let meas :: Measurement
meas = Measurement
        { measTime :: Word64
measTime   = Word64
endTime forall a. Num a => a -> a -> a
- Word64
startTime
        , measAllocs :: Word64
measAllocs = Word64
endAllocs forall a. Num a => a -> a -> a
- Word64
startAllocs
        , measCopied :: Word64
measCopied = Word64
endCopied forall a. Num a => a -> a -> a
- Word64
startCopied
        , measMaxMem :: Word64
measMaxMem = forall a. Ord a => a -> a -> a
max Word64
endMaxMemInUse Word64
startMaxMemInUse
        }
#ifdef DEBUG
  pure $ trace (show n ++ (if n == 1 then " iteration gives " else " iterations give ") ++ show meas) meas
#else
  forall (f :: * -> *) a. Applicative f => a -> f a
pure Measurement
meas
#endif

measureUntil :: TimeMode -> Bool -> Timeout -> RelStDev -> Benchmarkable -> IO Estimate
measureUntil :: TimeMode
-> Bool -> Timeout -> RelStDev -> Benchmarkable -> IO Estimate
measureUntil TimeMode
timeMode Bool
_ Timeout
_ (RelStDev Double
targetRelStDev) Benchmarkable
b
  | forall a. RealFloat a => a -> Bool
isInfinite Double
targetRelStDev, Double
targetRelStDev forall a. Ord a => a -> a -> Bool
> Double
0 = do
  Measurement
t1 <- TimeMode -> Word64 -> Benchmarkable -> IO Measurement
measure TimeMode
timeMode Word64
1 Benchmarkable
b
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Estimate { estMean :: Measurement
estMean = Measurement
t1, estStdev :: Word64
estStdev = Word64
0 }
measureUntil TimeMode
timeMode Bool
warnIfNoTimeout Timeout
timeout (RelStDev Double
targetRelStDev) Benchmarkable
b = do
  Measurement
t1 <- Word64 -> Benchmarkable -> IO Measurement
measure' Word64
1 Benchmarkable
b
  Word64 -> Measurement -> Word64 -> IO Estimate
go Word64
1 Measurement
t1 Word64
0
  where
    measure' :: Word64 -> Benchmarkable -> IO Measurement
measure' = TimeMode -> Word64 -> Benchmarkable -> IO Measurement
measure TimeMode
timeMode

    go :: Word64 -> Measurement -> Word64 -> IO Estimate
    go :: Word64 -> Measurement -> Word64 -> IO Estimate
go Word64
n Measurement
t1 Word64
sumOfTs = do
      Measurement
t2 <- Word64 -> Benchmarkable -> IO Measurement
measure' (Word64
2 forall a. Num a => a -> a -> a
* Word64
n) Benchmarkable
b

      let Estimate (Measurement Word64
meanN Word64
allocN Word64
copiedN Word64
maxMemN) Word64
stdevN = Measurement -> Measurement -> Estimate
predictPerturbed Measurement
t1 Measurement
t2
          isTimeoutSoon :: Bool
isTimeoutSoon = case Timeout
timeout of
            Timeout
NoTimeout -> Bool
False
            -- multiplying by 12/10 helps to avoid accidental timeouts
            Timeout Integer
micros String
_ -> (Word64
sumOfTs' forall a. Num a => a -> a -> a
+ Word64
3 forall a. Num a => a -> a -> a
* Measurement -> Word64
measTime Measurement
t2) forall {a}. Integral a => a -> a -> a
`quot` (Word64
1000000 forall a. Num a => a -> a -> a
* Word64
10 forall {a}. Integral a => a -> a -> a
`quot` Word64
12) forall a. Ord a => a -> a -> Bool
>= forall a. Num a => Integer -> a
fromInteger Integer
micros
          isStDevInTargetRange :: Bool
isStDevInTargetRange = Word64
stdevN forall a. Ord a => a -> a -> Bool
< forall a b. (RealFrac a, Integral b) => a -> b
truncate (forall a. Ord a => a -> a -> a
max Double
0 Double
targetRelStDev forall a. Num a => a -> a -> a
* Word64 -> Double
word64ToDouble Word64
meanN)
          scale :: Word64 -> Word64
scale = (forall {a}. Integral a => a -> a -> a
`quot` Word64
n)
          sumOfTs' :: Word64
sumOfTs' = Word64
sumOfTs forall a. Num a => a -> a -> a
+ Measurement -> Word64
measTime Measurement
t1

      case Timeout
timeout of
        Timeout
NoTimeout | Bool
warnIfNoTimeout, Word64
sumOfTs' forall a. Num a => a -> a -> a
+ Measurement -> Word64
measTime Measurement
t2 forall a. Ord a => a -> a -> Bool
> Word64
100 forall a. Num a => a -> a -> a
* Word64
1000000000000
          -> Handle -> String -> IO ()
hPutStrLn Handle
stderr String
"This benchmark takes more than 100 seconds. Consider setting --timeout, if this is unexpected (or to silence this warning)."
        Timeout
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()

      if Bool
isStDevInTargetRange Bool -> Bool -> Bool
|| Bool
isTimeoutSoon
        then forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Estimate
          { estMean :: Measurement
estMean  = Word64 -> Word64 -> Word64 -> Word64 -> Measurement
Measurement (Word64 -> Word64
scale Word64
meanN) (Word64 -> Word64
scale Word64
allocN) (Word64 -> Word64
scale Word64
copiedN) Word64
maxMemN
          , estStdev :: Word64
estStdev = Word64 -> Word64
scale Word64
stdevN }
        else Word64 -> Measurement -> Word64 -> IO Estimate
go (Word64
2 forall a. Num a => a -> a -> a
* Word64
n) Measurement
t2 Word64
sumOfTs'

-- | An internal routine to measure CPU execution time in seconds
-- for a given timeout (put 'NoTimeout', or 'mkTimeout' 100000000 for 100 seconds)
-- and a target relative standard deviation
-- (put 'RelStDev' 0.05 for 5% or 'RelStDev' (1/0) to run only one iteration).
--
-- 'Timeout' takes soft priority over 'RelStDev': this function prefers
-- to finish in time even if at cost of precision. However, timeout is guidance
-- not guarantee: 'measureCpuTime' can take longer, if there is not enough time
-- to run at least thrice or an iteration takes unusually long.
--
-- @since 0.3
measureCpuTime :: Timeout -> RelStDev -> Benchmarkable -> IO Double
measureCpuTime :: Timeout -> RelStDev -> Benchmarkable -> IO Double
measureCpuTime = ((forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
.) forall b c a. (b -> c) -> (a -> b) -> a -> c
.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Timeout -> RelStDev -> Benchmarkable -> IO (Double, Double)
measureCpuTimeAndStDev

-- | Same as 'measureCpuTime', but returns both CPU execution time
-- and its standard deviation.
--
-- @since 0.3.4
measureCpuTimeAndStDev :: Timeout -> RelStDev -> Benchmarkable -> IO (Double, Double)
measureCpuTimeAndStDev :: Timeout -> RelStDev -> Benchmarkable -> IO (Double, Double)
measureCpuTimeAndStDev
    = ((forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Estimate
x ->
        ( Word64 -> Double
word64ToDouble (Measurement -> Word64
measTime (Estimate -> Measurement
estMean Estimate
x)) forall a. Fractional a => a -> a -> a
/ Double
1e12
        , Word64 -> Double
word64ToDouble (Estimate -> Word64
estStdev Estimate
x) forall a. Fractional a => a -> a -> a
/ Double
1e12
        )) forall b c a. (b -> c) -> (a -> b) -> a -> c
.) forall b c a. (b -> c) -> (a -> b) -> a -> c
.)
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. TimeMode
-> Bool -> Timeout -> RelStDev -> Benchmarkable -> IO Estimate
measureUntil TimeMode
CpuTime Bool
False

#ifdef MIN_VERSION_tasty

instance IsTest Benchmarkable where
  testOptions :: Tagged Benchmarkable [OptionDescription]
testOptions = forall (f :: * -> *) a. Applicative f => a -> f a
pure
    [ forall v. IsOption v => Proxy v -> OptionDescription
Option (forall {k} (t :: k). Proxy t
Proxy :: Proxy RelStDev)
    -- FailIfSlower and FailIfFaster must be options of a test provider rather
    -- than options of an ingredient to allow setting them on per-test level.
    , forall v. IsOption v => Proxy v -> OptionDescription
Option (forall {k} (t :: k). Proxy t
Proxy :: Proxy FailIfSlower)
    , forall v. IsOption v => Proxy v -> OptionDescription
Option (forall {k} (t :: k). Proxy t
Proxy :: Proxy FailIfFaster)
    , forall v. IsOption v => Proxy v -> OptionDescription
Option (forall {k} (t :: k). Proxy t
Proxy :: Proxy TimeMode)
    ]
  run :: OptionSet -> Benchmarkable -> (Progress -> IO ()) -> IO Result
run OptionSet
opts Benchmarkable
b = forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ case NumThreads -> Int
getNumThreads (forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts) of
    Int
1 -> do
      let timeMode :: TimeMode
timeMode = forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
      Estimate
est <- TimeMode
-> Bool -> Timeout -> RelStDev -> Benchmarkable -> IO Estimate
measureUntil TimeMode
timeMode Bool
True (forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts) (forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts) Benchmarkable
b
      let FailIfSlower Double
ifSlower = forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
          FailIfFaster Double
ifFaster = forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
      forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ String -> Result
testPassed forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show (forall a. a -> Double -> Double -> WithLoHi a
WithLoHi Estimate
est (Double
1 forall a. Num a => a -> a -> a
- Double
ifFaster) (Double
1 forall a. Num a => a -> a -> a
+ Double
ifSlower))
    Int
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ String -> Result
testFailed String
"Benchmarks must not be run concurrently. Please pass -j1 and/or avoid +RTS -N."

-- | Attach a name to 'Benchmarkable'.
--
-- This is actually a synonym of 'Test.Tasty.Providers.singleTest' to
-- provide an interface compatible with @Criterion.@'Criterion.bench'
-- and @Gauge.@'Gauge.bench'.
--
-- @since 0.1
bench :: String -> Benchmarkable -> Benchmark
bench :: String -> Benchmarkable -> Benchmark
bench = forall t. IsTest t => String -> t -> Benchmark
singleTest

-- | Attach a name to a group of 'Benchmark'.
--
-- This is actually a synonym of 'Test.Tasty.testGroup' to provide an
-- interface compatible with @Criterion.@'Criterion.bgroup' and
-- @Gauge@.'Gauge.bgroup'.
--
-- @since 0.1
bgroup :: String -> [Benchmark] -> Benchmark
bgroup :: String -> [Benchmark] -> Benchmark
bgroup = String -> [Benchmark] -> Benchmark
testGroup

-- | Compare benchmarks, reporting relative speed up or slow down.
--
-- This function is a vague reminiscence of @bcompare@, which existed in pre-1.0
-- versions of @criterion@, but their types are incompatible. Under the hood
-- 'bcompare' is a thin wrapper over 'after'.
--
-- Here is a basic example:
--
-- > import Test.Tasty.Bench
-- >
-- > fibo :: Int -> Integer
-- > fibo n = if n < 2 then toInteger n else fibo (n - 1) + fibo (n - 2)
-- >
-- > main :: IO ()
-- > main = defaultMain
-- >   [ bgroup "Fibonacci numbers"
-- >     [ bcompare "tenth"  $ bench "fifth"     $ nf fibo  5
-- >     ,                     bench "tenth"     $ nf fibo 10
-- >     , bcompare "tenth"  $ bench "twentieth" $ nf fibo 20
-- >     ]
-- >   ]
--
-- More complex examples:
--
-- * https://hackage.haskell.org/package/chimera-0.3.3.0/src/bench/Bench.hs
-- * https://hackage.haskell.org/package/fast-digits-0.3.1.0/src/bench/Bench.hs
-- * https://hackage.haskell.org/package/unicode-data-0.4.0.1/src/bench/Main.hs
--
-- @since 0.2.4
bcompare
  :: String
  -- ^ @tasty@ pattern, which must unambiguously
  -- match a unique baseline benchmark. Consider using 'locateBenchmark' to construct it.
  -> Benchmark
  -- ^ Benchmark (or a group of benchmarks)
  -- to be compared against the baseline benchmark by dividing measured mean times.
  -- The result is reported by 'consoleBenchReporter', e. g., 0.50x or 1.25x.
  -> Benchmark
bcompare :: String -> Benchmark -> Benchmark
bcompare = Double -> Double -> String -> Benchmark -> Benchmark
bcompareWithin (-Double
1forall a. Fractional a => a -> a -> a
/Double
0) (Double
1forall a. Fractional a => a -> a -> a
/Double
0)

-- | Same as 'bcompare', but takes expected lower and upper bounds of
-- comparison. If the result is not within provided bounds, benchmark fails.
-- This allows to create portable performance tests: instead of comparing
-- to an absolute timeout or to previous runs, you can state that one implementation
-- of an algorithm must be faster than another.
--
-- E. g., 'bcompareWithin' 2.0 3.0 passes only if a benchmark is at least 2x
-- and at most 3x slower than a baseline.
--
-- @since 0.3.1
bcompareWithin
  :: Double    -- ^ Lower bound of relative speed up.
  -> Double    -- ^ Upper bound of relative speed up.
  -> String    -- ^ @tasty@ pattern to locate a baseline benchmark.
  -> Benchmark -- ^ Benchmark to compare against baseline.
  -> Benchmark
bcompareWithin :: Double -> Double -> String -> Benchmark -> Benchmark
bcompareWithin Double
lo Double
hi String
s = case String -> Maybe Expr
parseExpr String
s of
  Maybe Expr
Nothing -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Could not parse bcompare pattern " forall a. [a] -> [a] -> [a]
++ String
s
  Just Expr
e  -> DependencyType -> Expr -> Benchmark -> Benchmark
after_ DependencyType
AllSucceed (Expr -> Expr -> Expr
And (String -> Expr
StringLit (String
bcomparePrefix forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Double
lo, Double
hi))) Expr
e)

bcomparePrefix :: String
bcomparePrefix :: String
bcomparePrefix = String
"tasty-bench"

-- | Benchmarks are actually just a regular 'Test.Tasty.TestTree' in disguise.
--
-- This is a drop-in replacement for @Criterion.@'Criterion.Benchmark'
-- and @Gauge.@'Gauge.Benchmark'.
--
-- @since 0.1
type Benchmark = TestTree

-- | Run benchmarks and report results, providing an interface
-- compatible with @Criterion.@'Criterion.defaultMain' and
-- @Gauge.@'Gauge.defaultMain'.
--
-- @since 0.1
defaultMain :: [Benchmark] -> IO ()
defaultMain :: [Benchmark] -> IO ()
defaultMain [Benchmark]
bs = do
  let act :: IO ()
act = [Benchmark] -> IO ()
defaultMain' [Benchmark]
bs
#if MIN_VERSION_base(4,5,0)
  TextEncoding -> IO ()
setLocaleEncoding TextEncoding
utf8
#endif
#if defined(mingw32_HOST_OS)
  codePage <- getConsoleOutputCP
  bracket (setConsoleOutputCP 65001) (const $ setConsoleOutputCP codePage) (const act)
#else
  IO ()
act
#endif

defaultMain' :: [Benchmark] -> IO ()
defaultMain' :: [Benchmark] -> IO ()
defaultMain' [Benchmark]
bs  = do
  IO ()
installSignalHandlers
  let b :: Benchmark
b = String -> [Benchmark] -> Benchmark
testGroup String
"All" [Benchmark]
bs
  OptionSet
opts <- [Ingredient] -> Benchmark -> IO OptionSet
parseOptions [Ingredient]
benchIngredients Benchmark
b
  case [Ingredient] -> OptionSet -> Benchmark -> Maybe (IO Bool)
tryIngredients [Ingredient]
benchIngredients (forall v. IsOption v => v -> OptionSet -> OptionSet
setOption (Int -> NumThreads
NumThreads Int
1) OptionSet
opts) Benchmark
b of
    Maybe (IO Bool)
Nothing -> forall a. IO a
exitFailure
    Just IO Bool
act -> IO Bool
act forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
x -> if Bool
x then forall a. IO a
exitSuccess else forall a. IO a
exitFailure

-- | List of default benchmark ingredients. This is what 'defaultMain' runs.
--
-- @since 0.2
benchIngredients :: [Ingredient]
benchIngredients :: [Ingredient]
benchIngredients = [Ingredient
listingTests, Ingredient -> Ingredient -> Ingredient
composeReporters Ingredient
consoleBenchReporter (Ingredient -> Ingredient -> Ingredient
composeReporters Ingredient
csvReporter Ingredient
svgReporter)]

#endif

funcToBench :: forall a b c. (b -> c) -> (a -> b) -> a -> Benchmarkable
funcToBench :: forall a b c. (b -> c) -> (a -> b) -> a -> Benchmarkable
funcToBench b -> c
frc = ((Word64 -> IO ()) -> Benchmarkable
Benchmarkable forall b c a. (b -> c) -> (a -> b) -> a -> c
.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. SPEC -> (a -> b) -> a -> Word64 -> IO ()
benchLoop SPEC
SPEC
  where
    -- Here we rely on the fact that GHC (unless spurred by
    -- -fstatic-argument-transformation) is not smart enough:
    -- it does not notice that `f` and `x` arguments are loop invariant
    -- and could be floated, and the whole `f x` expression shared.
    -- If we create a closure with `f` and `x` bound in the environment,
    -- then GHC is smart enough to share computation of `f x`.
    --
    -- For perspective, gauge and criterion < 1.4 mark similar functions as INLINE,
    -- while criterion >= 1.4 switches to NOINLINE.
    -- If we mark `benchLoop` NOINLINE then benchmark results are slightly larger
    -- (noticeable in bench-fibo), because the loop body is slightly bigger,
    -- since GHC does not unbox numbers or inline `Eq @Word64` dictionary.
    --
    -- This function is called `benchLoop` instead of, say, `go`,
    -- so it is easier to spot in Core dumps.
    --
    -- Forcing SpecConst optimization with SPEC makes the behaviour of benchmarks
    -- independent of -fspec-constr-count.
    benchLoop :: SPEC -> (a -> b) -> a -> Word64 -> IO ()
    benchLoop :: SPEC -> (a -> b) -> a -> Word64 -> IO ()
benchLoop !SPEC
_ a -> b
f a
x Word64
n
      | Word64
n forall a. Eq a => a -> a -> Bool
== Word64
0    = forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
      | Bool
otherwise = do
        c
_ <- forall a. a -> IO a
evaluate (b -> c
frc (a -> b
f a
x))
        SPEC -> (a -> b) -> a -> Word64 -> IO ()
benchLoop SPEC
SPEC a -> b
f a
x (Word64
n forall a. Num a => a -> a -> a
- Word64
1)
{-# INLINE funcToBench #-}

-- | 'nf' @f@ @x@ measures time to compute
-- a normal form (by means of 'force', not 'Control.DeepSeq.rnf')
-- of an application of @f@ to @x@.
-- This does not include time to evaluate @f@ or @x@ themselves.
-- Ideally @x@ should be a primitive data type like 'Data.Int.Int'.
--
-- The same thunk of @x@ is shared by multiple calls of @f@. We cannot evaluate
-- @x@ beforehand: there is no 'NFData' @a@ constraint, and potentially @x@ may
-- be an infinite structure. Thus @x@ will be evaluated in course of the first
-- application of @f@. This noisy measurement is to be discarded soon,
-- but if @x@ is not a primitive data type, consider forcing its evaluation
-- separately, e. g., via 'env' or 'withResource'.
--
-- Here is a textbook anti-pattern: 'nf' 'sum' @[1..1000000]@.
-- Since an input list is shared by multiple invocations of 'sum',
-- it will be allocated in memory in full, putting immense pressure
-- on garbage collector. Also no list fusion will happen.
-- A better approach is 'nf' (@\\n@ @->@ 'sum' @[1..n]@) @1000000@.
--
-- If you are measuring an inlinable function,
-- it is prudent to ensure that its invocation is fully saturated,
-- otherwise inlining will not happen. That's why one can often
-- see 'nf' (@\\n@ @->@ @f@ @n@) @x@ instead of 'nf' @f@ @x@.
-- Same applies to rewrite rules.
--
-- While @tasty-bench@ is capable to perform micro- and even nanobenchmarks,
-- such measurements are noisy and involve an overhead. Results are more reliable
-- when @f@ @x@ takes at least several milliseconds.
--
-- Remember that forcing a normal form requires an additional
-- traverse of the structure. In certain scenarios (imagine benchmarking 'tail'),
-- especially when 'NFData' instance is badly written,
-- this traversal may take non-negligible time and affect results.
--
-- 'nf' @f@ is equivalent to 'whnf' ('force' '.' @f@), but not to
-- 'whnf' ('Control.DeepSeq.rnf' '.' @f@). The former retains the result
-- in memory until it is fully evaluated, while the latter allows
-- evaluated parts of the result to be garbage-collected immediately.
--
-- For users of @{-# LANGUAGE LinearTypes #-}@: if @f@ is a linear function,
-- then 'nf' @f@ @x@ is ill-typed, but you can use 'nf' @(\\y -> f y)@ @x@
-- instead.
--
-- Drop-in replacement for @Criterion.@'Criterion.nf' and
-- @Gauge.@'Gauge.nf'.
--
-- @since 0.1
nf :: NFData b => (a -> b) -> a -> Benchmarkable
nf :: forall b a. NFData b => (a -> b) -> a -> Benchmarkable
nf = forall a b c. (b -> c) -> (a -> b) -> a -> Benchmarkable
funcToBench forall a. NFData a => a -> a
force
{-# INLINE nf #-}

-- | 'whnf' @f@ @x@ measures time to compute
-- a weak head normal form of an application of @f@ to @x@.
-- This does not include time to evaluate @f@ or @x@ themselves.
-- Ideally @x@ should be a primitive data type like 'Data.Int.Int'.
--
-- The same thunk of @x@ is shared by multiple calls of @f@. We cannot evaluate
-- @x@ beforehand: there is no 'NFData' @a@ constraint, and potentially @x@ may
-- be an infinite structure. Thus @x@ will be evaluated in course of the first
-- application of @f@. This noisy measurement is to be discarded soon,
-- but if @x@ is not a primitive data type, consider forcing its evaluation
-- separately, e. g., via 'env' or 'withResource'.
--
-- Computing only a weak head normal form is
-- rarely what intuitively is meant by "evaluation".
-- Beware that many educational materials contain examples with 'whnf':
-- this is a wrong default.
-- Unless you understand precisely, what is measured,
-- it is recommended to use 'nf' instead.
--
-- Here is a textbook anti-pattern: 'whnf' ('Data.List.replicate' @1000000@) @1@.
-- This will succeed in a matter of nanoseconds, because weak head
-- normal form forces only the first element of the list.
--
-- Drop-in replacement for @Criterion.@'Criterion.whnf' and @Gauge.@'Gauge.whnf'.
--
-- @since 0.1
whnf :: (a -> b) -> a -> Benchmarkable
whnf :: forall a b. (a -> b) -> a -> Benchmarkable
whnf = forall a b c. (b -> c) -> (a -> b) -> a -> Benchmarkable
funcToBench forall a. a -> a
id
{-# INLINE whnf #-}

ioToBench :: (b -> c) -> IO b -> Benchmarkable
ioToBench :: forall b c. (b -> c) -> IO b -> Benchmarkable
ioToBench b -> c
frc IO b
act = (Word64 -> IO ()) -> Benchmarkable
Benchmarkable forall {t}. (Eq t, Num t) => t -> IO ()
go
  where
    go :: t -> IO ()
go t
n
      | t
n forall a. Eq a => a -> a -> Bool
== t
0    = forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
      | Bool
otherwise = do
        b
val <- IO b
act
        c
_ <- forall a. a -> IO a
evaluate (b -> c
frc b
val)
        t -> IO ()
go (t
n forall a. Num a => a -> a -> a
- t
1)
{-# INLINE ioToBench #-}

-- | 'nfIO' @x@ measures time to evaluate side-effects of @x@
-- and compute its normal form (by means of 'force', not 'Control.DeepSeq.rnf').
--
-- Pure subexpression of an effectful computation @x@
-- may be evaluated only once and get cached.
-- To avoid surprising results it is usually preferable
-- to use 'nfAppIO' instead.
--
-- Remember that forcing a normal form requires an additional
-- traverse of the structure. In certain scenarios,
-- especially when 'NFData' instance is badly written,
-- this traversal may take non-negligible time and affect results.
--
-- A typical use case is 'nfIO' ('readFile' @"foo.txt"@).
-- However, if your goal is not to benchmark I\/O per se,
-- but just read input data from a file, it is cleaner to
-- use 'env' or 'withResource'.
--
-- Drop-in replacement for @Criterion.@'Criterion.nfIO' and @Gauge.@'Gauge.nfIO'.
--
-- @since 0.1
nfIO :: NFData a => IO a -> Benchmarkable
nfIO :: forall a. NFData a => IO a -> Benchmarkable
nfIO = forall b c. (b -> c) -> IO b -> Benchmarkable
ioToBench forall a. NFData a => a -> a
force
{-# INLINE nfIO #-}

-- | 'whnfIO' @x@ measures time to evaluate side-effects of @x@
-- and compute its weak head normal form.
--
-- Pure subexpression of an effectful computation @x@
-- may be evaluated only once and get cached.
-- To avoid surprising results it is usually preferable
-- to use 'whnfAppIO' instead.
--
-- Computing only a weak head normal form is
-- rarely what intuitively is meant by "evaluation".
-- Unless you understand precisely, what is measured,
-- it is recommended to use 'nfIO' instead.
--
-- Lazy I\/O is treacherous.
-- If your goal is not to benchmark I\/O per se,
-- but just read input data from a file, it is cleaner to
-- use 'env' or 'withResource'.
--
-- Drop-in replacement for @Criterion.@'Criterion.whnfIO' and @Gauge.@'Gauge.whnfIO'.
--
-- @since 0.1
whnfIO :: IO a -> Benchmarkable
whnfIO :: forall a. IO a -> Benchmarkable
whnfIO = forall b c. (b -> c) -> IO b -> Benchmarkable
ioToBench forall a. a -> a
id
{-# INLINE whnfIO #-}

ioFuncToBench :: (b -> c) -> (a -> IO b) -> a -> Benchmarkable
ioFuncToBench :: forall b c a. (b -> c) -> (a -> IO b) -> a -> Benchmarkable
ioFuncToBench b -> c
frc = ((Word64 -> IO ()) -> Benchmarkable
Benchmarkable forall b c a. (b -> c) -> (a -> b) -> a -> c
.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {t} {t}. (Eq t, Num t) => (t -> IO b) -> t -> t -> IO ()
go
  where
    go :: (t -> IO b) -> t -> t -> IO ()
go t -> IO b
f t
x t
n
      | t
n forall a. Eq a => a -> a -> Bool
== t
0    = forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
      | Bool
otherwise = do
        b
val <- t -> IO b
f t
x
        c
_ <- forall a. a -> IO a
evaluate (b -> c
frc b
val)
        (t -> IO b) -> t -> t -> IO ()
go t -> IO b
f t
x (t
n forall a. Num a => a -> a -> a
- t
1)
{-# INLINE ioFuncToBench #-}

-- | 'nfAppIO' @f@ @x@ measures time to evaluate side-effects of
-- an application of @f@ to @x@
-- and compute its normal form (by means of 'force', not 'Control.DeepSeq.rnf').
-- This does not include time to evaluate @f@ or @x@ themselves.
-- Ideally @x@ should be a primitive data type like 'Data.Int.Int'.
--
-- The same thunk of @x@ is shared by multiple calls of @f@. We cannot evaluate
-- @x@ beforehand: there is no 'NFData' @a@ constraint, and potentially @x@ may
-- be an infinite structure. Thus @x@ will be evaluated in course of the first
-- application of @f@. This noisy measurement is to be discarded soon,
-- but if @x@ is not a primitive data type, consider forcing its evaluation
-- separately, e. g., via 'env' or 'withResource'.
--
-- Remember that forcing a normal form requires an additional
-- traverse of the structure. In certain scenarios,
-- especially when 'NFData' instance is badly written,
-- this traversal may take non-negligible time and affect results.
--
-- A typical use case is 'nfAppIO' 'readFile' @"foo.txt"@.
-- However, if your goal is not to benchmark I\/O per se,
-- but just read input data from a file, it is cleaner to
-- use 'env' or 'withResource'.
--
-- Drop-in replacement for @Criterion.@'Criterion.nfAppIO' and @Gauge.@'Gauge.nfAppIO'.
--
-- @since 0.1
nfAppIO :: NFData b => (a -> IO b) -> a -> Benchmarkable
nfAppIO :: forall b a. NFData b => (a -> IO b) -> a -> Benchmarkable
nfAppIO = forall b c a. (b -> c) -> (a -> IO b) -> a -> Benchmarkable
ioFuncToBench forall a. NFData a => a -> a
force
{-# INLINE nfAppIO #-}

-- | 'whnfAppIO' @f@ @x@ measures time to evaluate side-effects of
-- an application of @f@ to @x@
-- and compute its weak head normal form.
-- This does not include time to evaluate @f@ or @x@ themselves.
-- Ideally @x@ should be a primitive data type like 'Data.Int.Int'.
--
-- The same thunk of @x@ is shared by multiple calls of @f@. We cannot evaluate
-- @x@ beforehand: there is no 'NFData' @a@ constraint, and potentially @x@ may
-- be an infinite structure. Thus @x@ will be evaluated in course of the first
-- application of @f@. This noisy measurement is to be discarded soon,
-- but if @x@ is not a primitive data type, consider forcing its evaluation
-- separately, e. g., via 'env' or 'withResource'.
--
-- Computing only a weak head normal form is
-- rarely what intuitively is meant by "evaluation".
-- Unless you understand precisely, what is measured,
-- it is recommended to use 'nfAppIO' instead.
--
-- Lazy I\/O is treacherous.
-- If your goal is not to benchmark I\/O per se,
-- but just read input data from a file, it is cleaner to
-- use 'env' or 'withResource'.
--
-- Drop-in replacement for @Criterion.@'Criterion.whnfAppIO' and @Gauge.@'Gauge.whnfAppIO'.
--
-- @since 0.1
whnfAppIO :: (a -> IO b) -> a -> Benchmarkable
whnfAppIO :: forall a b. (a -> IO b) -> a -> Benchmarkable
whnfAppIO = forall b c a. (b -> c) -> (a -> IO b) -> a -> Benchmarkable
ioFuncToBench forall a. a -> a
id
{-# INLINE whnfAppIO #-}

#ifdef MIN_VERSION_tasty

-- | Run benchmarks in the given environment, usually reading large input data from file.
--
-- One might wonder why 'env' is needed,
-- when we can simply read all input data
-- before calling 'defaultMain'. The reason is that large data
-- dangling in the heap causes longer garbage collection
-- and slows down all benchmarks, even those which do not use it at all.
--
-- It is instrumental not only for proper 'IO' actions,
-- but also for a large statically-known data as well. Instead of a top-level
-- definition, which once evaluated will slow down garbage collection
-- during all subsequent benchmarks,
--
-- > largeData :: String
-- > largeData = replicate 1000000 'a'
-- >
-- > main :: IO ()
-- > main = defaultMain
-- >   [ bench "large" $ nf length largeData, ... ]
--
-- use
--
-- > import Control.DeepSeq (force)
-- > import Control.Exception (evaluate)
-- >
-- > main :: IO ()
-- > main = defaultMain
-- >   [ env (evaluate (force (replicate 1000000 'a'))) $ \largeData ->
-- >     bench "large" $ nf length largeData, ... ]
--
-- @Test.Tasty.Bench.@'env' is provided only for the sake of
-- compatibility with @Criterion.@'Criterion.env' and
-- @Gauge.@'Gauge.env', and involves 'unsafePerformIO'. Consider using
-- 'withResource' instead.
--
-- 'defaultMain' requires that the hierarchy of benchmarks and their names is
-- independent of underlying 'IO' actions. While executing 'IO' inside 'bench'
-- via 'nfIO' is fine, and reading test data from files via 'env' is also fine,
-- using 'env' to choose benchmarks or their names depending on 'IO' side effects
-- will throw a rather cryptic error message:
--
-- > Unhandled resource. Probably a bug in the runner you're using.
--
-- @since 0.2
env :: NFData env => IO env -> (env -> Benchmark) -> Benchmark
env :: forall env. NFData env => IO env -> (env -> Benchmark) -> Benchmark
env IO env
res = forall env a.
NFData env =>
IO env -> (env -> IO a) -> (env -> Benchmark) -> Benchmark
envWithCleanup IO env
res (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

-- | Similar to 'env', but includes an additional argument
-- to clean up created environment.
--
-- Provided only for the sake of compatibility with
-- @Criterion.@'Criterion.envWithCleanup' and
-- @Gauge.@'Gauge.envWithCleanup', and involves
-- 'unsafePerformIO'. Consider using 'withResource' instead.
--
-- @since 0.2
envWithCleanup :: NFData env => IO env -> (env -> IO a) -> (env -> Benchmark) -> Benchmark
envWithCleanup :: forall env a.
NFData env =>
IO env -> (env -> IO a) -> (env -> Benchmark) -> Benchmark
envWithCleanup IO env
res env -> IO a
fin env -> Benchmark
f = forall a. IO a -> (a -> IO ()) -> (IO a -> Benchmark) -> Benchmark
withResource
  (IO env
res forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. a -> IO a
evaluate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NFData a => a -> a
force)
  (forall (f :: * -> *) a. Functor f => f a -> f ()
void forall b c a. (b -> c) -> (a -> b) -> a -> c
. env -> IO a
fin)
  (env -> Benchmark
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IO a -> a
unsafePerformIO)

-- | A path to write results in CSV format, populated by @--csv@.
--
-- This is an option of 'csvReporter' and can be set only globally.
-- Modifying it via 'adjustOption' or 'localOption' does not have any effect.
-- One can however pass it to 'tryIngredients' 'benchIngredients'. For example,
-- here is how to set a default CSV location:
--
-- @
-- import Data.Maybe
-- import System.Exit
-- import Test.Tasty.Bench
-- import Test.Tasty.Ingredients
-- import Test.Tasty.Options
-- import Test.Tasty.Runners
--
-- main :: IO ()
-- main = do
--   let benchmarks = bgroup \"All\" ...
--   opts <- parseOptions benchIngredients benchmarks
--   let opts' = changeOption (Just . fromMaybe (CsvPath "foo.csv")) opts
--   case tryIngredients benchIngredients opts' benchmarks of
--     Nothing -> exitFailure
--     Just mb -> mb >>= \\b -> if b then exitSuccess else exitFailure
-- @
--
-- @since 0.3
newtype CsvPath = CsvPath FilePath
  deriving (Typeable)

instance IsOption (Maybe CsvPath) where
  defaultValue :: Maybe CsvPath
defaultValue = forall a. Maybe a
Nothing
  parseValue :: String -> Maybe (Maybe CsvPath)
parseValue = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> CsvPath
CsvPath
  optionName :: Tagged (Maybe CsvPath) String
optionName = forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"csv"
  optionHelp :: Tagged (Maybe CsvPath) String
optionHelp = forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"File to write results in CSV format"

-- | Run benchmarks and save results in CSV format.
-- It activates when @--csv@ @FILE@ command line option is specified.
--
-- @since 0.1
csvReporter :: Ingredient
csvReporter :: Ingredient
csvReporter = [OptionDescription]
-> (OptionSet
    -> Benchmark -> Maybe (StatusMap -> IO (Double -> IO Bool)))
-> Ingredient
TestReporter [forall v. IsOption v => Proxy v -> OptionDescription
Option (forall {k} (t :: k). Proxy t
Proxy :: Proxy (Maybe CsvPath))] forall a b. (a -> b) -> a -> b
$
  \OptionSet
opts Benchmark
tree -> do
    CsvPath String
path <- forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
    let names :: [String]
names = OptionSet -> Benchmark -> [String]
testsNames OptionSet
opts Benchmark
tree
        namesMap :: IntMap String
namesMap = forall a. [(Int, a)] -> IntMap a
IM.fromDistinctAscList forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] [String]
names
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ \StatusMap
smap -> do
      case forall a. Ord a => [a] -> Maybe a
findNonUniqueElement [String]
names of
        Maybe String
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
        Just String
name -> do -- 'die' is not available before base-4.8
          Handle -> String -> IO ()
hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ String
"CSV report cannot proceed, because name '" forall a. [a] -> [a] -> [a]
++ String
name forall a. [a] -> [a] -> [a]
++ String
"' corresponds to two or more benchmarks. Please disambiguate them."
          forall a. IO a
exitFailure
      let augmented :: IntMap (String, TVar Status)
augmented = forall a b c. (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
IM.intersectionWith (,) IntMap String
namesMap StatusMap
smap
      forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
        (do
          Handle
h <- String -> IOMode -> IO Handle
openFile String
path IOMode
WriteMode
          Handle -> BufferMode -> IO ()
hSetBuffering Handle
h BufferMode
LineBuffering
          Handle -> String -> IO ()
hPutStrLn Handle
h forall a b. (a -> b) -> a -> b
$ String
"Name,Mean (ps),2*Stdev (ps)" forall a. [a] -> [a] -> [a]
++
            (if Bool
hasGCStats then String
",Allocated,Copied,Peak Memory" else String
"")
          forall (f :: * -> *) a. Applicative f => a -> f a
pure Handle
h
        )
        Handle -> IO ()
hClose
        (Handle -> IntMap (String, TVar Status) -> IO ()
`csvOutput` IntMap (String, TVar Status)
augmented)
      forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ StatusMap -> IO Bool
isSuccessful StatusMap
smap

findNonUniqueElement :: Ord a => [a] -> Maybe a
findNonUniqueElement :: forall a. Ord a => [a] -> Maybe a
findNonUniqueElement = forall {a}. Ord a => Set a -> [a] -> Maybe a
go forall a. Set a
S.empty
  where
    go :: Set a -> [a] -> Maybe a
go Set a
_ [] = forall a. Maybe a
Nothing
    go Set a
acc (a
x : [a]
xs)
      | a
x forall a. Ord a => a -> Set a -> Bool
`S.member` Set a
acc = forall a. a -> Maybe a
Just a
x
      | Bool
otherwise = Set a -> [a] -> Maybe a
go (forall a. Ord a => a -> Set a -> Set a
S.insert a
x Set a
acc) [a]
xs

csvOutput :: Handle -> IntMap (TestName, TVar Status) -> IO ()
csvOutput :: Handle -> IntMap (String, TVar Status) -> IO ()
csvOutput Handle
h = forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ forall a b. (a -> b) -> a -> b
$ \(String
name, TVar Status
tv) -> do
  let csv :: Estimate -> String
csv = if Bool
hasGCStats then Estimate -> String
csvEstimateWithGC else Estimate -> String
csvEstimate
  Result
r <- forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ forall a. TVar a -> STM a
readTVar TVar Status
tv forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Status
s -> case Status
s of Done Result
r -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Result
r; Status
_ -> forall a. STM a
retry
  case forall a. Read a => String -> Maybe a
safeRead (Result -> String
resultDescription Result
r) of
    Maybe (WithLoHi Estimate)
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
    Just (WithLoHi Estimate
est Double
_ Double
_) -> do
      String
msg <- String -> IO String
formatMessage forall a b. (a -> b) -> a -> b
$ Estimate -> String
csv Estimate
est
      Handle -> String -> IO ()
hPutStrLn Handle
h (ShowS
encodeCsv String
name forall a. [a] -> [a] -> [a]
++ Char
',' forall a. a -> [a] -> [a]
: String
msg)

encodeCsv :: String -> String
encodeCsv :: ShowS
encodeCsv String
xs
  | forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
xs) String
",\"\n\r"
  = Char
'"' forall a. a -> [a] -> [a]
: ShowS
go String
xs -- opening quote
  | Bool
otherwise = String
xs
  where
    go :: ShowS
go [] = Char
'"' forall a. a -> [a] -> [a]
: [] -- closing quote
    go (Char
'"' : String
ys) = Char
'"' forall a. a -> [a] -> [a]
: Char
'"' forall a. a -> [a] -> [a]
: ShowS
go String
ys
    go (Char
y : String
ys) = Char
y forall a. a -> [a] -> [a]
: ShowS
go String
ys

-- | A path to plot results in SVG format, populated by @--svg@.
--
-- This is an option of 'svgReporter' and can be set only globally.
-- Modifying it via 'adjustOption' or 'localOption' does not have any effect.
-- One can however pass it to 'tryIngredients' 'benchIngredients'.
--
-- @since 0.3
newtype SvgPath = SvgPath FilePath
  deriving (Typeable)

instance IsOption (Maybe SvgPath) where
  defaultValue :: Maybe SvgPath
defaultValue = forall a. Maybe a
Nothing
  parseValue :: String -> Maybe (Maybe SvgPath)
parseValue = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> SvgPath
SvgPath
  optionName :: Tagged (Maybe SvgPath) String
optionName = forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"svg"
  optionHelp :: Tagged (Maybe SvgPath) String
optionHelp = forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"File to plot results in SVG format"

-- | Run benchmarks and plot results in SVG format.
-- It activates when @--svg@ @FILE@ command line option is specified.
--
-- @since 0.2.4
svgReporter :: Ingredient
svgReporter :: Ingredient
svgReporter = [OptionDescription]
-> (OptionSet
    -> Benchmark -> Maybe (StatusMap -> IO (Double -> IO Bool)))
-> Ingredient
TestReporter [forall v. IsOption v => Proxy v -> OptionDescription
Option (forall {k} (t :: k). Proxy t
Proxy :: Proxy (Maybe SvgPath))] forall a b. (a -> b) -> a -> b
$
  \OptionSet
opts Benchmark
tree -> do
    SvgPath String
path <- forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
    let names :: [String]
names = OptionSet -> Benchmark -> [String]
testsNames OptionSet
opts Benchmark
tree
        namesMap :: IntMap String
namesMap = forall a. [(Int, a)] -> IntMap a
IM.fromDistinctAscList forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] [String]
names
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ \StatusMap
smap -> do
      IORef [(String, Estimate)]
ref <- forall a. a -> IO (IORef a)
newIORef []
      IORef [(String, Estimate)] -> IntMap (String, TVar Status) -> IO ()
svgCollect IORef [(String, Estimate)]
ref (forall a b c. (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
IM.intersectionWith (,) IntMap String
namesMap StatusMap
smap)
      [(String, Estimate)]
res <- forall a. IORef a -> IO a
readIORef IORef [(String, Estimate)]
ref
      String -> String -> IO ()
writeFile String
path ([(String, Estimate)] -> String
svgRender (forall a. [a] -> [a]
reverse [(String, Estimate)]
res))
      forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ StatusMap -> IO Bool
isSuccessful StatusMap
smap

isSuccessful :: StatusMap -> IO Bool
isSuccessful :: StatusMap -> IO Bool
isSuccessful = [TVar Status] -> IO Bool
go forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IntMap a -> [a]
IM.elems
  where
    go :: [TVar Status] -> IO Bool
go [] = forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
True
    go (TVar Status
tv : [TVar Status]
tvs) = do
      Bool
b <- forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ forall a. TVar a -> STM a
readTVar TVar Status
tv forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Status
s -> case Status
s of Done Result
r -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (Result -> Bool
resultSuccessful Result
r); Status
_ -> forall a. STM a
retry
      if Bool
b then [TVar Status] -> IO Bool
go [TVar Status]
tvs else forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False

svgCollect :: IORef [(TestName, Estimate)] -> IntMap (TestName, TVar Status) -> IO ()
svgCollect :: IORef [(String, Estimate)] -> IntMap (String, TVar Status) -> IO ()
svgCollect IORef [(String, Estimate)]
ref = forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ forall a b. (a -> b) -> a -> b
$ \(String
name, TVar Status
tv) -> do
  Result
r <- forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ forall a. TVar a -> STM a
readTVar TVar Status
tv forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Status
s -> case Status
s of Done Result
r -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Result
r; Status
_ -> forall a. STM a
retry
  case forall a. Read a => String -> Maybe a
safeRead (Result -> String
resultDescription Result
r) of
    Maybe (WithLoHi Estimate)
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
    Just (WithLoHi Estimate
est Double
_ Double
_) -> forall a. IORef a -> (a -> a) -> IO ()
modifyIORef IORef [(String, Estimate)]
ref ((String
name, Estimate
est) forall a. a -> [a] -> [a]
:)

svgRender :: [(TestName, Estimate)] -> String
svgRender :: [(String, Estimate)] -> String
svgRender [] = String
""
svgRender [(String, Estimate)]
pairs = String
header forall a. [a] -> [a] -> [a]
++ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
  (\Word64
i (String
name, Estimate
est) -> Word64 -> Word64 -> Double -> String -> Estimate -> String
svgRenderItem Word64
i Word64
l Double
xMax (forall a. [a] -> [a]
dropAllPrefix String
name) Estimate
est)
  [Word64
0..]
  [(String, Estimate)]
pairs) forall a. [a] -> [a] -> [a]
++ String
footer
  where
    dropAllPrefix :: [a] -> [a]
dropAllPrefix
      | forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((String
"All." forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf`) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) [(String, Estimate)]
pairs = forall a. Int -> [a] -> [a]
drop Int
4
      | Bool
otherwise = forall a. a -> a
id

    l :: Word64
l = forall i a. Num i => [a] -> i
genericLength [(String, Estimate)]
pairs
    findMaxX :: Estimate -> Word64
findMaxX (Estimate Measurement
m Word64
stdev) = Measurement -> Word64
measTime Measurement
m forall a. Num a => a -> a -> a
+ Word64
2 forall a. Num a => a -> a -> a
* Word64
stdev
    xMax :: Double
xMax = Word64 -> Double
word64ToDouble forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum forall a b. (a -> b) -> a -> b
$ forall a. Bounded a => a
minBound forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map (Estimate -> Word64
findMaxX forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd) [(String, Estimate)]
pairs
    header :: String
header = forall r. PrintfType r => String -> r
printf String
"<svg xmlns=\"http://www.w3.org/2000/svg\" height=\"%i\" width=\"%f\" font-size=\"%i\" font-family=\"sans-serif\" stroke-width=\"2\">\n<g transform=\"translate(%f 0)\">\n" (Word64 -> Word64
svgItemOffset Word64
l forall a. Num a => a -> a -> a
- Word64
15) Double
svgCanvasWidth Word64
svgFontSize Double
svgCanvasMargin
    footer :: String
footer = String
"</g>\n</svg>\n"

svgCanvasWidth :: Double
svgCanvasWidth :: Double
svgCanvasWidth = Double
960

svgCanvasMargin :: Double
svgCanvasMargin :: Double
svgCanvasMargin = Double
10

svgItemOffset :: Word64 -> Word64
svgItemOffset :: Word64 -> Word64
svgItemOffset Word64
i = Word64
22 forall a. Num a => a -> a -> a
+ Word64
55 forall a. Num a => a -> a -> a
* Word64
i

svgFontSize :: Word64
svgFontSize :: Word64
svgFontSize = Word64
16

svgRenderItem :: Word64 -> Word64 -> Double -> TestName -> Estimate -> String
svgRenderItem :: Word64 -> Word64 -> Double -> String -> Estimate -> String
svgRenderItem Word64
i Word64
iMax Double
xMax String
name est :: Estimate
est@(Estimate Measurement
m Word64
stdev) =
  (if forall i a. Num i => [a] -> i
genericLength String
shortTextContent forall a. Num a => a -> a -> a
* Double
glyphWidth forall a. Ord a => a -> a -> Bool
< Double
boxWidth then String
longText else String
shortText) forall a. [a] -> [a] -> [a]
++ String
box
  where
    y :: Word64
y  = Word64 -> Word64
svgItemOffset Word64
i
    y' :: Word64
y' = Word64
y  forall a. Num a => a -> a -> a
+ (Word64
svgFontSize forall a. Num a => a -> a -> a
* Word64
3) forall {a}. Integral a => a -> a -> a
`quot` Word64
8
    y1 :: Word64
y1 = Word64
y' forall a. Num a => a -> a -> a
+ Word64
whiskerMargin
    y2 :: Word64
y2 = Word64
y' forall a. Num a => a -> a -> a
+ Word64
boxHeight forall {a}. Integral a => a -> a -> a
`quot` Word64
2
    y3 :: Word64
y3 = Word64
y' forall a. Num a => a -> a -> a
+ Word64
boxHeight forall a. Num a => a -> a -> a
- Word64
whiskerMargin
    x1 :: Double
x1 = Double
boxWidth forall a. Num a => a -> a -> a
- Double
whiskerWidth
    x2 :: Double
x2 = Double
boxWidth forall a. Num a => a -> a -> a
+ Double
whiskerWidth
    deg :: Word64
deg = (Word64
i forall a. Num a => a -> a -> a
* Word64
360) forall {a}. Integral a => a -> a -> a
`quot` Word64
iMax
    glyphWidth :: Double
glyphWidth = Word64 -> Double
word64ToDouble Word64
svgFontSize forall a. Fractional a => a -> a -> a
/ Double
2

    scale :: Word64 -> Double
scale Word64
w       = Word64 -> Double
word64ToDouble Word64
w forall a. Num a => a -> a -> a
* (Double
svgCanvasWidth forall a. Num a => a -> a -> a
- Double
2 forall a. Num a => a -> a -> a
* Double
svgCanvasMargin) forall a. Fractional a => a -> a -> a
/ Double
xMax
    boxWidth :: Double
boxWidth      = Word64 -> Double
scale (Measurement -> Word64
measTime Measurement
m)
    whiskerWidth :: Double
whiskerWidth  = Word64 -> Double
scale (Word64
2 forall a. Num a => a -> a -> a
* Word64
stdev)
    boxHeight :: Word64
boxHeight     = Word64
22
    whiskerMargin :: Word64
whiskerMargin = Word64
5

    box :: String
box = forall r. PrintfType r => String -> r
printf String
boxTemplate
      (Estimate -> String
prettyEstimate Estimate
est)
      Word64
y' Word64
boxHeight Double
boxWidth Word64
deg Word64
deg
      Word64
deg
      Double
x1 Double
x2 Word64
y2 Word64
y2
      Double
x1 Double
x1 Word64
y1 Word64
y3
      Double
x2 Double
x2 Word64
y1 Word64
y3
    boxTemplate :: String
boxTemplate
      =  String
"<g>\n<title>%s</title>\n"
      forall a. [a] -> [a] -> [a]
++ String
"<rect y=\"%i\" rx=\"5\" height=\"%i\" width=\"%f\" fill=\"hsl(%i, 100%%, 80%%)\" stroke=\"hsl(%i, 100%%, 55%%)\" />\n"
      forall a. [a] -> [a] -> [a]
++ String
"<g stroke=\"hsl(%i, 100%%, 40%%)\">"
      forall a. [a] -> [a] -> [a]
++ String
"<line x1=\"%f\" x2=\"%f\" y1=\"%i\" y2=\"%i\" />\n"
      forall a. [a] -> [a] -> [a]
++ String
"<line x1=\"%f\" x2=\"%f\" y1=\"%i\" y2=\"%i\" />\n"
      forall a. [a] -> [a] -> [a]
++ String
"<line x1=\"%f\" x2=\"%f\" y1=\"%i\" y2=\"%i\" />\n"
      forall a. [a] -> [a] -> [a]
++ String
"</g>\n</g>\n"

    longText :: String
longText = forall r. PrintfType r => String -> r
printf String
longTextTemplate
      Word64
deg
      Word64
y (ShowS
encodeSvg String
name)
      Word64
y Double
boxWidth (Word64 -> String
showPicos4 (Measurement -> Word64
measTime Measurement
m))
    longTextTemplate :: String
longTextTemplate
      =  String
"<g fill=\"hsl(%i, 100%%, 40%%)\">\n"
      forall a. [a] -> [a] -> [a]
++ String
"<text y=\"%i\">%s</text>\n"
      forall a. [a] -> [a] -> [a]
++ String
"<text y=\"%i\" x=\"%f\" text-anchor=\"end\">%s</text>\n"
      forall a. [a] -> [a] -> [a]
++ String
"</g>\n"

    shortTextContent :: String
shortTextContent  = ShowS
encodeSvg String
name forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ Word64 -> String
showPicos4 (Measurement -> Word64
measTime Measurement
m)
    shortText :: String
shortText         = forall r. PrintfType r => String -> r
printf String
shortTextTemplate Word64
deg Word64
y String
shortTextContent
    shortTextTemplate :: String
shortTextTemplate = String
"<text fill=\"hsl(%i, 100%%, 40%%)\" y=\"%i\">%s</text>\n"

encodeSvg :: String -> String
encodeSvg :: ShowS
encodeSvg [] = []
encodeSvg (Char
'<' : String
xs) = Char
'&' forall a. a -> [a] -> [a]
: Char
'l' forall a. a -> [a] -> [a]
: Char
't' forall a. a -> [a] -> [a]
: Char
';' forall a. a -> [a] -> [a]
: ShowS
encodeSvg String
xs
encodeSvg (Char
'&' : String
xs) = Char
'&' forall a. a -> [a] -> [a]
: Char
'a' forall a. a -> [a] -> [a]
: Char
'm' forall a. a -> [a] -> [a]
: Char
'p' forall a. a -> [a] -> [a]
: Char
';' forall a. a -> [a] -> [a]
: ShowS
encodeSvg String
xs
encodeSvg (Char
x : String
xs) = Char
x forall a. a -> [a] -> [a]
: ShowS
encodeSvg String
xs

-- | A path to read baseline results in CSV format, populated by @--baseline@.
--
-- This is an option of 'csvReporter' and can be set only globally.
-- Modifying it via 'adjustOption' or 'localOption' does not have any effect.
-- One can however pass it to 'tryIngredients' 'benchIngredients'.
--
-- @since 0.3
newtype BaselinePath = BaselinePath FilePath
  deriving (Typeable)

instance IsOption (Maybe BaselinePath) where
  defaultValue :: Maybe BaselinePath
defaultValue = forall a. Maybe a
Nothing
  parseValue :: String -> Maybe (Maybe BaselinePath)
parseValue = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> BaselinePath
BaselinePath
  optionName :: Tagged (Maybe BaselinePath) String
optionName = forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"baseline"
  optionHelp :: Tagged (Maybe BaselinePath) String
optionHelp = forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"File with baseline results in CSV format to compare against"

-- | Run benchmarks and report results
-- in a manner similar to 'consoleTestReporter'.
--
-- If @--baseline@ @FILE@ command line option is specified,
-- compare results against an earlier run and mark
-- too slow / too fast benchmarks as failed in accordance to
-- bounds specified by @--fail-if-slower@ @PERCENT@ and @--fail-if-faster@ @PERCENT@.
--
-- @since 0.2
consoleBenchReporter :: Ingredient
consoleBenchReporter :: Ingredient
consoleBenchReporter = [OptionDescription]
-> (OptionSet
    -> IO (String -> Maybe (WithLoHi Result) -> Result -> Result))
-> Ingredient
modifyConsoleReporter [forall v. IsOption v => Proxy v -> OptionDescription
Option (forall {k} (t :: k). Proxy t
Proxy :: Proxy (Maybe BaselinePath))] forall a b. (a -> b) -> a -> b
$ \OptionSet
opts -> do
  Set String
baseline <- case forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts of
    Maybe BaselinePath
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Set a
S.empty
    Just (BaselinePath String
path) -> forall a. Ord a => [a] -> Set a
S.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
joinQuotedFields forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> IO String
readFile String
path forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. a -> IO a
evaluate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NFData a => a -> a
force)
  let pretty :: Estimate -> String
pretty = if Bool
hasGCStats then Estimate -> String
prettyEstimateWithGC else Estimate -> String
prettyEstimate
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ \String
name Maybe (WithLoHi Result)
mDepR Result
r -> case forall a. Read a => String -> Maybe a
safeRead (Result -> String
resultDescription Result
r) of
    Maybe (WithLoHi Estimate)
Nothing  -> Result
r
    Just (WithLoHi Estimate
est Double
lowerBound Double
upperBound) ->
      (if Bool
isAcceptable then forall a. a -> a
id else Result -> Result
forceFail)
      Result
r { resultDescription :: String
resultDescription = Estimate -> String
pretty Estimate
est forall a. [a] -> [a] -> [a]
++ String
bcompareMsg forall a. [a] -> [a] -> [a]
++ Maybe Double -> String
formatSlowDown Maybe Double
mSlowDown }
      where
        isAcceptable :: Bool
isAcceptable = Bool
isAcceptableVsBaseline Bool -> Bool -> Bool
&& Bool
isAcceptableVsBcompare
        mSlowDown :: Maybe Double
mSlowDown = Set String -> String -> Estimate -> Maybe Double
compareVsBaseline Set String
baseline String
name Estimate
est
        slowDown :: Double
slowDown = forall a. a -> Maybe a -> a
fromMaybe Double
1 Maybe Double
mSlowDown
        isAcceptableVsBaseline :: Bool
isAcceptableVsBaseline = Double
slowDown forall a. Ord a => a -> a -> Bool
>= Double
lowerBound Bool -> Bool -> Bool
&& Double
slowDown forall a. Ord a => a -> a -> Bool
<= Double
upperBound
        (Bool
isAcceptableVsBcompare, String
bcompareMsg) = case Maybe (WithLoHi Result)
mDepR of
          Maybe (WithLoHi Result)
Nothing -> (Bool
True, String
"")
          Just (WithLoHi Result
depR Double
depLowerBound Double
depUpperBound) -> case forall a. Read a => String -> Maybe a
safeRead (Result -> String
resultDescription Result
depR) of
            Maybe (WithLoHi Estimate)
Nothing -> (Bool
True, String
"")
            Just (WithLoHi Estimate
depEst Double
_ Double
_) -> let ratio :: Double
ratio = Estimate -> Double
estTime Estimate
est forall a. Fractional a => a -> a -> a
/ Estimate -> Double
estTime Estimate
depEst in
              ( Double
ratio forall a. Ord a => a -> a -> Bool
>= Double
depLowerBound Bool -> Bool -> Bool
&& Double
ratio forall a. Ord a => a -> a -> Bool
<= Double
depUpperBound
              , forall r. PrintfType r => String -> r
printf String
", %.2fx" Double
ratio
              )

-- | A well-formed CSV entry contains an even number of quotes: 0, 2 or more.
joinQuotedFields :: [String] -> [String]
joinQuotedFields :: [String] -> [String]
joinQuotedFields [] = []
joinQuotedFields (String
x : [String]
xs)
  | String -> Bool
areQuotesBalanced String
x = String
x forall a. a -> [a] -> [a]
: [String] -> [String]
joinQuotedFields [String]
xs
  | Bool
otherwise = case forall a. (a -> Bool) -> [a] -> ([a], [a])
span String -> Bool
areQuotesBalanced [String]
xs of
    ([String]
_, [])      -> [] -- malformed CSV
    ([String]
ys, String
z : [String]
zs) -> [String] -> String
unlines (String
x forall a. a -> [a] -> [a]
: [String]
ys forall a. [a] -> [a] -> [a]
++ [String
z]) forall a. a -> [a] -> [a]
: [String] -> [String]
joinQuotedFields [String]
zs
  where
    areQuotesBalanced :: String -> Bool
areQuotesBalanced = forall a. Integral a => a -> Bool
even forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Int
length forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
== Char
'"')

estTime :: Estimate -> Double
estTime :: Estimate -> Double
estTime = Word64 -> Double
word64ToDouble forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measurement -> Word64
measTime forall b c a. (b -> c) -> (a -> b) -> a -> c
. Estimate -> Measurement
estMean

compareVsBaseline :: S.Set String -> TestName -> Estimate -> Maybe Double
compareVsBaseline :: Set String -> String -> Estimate -> Maybe Double
compareVsBaseline Set String
baseline String
name (Estimate Measurement
m Word64
stdev) = case Maybe (Int64, Int64)
mOld of
  Maybe (Int64, Int64)
Nothing -> forall a. Maybe a
Nothing
  Just (Int64
oldTime, Int64
oldDoubleSigma)
    -- time and oldTime must be signed integers to use 'abs'
    | forall {a}. Num a => a -> a
abs (Int64
time forall a. Num a => a -> a -> a
- Int64
oldTime) forall a. Ord a => a -> a -> Bool
< forall a. Ord a => a -> a -> a
max (Int64
2 forall a. Num a => a -> a -> a
* Word64 -> Int64
word64ToInt64 Word64
stdev) Int64
oldDoubleSigma -> forall a. a -> Maybe a
Just Double
1
    | Bool
otherwise -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Int64 -> Double
int64ToDouble Int64
time forall a. Fractional a => a -> a -> a
/ Int64 -> Double
int64ToDouble Int64
oldTime
  where
    time :: Int64
time = Word64 -> Int64
word64ToInt64 forall a b. (a -> b) -> a -> b
$ Measurement -> Word64
measTime Measurement
m

    mOld :: Maybe (Int64, Int64)
    mOld :: Maybe (Int64, Int64)
mOld = do
      let prefix :: String
prefix = ShowS
encodeCsv String
name forall a. [a] -> [a] -> [a]
++ String
","
      (String
line, Set String
furtherLines) <- forall a. Set a -> Maybe (a, Set a)
S.minView forall a b. (a -> b) -> a -> b
$ forall a b. (a, b) -> b
snd forall a b. (a -> b) -> a -> b
$ forall a. Ord a => a -> Set a -> (Set a, Set a)
S.split String
prefix Set String
baseline

      case forall a. Set a -> Maybe (a, Set a)
S.minView Set String
furtherLines of
        Maybe (String, Set String)
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
        Just (String
nextLine, Set String
_) -> case forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix String
prefix String
nextLine of
          Maybe String
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
          -- If there are several lines matching prefix, skip them all.
          -- Should not normally happen, 'csvReporter' prohibits repeating test names.
          Just{}  -> forall a. Maybe a
Nothing

      (String
timeCell, Char
',' : String
rest) <- forall a. (a -> Bool) -> [a] -> ([a], [a])
span (forall a. Eq a => a -> a -> Bool
/= Char
',') forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix String
prefix String
line
      let doubleSigmaCell :: String
doubleSigmaCell = forall a. (a -> Bool) -> [a] -> [a]
takeWhile (forall a. Eq a => a -> a -> Bool
/= Char
',') String
rest
      (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Read a => String -> Maybe a
safeRead String
timeCell forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Read a => String -> Maybe a
safeRead String
doubleSigmaCell

formatSlowDown :: Maybe Double -> String
formatSlowDown :: Maybe Double -> String
formatSlowDown Maybe Double
Nothing = String
""
formatSlowDown (Just Double
ratio) = case Int64
percents forall a. Ord a => a -> a -> Ordering
`compare` Int64
0 of
  Ordering
LT -> forall r. PrintfType r => String -> r
printf String
", %2i%% less than baseline" (-Int64
percents)
  Ordering
EQ -> String
",       same as baseline"
  Ordering
GT -> forall r. PrintfType r => String -> r
printf String
", %2i%% more than baseline" Int64
percents
  where
    percents :: Int64
    percents :: Int64
percents = forall a b. (RealFrac a, Integral b) => a -> b
truncate ((Double
ratio forall a. Num a => a -> a -> a
- Double
1) forall a. Num a => a -> a -> a
* Double
100)

forceFail :: Result -> Result
forceFail :: Result -> Result
forceFail Result
r = Result
r { resultOutcome :: Outcome
resultOutcome = FailureReason -> Outcome
Failure FailureReason
TestFailed, resultShortDescription :: String
resultShortDescription = String
"FAIL" }

data Unique a = None | Unique !a | NotUnique
  deriving (forall a b. a -> Unique b -> Unique a
forall a b. (a -> b) -> Unique a -> Unique b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Unique b -> Unique a
$c<$ :: forall a b. a -> Unique b -> Unique a
fmap :: forall a b. (a -> b) -> Unique a -> Unique b
$cfmap :: forall a b. (a -> b) -> Unique a -> Unique b
Functor)

appendUnique :: Unique a -> Unique a -> Unique a
appendUnique :: forall a. Unique a -> Unique a -> Unique a
appendUnique Unique a
None Unique a
a = Unique a
a
appendUnique Unique a
a Unique a
None = Unique a
a
appendUnique Unique a
_ Unique a
_ = forall a. Unique a
NotUnique

#if MIN_VERSION_base(4,9,0)
instance Semigroup (Unique a) where
  <> :: Unique a -> Unique a -> Unique a
(<>) = forall a. Unique a -> Unique a -> Unique a
appendUnique
#endif

instance Monoid (Unique a) where
  mempty :: Unique a
mempty = forall a. Unique a
None
#if MIN_VERSION_base(4,9,0)
  mappend :: Unique a -> Unique a -> Unique a
mappend = forall a. Semigroup a => a -> a -> a
(<>)
#else
  mappend = appendUnique
#endif

modifyConsoleReporter
    :: [OptionDescription]
    -> (OptionSet -> IO (TestName -> Maybe (WithLoHi Result) -> Result -> Result))
    -> Ingredient
modifyConsoleReporter :: [OptionDescription]
-> (OptionSet
    -> IO (String -> Maybe (WithLoHi Result) -> Result -> Result))
-> Ingredient
modifyConsoleReporter [OptionDescription]
desc' OptionSet
-> IO (String -> Maybe (WithLoHi Result) -> Result -> Result)
iof = [OptionDescription]
-> (OptionSet
    -> Benchmark -> Maybe (StatusMap -> IO (Double -> IO Bool)))
-> Ingredient
TestReporter ([OptionDescription]
desc forall a. [a] -> [a] -> [a]
++ [OptionDescription]
desc') forall a b. (a -> b) -> a -> b
$ \OptionSet
opts Benchmark
tree ->
  let nameSeqs :: IntMap (Seq String)
nameSeqs     = forall a. [(Int, a)] -> IntMap a
IM.fromDistinctAscList forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] forall a b. (a -> b) -> a -> b
$ OptionSet -> Benchmark -> [Seq String]
testNameSeqs OptionSet
opts Benchmark
tree
      namesAndDeps :: IntMap (String, Maybe (WithLoHi Int))
namesAndDeps = forall a. [(Int, a)] -> IntMap a
IM.fromDistinctAscList forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second forall {a}. Unique a -> Maybe a
isSingle)
                   forall a b. (a -> b) -> a -> b
$ IntMap (Seq String)
-> OptionSet -> Benchmark -> [(String, Unique (WithLoHi Int))]
testNamesAndDeps IntMap (Seq String)
nameSeqs OptionSet
opts Benchmark
tree
      modifySMap :: StatusMap -> IO StatusMap
modifySMap   = (OptionSet
-> IO (String -> Maybe (WithLoHi Result) -> Result -> Result)
iof OptionSet
opts forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> b -> a -> c
flip (String -> Maybe (WithLoHi Result) -> Result -> Result)
-> IntMap (String, Maybe (WithLoHi Int), TVar Status)
-> IO StatusMap
postprocessResult
                   forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
IM.intersectionWith (\(String
a, Maybe (WithLoHi Int)
b) TVar Status
c -> (String
a, Maybe (WithLoHi Int)
b, TVar Status
c)) IntMap (String, Maybe (WithLoHi Int))
namesAndDeps
  in (StatusMap -> IO StatusMap
modifySMap forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=>) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OptionSet
-> Benchmark -> Maybe (StatusMap -> IO (Double -> IO Bool))
cb OptionSet
opts Benchmark
tree
  where
    ([OptionDescription]
desc, OptionSet
-> Benchmark -> Maybe (StatusMap -> IO (Double -> IO Bool))
cb) = case Ingredient
consoleTestReporter of
      TestReporter [OptionDescription]
d OptionSet
-> Benchmark -> Maybe (StatusMap -> IO (Double -> IO Bool))
c -> ([OptionDescription]
d, OptionSet
-> Benchmark -> Maybe (StatusMap -> IO (Double -> IO Bool))
c)
      Ingredient
_ -> forall a. HasCallStack => String -> a
error String
"modifyConsoleReporter: consoleTestReporter must be TestReporter"

    isSingle :: Unique a -> Maybe a
isSingle (Unique a
a) = forall a. a -> Maybe a
Just a
a
    isSingle Unique a
_ = forall a. Maybe a
Nothing

testNameSeqs :: OptionSet -> TestTree -> [Seq TestName]
testNameSeqs :: OptionSet -> Benchmark -> [Seq String]
testNameSeqs = forall b. Monoid b => TreeFold b -> OptionSet -> Benchmark -> b
foldTestTree forall b. Monoid b => TreeFold b
trivialFold
  { foldSingle :: forall t. IsTest t => OptionSet -> String -> t -> [Seq String]
foldSingle = forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> a
const forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. a -> [a] -> [a]
:[]) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Seq a
Seq.singleton
#if MIN_VERSION_tasty(1,4,0)
  , foldGroup :: OptionSet -> String -> [Seq String] -> [Seq String]
foldGroup  = forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Seq a -> Seq a
(<|)
#else
  , foldGroup  = map . (<|)
#endif
  }

testNamesAndDeps :: IntMap (Seq TestName) -> OptionSet -> TestTree -> [(TestName, Unique (WithLoHi IM.Key))]
testNamesAndDeps :: IntMap (Seq String)
-> OptionSet -> Benchmark -> [(String, Unique (WithLoHi Int))]
testNamesAndDeps IntMap (Seq String)
im = forall b. Monoid b => TreeFold b -> OptionSet -> Benchmark -> b
foldTestTree forall b. Monoid b => TreeFold b
trivialFold
  { foldSingle :: forall t.
IsTest t =>
OptionSet -> String -> t -> [(String, Unique (WithLoHi Int))]
foldSingle = forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> a
const forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. a -> [a] -> [a]
: []) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (, forall a. Monoid a => a
mempty)
#if MIN_VERSION_tasty(1,4,0)
  , foldGroup :: OptionSet
-> String
-> [(String, Unique (WithLoHi Int))]
-> [(String, Unique (WithLoHi Int))]
foldGroup  = forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a] -> [a]
(++) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. [a] -> [a] -> [a]
++ String
".")
  , foldAfter :: OptionSet
-> DependencyType
-> Expr
-> [(String, Unique (WithLoHi Int))]
-> [(String, Unique (WithLoHi Int))]
foldAfter  = forall a b. a -> b -> a
const forall a.
DependencyType
-> Expr
-> [(a, Unique (WithLoHi Int))]
-> [(a, Unique (WithLoHi Int))]
foldDeps
#else
  , foldGroup  = map . first . (++) . (++ ".")
  , foldAfter  = foldDeps
#endif
  }
  where
    foldDeps :: DependencyType -> Expr -> [(a, Unique (WithLoHi IM.Key))] -> [(a, Unique (WithLoHi IM.Key))]
    foldDeps :: forall a.
DependencyType
-> Expr
-> [(a, Unique (WithLoHi Int))]
-> [(a, Unique (WithLoHi Int))]
foldDeps DependencyType
AllSucceed (And (StringLit String
xs) Expr
p)
      | String
bcomparePrefix forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
xs
      , Just (Double
lo :: Double, Double
hi :: Double) <- forall a. Read a => String -> Maybe a
safeRead forall a b. (a -> b) -> a -> b
$ forall a. Int -> [a] -> [a]
drop (forall (t :: * -> *) a. Foldable t => t a -> Int
length String
bcomparePrefix) String
xs
      = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a -> b) -> a -> b
$ forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => a -> a -> a
mappend forall a b. (a -> b) -> a -> b
$ (\Int
x -> forall a. a -> Double -> Double -> WithLoHi a
WithLoHi Int
x Double
lo Double
hi) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IntMap (Seq String) -> Expr -> Unique Int
findMatchingKeys IntMap (Seq String)
im Expr
p
    foldDeps DependencyType
_ Expr
_ = forall a. a -> a
id

findMatchingKeys :: IntMap (Seq TestName) -> Expr -> Unique IM.Key
findMatchingKeys :: IntMap (Seq String) -> Expr -> Unique Int
findMatchingKeys IntMap (Seq String)
im Expr
pattern =
  forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (\(Int
k, Seq String
v) -> if forall a. Seq String -> M a -> Either String a
withFields Seq String
v ReaderT (Seq String) (Either String) Bool
pat forall a. Eq a => a -> a -> Bool
== forall a b. b -> Either a b
Right Bool
True then forall a. a -> Unique a
Unique Int
k else forall a. Monoid a => a
mempty) forall a b. (a -> b) -> a -> b
$ forall a. IntMap a -> [(Int, a)]
IM.assocs IntMap (Seq String)
im
  where
    pat :: ReaderT (Seq String) (Either String) Bool
pat = Expr -> M Value
eval Expr
pattern forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Value -> ReaderT (Seq String) (Either String) Bool
asB

postprocessResult
    :: (TestName -> Maybe (WithLoHi Result) -> Result -> Result)
    -> IntMap (TestName, Maybe (WithLoHi IM.Key), TVar Status)
    -> IO StatusMap
postprocessResult :: (String -> Maybe (WithLoHi Result) -> Result -> Result)
-> IntMap (String, Maybe (WithLoHi Int), TVar Status)
-> IO StatusMap
postprocessResult String -> Maybe (WithLoHi Result) -> Result -> Result
f IntMap (String, Maybe (WithLoHi Int), TVar Status)
src = do
  IntMap (String, Maybe (WithLoHi Int), TVar Status, TVar Status)
paired <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM IntMap (String, Maybe (WithLoHi Int), TVar Status)
src forall a b. (a -> b) -> a -> b
$ \(String
name, Maybe (WithLoHi Int)
mDepId, TVar Status
tv) -> (String
name, Maybe (WithLoHi Int)
mDepId, TVar Status
tv,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. a -> IO (TVar a)
newTVarIO Status
NotStarted
  let doUpdate :: IO Bool
doUpdate = forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ do
        (Any Bool
anyUpdated, All Bool
allDone) <-
          forall (f :: * -> *) a. Ap f a -> f a
getApp forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap IntMap (String, Maybe (WithLoHi Int), TVar Status, TVar Status)
paired forall a b. (a -> b) -> a -> b
$ \(String
name, Maybe (WithLoHi Int)
mDepId, TVar Status
newTV, TVar Status
oldTV) -> forall (f :: * -> *) a. f a -> Ap f a
Ap forall a b. (a -> b) -> a -> b
$ do
            Status
old <- forall a. TVar a -> STM a
readTVar TVar Status
oldTV
            case Status
old of
              Done{} -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Any
Any Bool
False, Bool -> All
All Bool
True)
              Status
_ -> do
                Status
new <- forall a. TVar a -> STM a
readTVar TVar Status
newTV
                case Status
new of
                  Done Result
res -> do

                    Maybe (WithLoHi Result)
depRes <- case Maybe (WithLoHi Int)
mDepId of
                      Maybe (WithLoHi Int)
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
                      Just (WithLoHi Int
depId Double
lo Double
hi) -> case forall a. Int -> IntMap a -> Maybe a
IM.lookup Int
depId IntMap (String, Maybe (WithLoHi Int), TVar Status)
src of
                        Maybe (String, Maybe (WithLoHi Int), TVar Status)
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
                        Just (String
_, Maybe (WithLoHi Int)
_, TVar Status
depTV) -> do
                          Status
depStatus <- forall a. TVar a -> STM a
readTVar TVar Status
depTV
                          case Status
depStatus of
                            Done Result
dep -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just (forall a. a -> Double -> Double -> WithLoHi a
WithLoHi Result
dep Double
lo Double
hi)
                            Status
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing

                    forall a. TVar a -> a -> STM ()
writeTVar TVar Status
oldTV (Result -> Status
Done (String -> Maybe (WithLoHi Result) -> Result -> Result
f String
name Maybe (WithLoHi Result)
depRes Result
res))
                    forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Any
Any Bool
True, Bool -> All
All Bool
True)
                  -- ignoring Progress nodes, we do not report any
                  -- it would be helpful to have instance Eq Progress
                  Status
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Any
Any Bool
False, Bool -> All
All Bool
False)
        if Bool
anyUpdated Bool -> Bool -> Bool
|| Bool
allDone then forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
allDone else forall a. STM a
retry
      adNauseam :: IO ()
adNauseam = IO Bool
doUpdate forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`unless` IO ()
adNauseam)
  ThreadId
_ <- IO () -> IO ThreadId
forkIO IO ()
adNauseam
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(String
_, Maybe (WithLoHi Int)
_, TVar Status
_, TVar Status
a) -> TVar Status
a) IntMap (String, Maybe (WithLoHi Int), TVar Status, TVar Status)
paired

int64ToDouble :: Int64 -> Double
int64ToDouble :: Int64 -> Double
int64ToDouble = forall a b. (Integral a, Num b) => a -> b
fromIntegral

word64ToInt64 :: Word64 -> Int64
word64ToInt64 :: Word64 -> Int64
word64ToInt64 = forall a b. (Integral a, Num b) => a -> b
fromIntegral

#endif

word64ToDouble :: Word64 -> Double
word64ToDouble :: Word64 -> Double
word64ToDouble = forall a b. (Integral a, Num b) => a -> b
fromIntegral

#if !MIN_VERSION_base(4,10,0) && MIN_VERSION_base(4,6,0)
int64ToWord64 :: Int64 -> Word64
int64ToWord64 = fromIntegral
#endif


#if defined(mingw32_HOST_OS)

#if defined(i386_HOST_ARCH)
#define CCONV stdcall
#else
#define CCONV ccall
#endif

foreign import CCONV unsafe "windows.h GetConsoleOutputCP" getConsoleOutputCP :: IO Word32
foreign import CCONV unsafe "windows.h SetConsoleOutputCP" setConsoleOutputCP :: Word32 -> IO ()

#endif

#ifdef MIN_VERSION_tasty

-- | Map leaf benchmarks ('bench', not 'bgroup') with a provided function,
-- which has an access to leaf's reversed path.
--
-- This helper is useful for bulk application of 'bcompare'.
-- See also 'locateBenchmark'.
--
-- Real world examples:
--
-- * https://hackage.haskell.org/package/chimera-0.3.3.0/src/bench/Bench.hs
-- * https://hackage.haskell.org/package/text-builder-linear-0.1.1/src/bench/Main.hs
--
-- @since 0.3.2
mapLeafBenchmarks :: ([String] -> Benchmark -> Benchmark) -> Benchmark -> Benchmark
mapLeafBenchmarks :: ([String] -> Benchmark -> Benchmark) -> Benchmark -> Benchmark
mapLeafBenchmarks [String] -> Benchmark -> Benchmark
processLeaf = [String] -> Benchmark -> Benchmark
go forall a. Monoid a => a
mempty
  where
    go :: [String] -> Benchmark -> Benchmark
    go :: [String] -> Benchmark -> Benchmark
go [String]
path Benchmark
x = case Benchmark
x of
      SingleTest String
name t
t    -> [String] -> Benchmark -> Benchmark
processLeaf (String
name forall a. a -> [a] -> [a]
: [String]
path) (forall t. IsTest t => String -> t -> Benchmark
SingleTest String
name t
t)
      TestGroup String
name [Benchmark]
tts   -> String -> [Benchmark] -> Benchmark
TestGroup String
name (forall a b. (a -> b) -> [a] -> [b]
map ([String] -> Benchmark -> Benchmark
go (String
name forall a. a -> [a] -> [a]
: [String]
path))  [Benchmark]
tts)
      PlusTestOptions OptionSet -> OptionSet
g Benchmark
tt -> (OptionSet -> OptionSet) -> Benchmark -> Benchmark
PlusTestOptions OptionSet -> OptionSet
g ([String] -> Benchmark -> Benchmark
go [String]
path Benchmark
tt)
      WithResource ResourceSpec a
res IO a -> Benchmark
f   -> forall a. ResourceSpec a -> (IO a -> Benchmark) -> Benchmark
WithResource ResourceSpec a
res ([String] -> Benchmark -> Benchmark
go [String]
path forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> Benchmark
f)
      AskOptions OptionSet -> Benchmark
f         -> (OptionSet -> Benchmark) -> Benchmark
AskOptions ([String] -> Benchmark -> Benchmark
go [String]
path forall b c a. (b -> c) -> (a -> b) -> a -> c
. OptionSet -> Benchmark
f)
      After DependencyType
dep Expr
expr Benchmark
tt    -> DependencyType -> Expr -> Benchmark -> Benchmark
After DependencyType
dep Expr
expr ([String] -> Benchmark -> Benchmark
go [String]
path Benchmark
tt)

-- | Construct an AWK expression to locate an individual element or elements in 'Benchmark'
-- by the suffix of the path. Names are listed in reverse order:
-- from 'bench'\'s own name to a name of the outermost 'bgroup'.
--
-- This function is meant to be used in conjunction with 'bcompare', e. g.,
-- 'bcompare' ('Test.Tasty.Patterns.Printer.printAwkExpr' ('locateBenchmark' @path@)).
-- See also 'mapLeafBenchmarks'.
--
-- Real world examples:
--
-- * https://hackage.haskell.org/package/chimera-0.3.3.0/src/bench/Bench.hs
-- * https://hackage.haskell.org/package/text-builder-linear-0.1.1/src/bench/Main.hs
--
-- @since 0.3.2
locateBenchmark :: [String] -> Expr
locateBenchmark :: [String] -> Expr
locateBenchmark [] = Int -> Expr
IntLit Int
1
locateBenchmark [String]
path
  = forall a. (a -> a -> a) -> [a] -> a
foldl1' Expr -> Expr -> Expr
And
  forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\Int
i String
name -> Expr -> Expr -> Expr
Patterns.EQ (Expr -> Expr
Field (Expr -> Expr -> Expr
Sub Expr
NF (Int -> Expr
IntLit Int
i))) (String -> Expr
StringLit String
name)) [Int
0..] [String]
path

#endif