| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Agda.Benchmarking
Description
Agda-specific benchmarking structure.
Synopsis
- data Phase
- = Parsing
 - | Import
 - | Deserialization
 - | Scoping
 - | Typing
 - | Termination
 - | Positivity
 - | Injectivity
 - | ProjectionLikeness
 - | Coverage
 - | Highlighting
 - | Serialization
 - | DeadCode
 - | Graph
 - | RecCheck
 - | Reduce
 - | Level
 - | Compare
 - | With
 - | ModuleName
 - | Compaction
 - | BuildInterface
 - | Sort
 - | BinaryEncode
 - | Compress
 - | OperatorsExpr
 - | OperatorsPattern
 - | Free
 - | OccursCheck
 - | CheckLHS
 - | CheckRHS
 - | TypeSig
 - | Generalize
 - | InstanceSearch
 - | UnifyIndices
 - | InverseScopeLookup
 - | TopModule TopLevelModuleName
 - | Definition QName
 
 - type Benchmark = Benchmark Phase
 - type Account = Account Phase
 - isModuleAccount :: Account -> Bool
 - isDefAccount :: Account -> Bool
 - isInternalAccount :: Account -> Bool
 - benchmarks :: IORef Benchmark
 - billToIO :: Account -> IO a -> IO a
 - billToPure :: Account -> a -> a
 
Documentation
Phases to allocate CPU time to.
Constructors
| Parsing | Happy parsing and operator parsing.  | 
| Import | Import chasing.  | 
| Deserialization | Reading interface files.  | 
| Scoping | Scope checking and translation to abstract syntax.  | 
| Typing | Type checking and translation to internal syntax.  | 
| Termination | Termination checking.  | 
| Positivity | Positivity checking and polarity computation.  | 
| Injectivity | Injectivity checking.  | 
| ProjectionLikeness | Checking for projection likeness.  | 
| Coverage | Coverage checking and compilation to case trees.  | 
| Highlighting | Generating highlighting info.  | 
| Serialization | Writing interface files.  | 
| DeadCode | Deac code elimination.  | 
| Graph | Subphase for   | 
| RecCheck | Subphase for   | 
| Reduce | Subphase for   | 
| Level | Subphase for   | 
| Compare | Subphase for   | 
| With | Subphase for   | 
| ModuleName | Subphase for   | 
| Compaction | Subphase for   | 
| BuildInterface | Subphase for   | 
| Sort | Subphase for   | 
| BinaryEncode | Subphase for   | 
| Compress | Subphase for   | 
| OperatorsExpr | Subphase for   | 
| OperatorsPattern | Subphase for   | 
| Free | Subphase for   | 
| OccursCheck | Subphase for   | 
| CheckLHS | Subphase for   | 
| CheckRHS | Subphase for   | 
| TypeSig | Subphase for   | 
| Generalize | Subphase for   | 
| InstanceSearch | Subphase for   | 
| UnifyIndices | Subphase for   | 
| InverseScopeLookup | Pretty printing names.  | 
| TopModule TopLevelModuleName | |
| Definition QName | 
Instances
| Eq Phase Source # | |
| Ord Phase Source # | |
| Show Phase Source # | |
| Pretty Phase Source # | |
| MonadBench Phase IO Source # | |
| MonadBench Phase TCM Source # | We store benchmark statistics in an IORef. This enables benchmarking pure computation, see Agda.Benchmarking.  | 
Defined in Agda.TypeChecking.Monad.Base  | |
| MonadBench Phase TerM Source # | |
Defined in Agda.Termination.Monad  | |
isModuleAccount :: Account -> Bool Source #
isDefAccount :: Account -> Bool Source #
isInternalAccount :: Account -> Bool Source #
Benchmarking in the IO monad.
benchmarks :: IORef Benchmark Source #
Global variable to store benchmark statistics.
billToIO :: Account -> IO a -> IO a Source #
Benchmark an IO computation and bill it to the given account.
billToPure :: Account -> a -> a Source #
Benchmark a pure computation and bill it to the given account.