Agda-2.4.2.4: A dependently typed functional programming language and proof assistant

Safe HaskellNone
LanguageHaskell98

Agda.Utils.Benchmark

Contents

Description

Tools for benchmarking and accumulating results. Nothing Agda-specific in here.

Synopsis

Benchmark trie

type Account a = [a] Source

Account we can bill computation time to.

type CurrentAccount a = Maybe (Account a, CPUTime) Source

Record when we started billing the current account.

data Benchmark a Source

Benchmark structure is a trie, mapping accounts (phases and subphases) to CPU time spent on their performance.

Constructors

Benchmark 

Fields

benchmarkOn :: !Bool

Are we benchmarking at all?

currentAccount :: !(CurrentAccount a)

What are we billing to currently?

timings :: !(Timings a)

The accounts and their accumulated timing bill.

Instances

Null (Benchmark a) Source

Initial benchmark structure (empty).

(Ord a, Pretty a) => Pretty (Benchmark a) Source

Print benchmark as two-column table with totals.

mapBenchmarkOn :: (Bool -> Bool) -> Benchmark a -> Benchmark a Source

Semantic editor combinator.

mapCurrentAccount :: (CurrentAccount a -> CurrentAccount a) -> Benchmark a -> Benchmark a Source

Semantic editor combinator.

mapTimings :: (Timings a -> Timings a) -> Benchmark a -> Benchmark a Source

Semantic editor combinator.

addCPUTime :: Ord a => Account a -> CPUTime -> Benchmark a -> Benchmark a Source

Add to specified CPU time account.

Benchmarking monad.

class (Ord a, Functor m, MonadIO m) => MonadBench a m | m -> a where Source

Monad with access to benchmarking data.

Minimal complete definition

getBenchmark, finally

Methods

getBenchmark :: m (Benchmark a) Source

getsBenchmark :: (Benchmark a -> c) -> m c Source

putBenchmark :: Benchmark a -> m () Source

modifyBenchmark :: (Benchmark a -> Benchmark a) -> m () Source

finally :: m b -> m c -> m b Source

We need to be able to terminate benchmarking in case of an exception.

Instances

MonadBench Phase TCM Source

We store benchmark statistics in an IORef. This enables benchmarking pure computation, see Agda.Benchmarking.

MonadBench Phase TerM Source 
MonadBench a m => MonadBench a (ReaderT r m) Source 

setBenchmarking :: MonadBench a m => Bool -> m () Source

Turn benchmarking on/off.

switchBenchmarking Source

Arguments

:: MonadBench a m 
=> Maybe (Account a)

Maybe new account.

-> m (Maybe (Account a))

Maybe old account.

Bill current account with time up to now. Switch to new account. Return old account (if any).

billTo :: MonadBench a m => Account a -> m c -> m c Source

Bill a computation to a specific account. Works even if the computation is aborted by an exception.

billPureTo :: MonadBench a m => Account a -> c -> m c Source

Bill a pure computation to a specific account.