Safe Haskell | None |
---|---|
Language | Haskell2010 |
Measure CPU time for individual phases of the Agda pipeline.
Synopsis
- module Agda.Benchmarking
- class (Ord (BenchPhase m), Functor m, MonadIO m) => MonadBench (m :: Type -> Type)
- type family BenchPhase (m :: Type -> Type)
- getBenchmark :: MonadBench m => m (Benchmark (BenchPhase m))
- updateBenchmarkingStatus :: TCM ()
- billTo :: MonadBench m => Account (BenchPhase m) -> m c -> m c
- billPureTo :: MonadBench m => Account (BenchPhase m) -> c -> m c
- billToCPS :: MonadBench m => Account (BenchPhase m) -> ((b -> m c) -> m c) -> (b -> m c) -> m c
- reset :: MonadBench m => m ()
- print :: MonadTCM tcm => tcm ()
Documentation
module Agda.Benchmarking
class (Ord (BenchPhase m), Functor m, MonadIO m) => MonadBench (m :: Type -> Type) Source #
Monad with access to benchmarking data.
Instances
type family BenchPhase (m :: Type -> Type) Source #
Instances
type BenchPhase TerM Source # | |
Defined in Agda.Termination.Monad | |
type BenchPhase TCM Source # | |
Defined in Agda.TypeChecking.Monad.Base | |
type BenchPhase IO Source # | |
Defined in Agda.Benchmarking | |
type BenchPhase (ListT m) Source # | |
Defined in Agda.Utils.Benchmark | |
type BenchPhase (ExceptT e m) Source # | |
Defined in Agda.Utils.Benchmark | |
type BenchPhase (ReaderT r m) Source # | |
Defined in Agda.Utils.Benchmark | |
type BenchPhase (StateT r m) Source # | |
Defined in Agda.Utils.Benchmark | |
type BenchPhase (WriterT w m) Source # | |
Defined in Agda.Utils.Benchmark |
getBenchmark :: MonadBench m => m (Benchmark (BenchPhase m)) Source #
updateBenchmarkingStatus :: TCM () Source #
When profile options are set or changed, we need to turn benchmarking on or off.
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.
billPureTo :: MonadBench m => Account (BenchPhase m) -> c -> m c Source #
Bill a pure computation to a specific account.
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.
reset :: MonadBench m => m () Source #
Resets the account and the timing information.