Agda-2.6.2.0.20211129: A dependently typed functional programming language and proof assistant
Safe HaskellSafe-Inferred
LanguageHaskell2010

Agda.Utils.Benchmark

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 BenchmarkOn a Source #

Instances

Instances details
Generic (BenchmarkOn a) Source # 
Instance details

Defined in Agda.Utils.Benchmark

Associated Types

type Rep (BenchmarkOn a) :: Type -> Type #

Methods

from :: BenchmarkOn a -> Rep (BenchmarkOn a) x #

to :: Rep (BenchmarkOn a) x -> BenchmarkOn a #

NFData a => NFData (BenchmarkOn a) Source # 
Instance details

Defined in Agda.Utils.Benchmark

Methods

rnf :: BenchmarkOn a -> () #

type Rep (BenchmarkOn a) Source # 
Instance details

Defined in Agda.Utils.Benchmark

type Rep (BenchmarkOn a) = D1 ('MetaData "BenchmarkOn" "Agda.Utils.Benchmark" "Agda-2.6.2.0.20211129-inplace" 'False) (C1 ('MetaCons "BenchmarkOff" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BenchmarkOn" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BenchmarkSome" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Account a -> Bool)))))

data Benchmark a Source #

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

Constructors

Benchmark 

Fields

Instances

Instances details
Null (Benchmark a) Source #

Initial benchmark structure (empty).

Instance details

Defined in Agda.Utils.Benchmark

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

Print benchmark as three-column table with totals.

Instance details

Defined in Agda.Utils.Benchmark

Generic (Benchmark a) Source # 
Instance details

Defined in Agda.Utils.Benchmark

Associated Types

type Rep (Benchmark a) :: Type -> Type #

Methods

from :: Benchmark a -> Rep (Benchmark a) x #

to :: Rep (Benchmark a) x -> Benchmark a #

NFData a => NFData (Benchmark a) Source # 
Instance details

Defined in Agda.Utils.Benchmark

Methods

rnf :: Benchmark a -> () #

type Rep (Benchmark a) Source # 
Instance details

Defined in Agda.Utils.Benchmark

type Rep (Benchmark a) = D1 ('MetaData "Benchmark" "Agda.Utils.Benchmark" "Agda-2.6.2.0.20211129-inplace" 'False) (C1 ('MetaCons "Benchmark" 'PrefixI 'True) (S1 ('MetaSel ('Just "benchmarkOn") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BenchmarkOn a)) :*: (S1 ('MetaSel ('Just "currentAccount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CurrentAccount a)) :*: S1 ('MetaSel ('Just "timings") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Timings a)))))

mapBenchmarkOn :: (BenchmarkOn a -> BenchmarkOn a) -> 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 (BenchPhase m), Functor m, MonadIO m) => MonadBench m where Source #

Monad with access to benchmarking data.

Minimal complete definition

getBenchmark, finally

Associated Types

type BenchPhase m Source #

Methods

getBenchmark :: m (Benchmark (BenchPhase m)) Source #

putBenchmark :: Benchmark (BenchPhase m) -> m () Source #

modifyBenchmark :: (Benchmark (BenchPhase m) -> Benchmark (BenchPhase m)) -> m () Source #

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

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

Instances

Instances details
MonadBench TerM Source # 
Instance details

Defined in Agda.Termination.Monad

Associated Types

type BenchPhase TerM Source #

MonadBench TCM Source #

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

Instance details

Defined in Agda.TypeChecking.Monad.Base

Associated Types

type BenchPhase TCM Source #

MonadBench IO Source # 
Instance details

Defined in Agda.Benchmarking

Associated Types

type BenchPhase IO Source #

MonadBench m => MonadBench (ListT m) Source # 
Instance details

Defined in Agda.Utils.Benchmark

Associated Types

type BenchPhase (ListT m) Source #

MonadBench m => MonadBench (ExceptT e m) Source # 
Instance details

Defined in Agda.Utils.Benchmark

Associated Types

type BenchPhase (ExceptT e m) Source #

MonadBench m => MonadBench (ReaderT r m) Source # 
Instance details

Defined in Agda.Utils.Benchmark

Associated Types

type BenchPhase (ReaderT r m) Source #

MonadBench m => MonadBench (StateT r m) Source # 
Instance details

Defined in Agda.Utils.Benchmark

Associated Types

type BenchPhase (StateT r m) Source #

(MonadBench m, Monoid w) => MonadBench (WriterT w m) Source # 
Instance details

Defined in Agda.Utils.Benchmark

Associated Types

type BenchPhase (WriterT w m) Source #

setBenchmarking :: MonadBench m => BenchmarkOn (BenchPhase m) -> m () Source #

Turn benchmarking on/off.

switchBenchmarking Source #

Arguments

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

Maybe new account.

-> m (Maybe (Account (BenchPhase m)))

Maybe old account.

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

reset :: MonadBench m => m () Source #

Resets the account and the timing information.

billTo :: MonadBench m => Account (BenchPhase m) -> m c -> m c Source #

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

billToCPS :: MonadBench m => Account (BenchPhase m) -> ((b -> m c) -> m c) -> (b -> m c) -> m c Source #

Bill a CPS function to an account. Can't handle exceptions.

billPureTo :: MonadBench m => Account (BenchPhase m) -> c -> m c Source #

Bill a pure computation to a specific account.