-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Robust, reliable performance measurement and analysis -- -- This library provides a powerful but simple way to measure software -- performance. It provides both a framework for executing and analysing -- benchmarks and a set of driver functions that makes it easy to build -- and run benchmarks, and to analyse their results. -- -- The fastest way to get started is to read the documentation and -- examples in the Criterion.Main module. -- -- For an example of the kinds of reports that criterion generates, see -- http://bos.github.com/criterion/. @package criterion @version 0.6.0.1 -- | Analysis types. module Criterion.Analysis.Types -- | Outliers from sample data, calculated using the boxplot technique. data Outliers Outliers :: {-# UNPACK #-} !Int64 -> {-# UNPACK #-} !Int64 -> {-# UNPACK #-} !Int64 -> {-# UNPACK #-} !Int64 -> {-# UNPACK #-} !Int64 -> Outliers samplesSeen :: Outliers -> {-# UNPACK #-} !Int64 -- | More than 3 times the interquartile range (IQR) below the first -- quartile. lowSevere :: Outliers -> {-# UNPACK #-} !Int64 -- | Between 1.5 and 3 times the IQR below the first quartile. lowMild :: Outliers -> {-# UNPACK #-} !Int64 -- | Between 1.5 and 3 times the IQR above the third quartile. highMild :: Outliers -> {-# UNPACK #-} !Int64 -- | More than 3 times the IQR above the third quartile. highSevere :: Outliers -> {-# UNPACK #-} !Int64 -- | A description of the extent to which outliers in the sample data -- affect the sample mean and standard deviation. data OutlierEffect -- | Less than 1% effect. Unaffected :: OutlierEffect -- | Between 1% and 10%. Slight :: OutlierEffect -- | Between 10% and 50%. Moderate :: OutlierEffect -- | Above 50% (i.e. measurements are useless). Severe :: OutlierEffect -- | Analysis of the extent to which outliers in a sample affect its -- standard deviation (and to some extent, its mean). data OutlierVariance OutlierVariance :: OutlierEffect -> String -> Double -> OutlierVariance -- | Qualitative description of effect. ovEffect :: OutlierVariance -> OutlierEffect -- | Brief textual description of effect. ovDesc :: OutlierVariance -> String -- | Quantitative description of effect (a fraction between 0 and 1). ovFraction :: OutlierVariance -> Double -- | Result of a bootstrap analysis of a non-parametric sample. data SampleAnalysis SampleAnalysis :: Estimate -> Estimate -> OutlierVariance -> SampleAnalysis anMean :: SampleAnalysis -> Estimate anStdDev :: SampleAnalysis -> Estimate anOutlierVar :: SampleAnalysis -> OutlierVariance instance Typeable Outliers instance Typeable OutlierEffect instance Typeable OutlierVariance instance Typeable SampleAnalysis instance Eq Outliers instance Read Outliers instance Show Outliers instance Data Outliers instance Eq OutlierEffect instance Ord OutlierEffect instance Read OutlierEffect instance Show OutlierEffect instance Data OutlierEffect instance Eq OutlierVariance instance Read OutlierVariance instance Show OutlierVariance instance Data OutlierVariance instance Eq SampleAnalysis instance Show SampleAnalysis instance Data SampleAnalysis instance NFData SampleAnalysis instance NFData OutlierVariance instance Monoid Outliers instance NFData OutlierEffect instance NFData Outliers -- | Types for benchmarking. -- -- The core class is Benchmarkable, which admits both pure -- functions and IO actions. -- -- For a pure function of type a -> b, the benchmarking -- harness calls this function repeatedly, each time with a different -- Int argument, and reduces the result the function returns to -- weak head normal form. If you need the result reduced to normal form, -- that is your responsibility. -- -- For an action of type IO a, the benchmarking harness calls -- the action repeatedly, but does not reduce the result. module Criterion.Types -- | A benchmarkable function or action. class Benchmarkable a run :: Benchmarkable a => a -> Int -> IO () -- | A benchmark may consist of either a single Benchmarkable item -- with a name, created with bench, or a (possibly nested) group -- of Benchmarks, created with bgroup. data Benchmark Benchmark :: String -> b -> Benchmark BenchGroup :: String -> [Benchmark] -> Benchmark -- | A container for a pure function to benchmark, and an argument to -- supply to it each time it is evaluated. data Pure -- | Apply an argument to a function, and evaluate the result to weak head -- normal form (WHNF). whnf :: (a -> b) -> a -> Pure -- | Apply an argument to a function, and evaluate the result to head -- normal form (NF). nf :: NFData b => (a -> b) -> a -> Pure -- | Perform an action, then evaluate its result to head normal form. This -- is particularly useful for forcing a lazy IO action to be completely -- performed. nfIO :: NFData a => IO a -> IO () -- | Perform an action, then evaluate its result to weak head normal form -- (WHNF). This is useful for forcing an IO action whose result is an -- expression to be evaluated down to a more useful value. whnfIO :: IO a -> IO () -- | Create a single benchmark. bench :: Benchmarkable b => String -> b -> Benchmark -- | Group several benchmarks together under a common name. bgroup :: String -> [Benchmark] -> Benchmark -- | Retrieve the names of all benchmarks. Grouped benchmarks are prefixed -- with the name of the group they're in. benchNames :: Benchmark -> [String] instance Show Benchmark instance Benchmarkable (IO a) instance Benchmarkable Pure -- | Benchmark measurement code. module Criterion.Measurement getTime :: IO Double runForAtLeast :: Double -> Int -> (Int -> IO a) -> IO (Double, Int, a) secs :: Double -> String time :: IO a -> IO (Double, a) time_ :: IO a -> IO Double -- | Benchmarking configuration. module Criterion.Config -- | Top-level program configuration. data Config Config :: Last String -> Last Double -> Last Bool -> PrintExit -> Last Int -> Last FilePath -> Last Int -> Last FilePath -> Last FilePath -> Last Verbosity -> Config -- | The "version" banner to print. cfgBanner :: Config -> Last String -- | Confidence interval to use. cfgConfInterval :: Config -> Last Double -- | Whether to run the GC between passes. cfgPerformGC :: Config -> Last Bool -- | Whether to print information and exit. cfgPrintExit :: Config -> PrintExit -- | Number of resamples to perform. cfgResamples :: Config -> Last Int -- | Filename of report. cfgReport :: Config -> Last FilePath -- | Number of samples to collect. cfgSamples :: Config -> Last Int -- | Filename of summary CSV. cfgSummaryFile :: Config -> Last FilePath -- | Filename of report template. cfgTemplate :: Config -> Last FilePath -- | Whether to run verbosely. cfgVerbosity :: Config -> Last Verbosity -- | Print some information and exit, without running any benchmarks. data PrintExit -- | Do not actually print-and-exit. (Default.) Nada :: PrintExit -- | Print a list of known benchmarks. List :: PrintExit -- | Print version information (if known). Version :: PrintExit -- | Print a help/usaage message. Help :: PrintExit -- | Control the amount of information displayed. data Verbosity Quiet :: Verbosity Normal :: Verbosity Verbose :: Verbosity -- | A configuration with sensible defaults. defaultConfig :: Config -- | Deconstructor for Last values. fromLJ :: (Config -> Last a) -> Config -> a -- | Constructor for Last values. ljust :: a -> Last a instance Typeable Verbosity instance Typeable PrintExit instance Typeable Config instance Eq Verbosity instance Ord Verbosity instance Bounded Verbosity instance Enum Verbosity instance Read Verbosity instance Show Verbosity instance Eq PrintExit instance Ord PrintExit instance Bounded PrintExit instance Enum PrintExit instance Read PrintExit instance Show PrintExit instance Data PrintExit instance Eq Config instance Read Config instance Show Config instance Monoid Config instance Monoid PrintExit -- | The environment in which most criterion code executes. module Criterion.Monad -- | The monad in which most criterion code executes. data Criterion a getConfig :: Criterion Config getConfigItem :: (Config -> a) -> Criterion a withConfig :: Config -> Criterion a -> IO a instance Functor Criterion instance Monad Criterion instance MonadReader Config Criterion instance MonadIO Criterion -- | Input and output actions. module Criterion.IO -- | An internal class that acts like Printf/HPrintf. -- -- The implementation is visible to the rest of the program, but the -- details of the class are not. class CritHPrintfType a -- | Print a "normal" note. note :: CritHPrintfType r => String -> r -- | Print an error message. printError :: CritHPrintfType r => String -> r -- | Print verbose output. prolix :: CritHPrintfType r => String -> r -- | Add to summary CSV (if applicable) summary :: String -> Criterion () instance (CritHPrintfType r, PrintfArg a) => CritHPrintfType (a -> r) instance CritHPrintfType (IO a) instance CritHPrintfType (Criterion a) -- | Analysis code for benchmarks. module Criterion.Analysis -- | Outliers from sample data, calculated using the boxplot technique. data Outliers Outliers :: {-# UNPACK #-} !Int64 -> {-# UNPACK #-} !Int64 -> {-# UNPACK #-} !Int64 -> {-# UNPACK #-} !Int64 -> {-# UNPACK #-} !Int64 -> Outliers samplesSeen :: Outliers -> {-# UNPACK #-} !Int64 -- | More than 3 times the interquartile range (IQR) below the first -- quartile. lowSevere :: Outliers -> {-# UNPACK #-} !Int64 -- | Between 1.5 and 3 times the IQR below the first quartile. lowMild :: Outliers -> {-# UNPACK #-} !Int64 -- | Between 1.5 and 3 times the IQR above the third quartile. highMild :: Outliers -> {-# UNPACK #-} !Int64 -- | More than 3 times the IQR above the third quartile. highSevere :: Outliers -> {-# UNPACK #-} !Int64 -- | A description of the extent to which outliers in the sample data -- affect the sample mean and standard deviation. data OutlierEffect -- | Less than 1% effect. Unaffected :: OutlierEffect -- | Between 1% and 10%. Slight :: OutlierEffect -- | Between 10% and 50%. Moderate :: OutlierEffect -- | Above 50% (i.e. measurements are useless). Severe :: OutlierEffect -- | Analysis of the extent to which outliers in a sample affect its -- standard deviation (and to some extent, its mean). data OutlierVariance OutlierVariance :: OutlierEffect -> String -> Double -> OutlierVariance -- | Qualitative description of effect. ovEffect :: OutlierVariance -> OutlierEffect -- | Brief textual description of effect. ovDesc :: OutlierVariance -> String -- | Quantitative description of effect (a fraction between 0 and 1). ovFraction :: OutlierVariance -> Double -- | Result of a bootstrap analysis of a non-parametric sample. data SampleAnalysis SampleAnalysis :: Estimate -> Estimate -> OutlierVariance -> SampleAnalysis anMean :: SampleAnalysis -> Estimate anStdDev :: SampleAnalysis -> Estimate anOutlierVar :: SampleAnalysis -> OutlierVariance -- | Perform a bootstrap analysis of a non-parametric sample. analyseSample :: Double -> Sample -> Int -> IO SampleAnalysis -- | Multiply the Estimates in an analysis by the given value, -- using scale. scale :: Double -> SampleAnalysis -> SampleAnalysis -- | Display the mean of a Sample, and characterise the outliers -- present in the sample. analyseMean :: Sample -> Int -> Criterion Double -- | Count the total number of outliers in a sample. countOutliers :: Outliers -> Int64 -- | Classify outliers in a data set, using the boxplot technique. classifyOutliers :: Sample -> Outliers -- | Display a report of the Outliers present in a Sample. noteOutliers :: Outliers -> Criterion () -- | Compute the extent to which outliers in the sample data affect the -- sample mean and standard deviation. outlierVariance :: Estimate -> Estimate -> Double -> OutlierVariance -- | Code for measuring and characterising the execution environment. module Criterion.Environment -- | Measured aspects of the execution environment. data Environment Environment :: {-# UNPACK #-} !Double -> {-# UNPACK #-} !Double -> Environment -- | Clock resolution (in seconds). envClockResolution :: Environment -> {-# UNPACK #-} !Double -- | The cost of a single clock call (in seconds). envClockCost :: Environment -> {-# UNPACK #-} !Double -- | Measure the execution environment. measureEnvironment :: Criterion Environment instance Typeable Environment instance Eq Environment instance Read Environment instance Show Environment -- | Reporting functions. module Criterion.Report data Report Report :: Int -> String -> Sample -> SampleAnalysis -> Outliers -> Report reportNumber :: Report -> Int reportName :: Report -> String reportTimes :: Report -> Sample reportAnalysis :: Report -> SampleAnalysis reportOutliers :: Report -> Outliers -- | Format a series of Report values using the given Hastache -- template. formatReport :: [Report] -> ByteString -> IO ByteString -- | Write out a series of Report values to a single file, if -- configured to do so. report :: [Report] -> Criterion () -- | A problem arose with a template. data TemplateException -- | The template could not be found. TemplateNotFound :: FilePath -> TemplateException -- | Load a Hastache template file. -- -- If the name is an absolute or relative path, the search path is -- not used, and the name is treated as a literal path. -- -- This function throws a TemplateException if the template could -- not be found, or an IOException if no template could be loaded. loadTemplate :: [FilePath] -> FilePath -> IO ByteString -- | Attempt to include the contents of a file based on a search path. -- Returns empty if the search fails or the file could not be -- read. -- -- Intended for use with Hastache's MuLambdaM, for example: -- --
--   context "include" = MuLambdaM $ includeFile [templateDir]
--   
-- -- Hastache template expansion is not performed within the -- included file. No attempt is made to ensure that the included file -- path is safe, i.e. that it does not refer to an unexpected file such -- as "etcpasswd". includeFile :: MonadIO m => [FilePath] -> ByteString -> m ByteString -- | The path to the template and other files used for generating reports. templateDir :: FilePath -- | Render the elements of a vector. -- -- For example, given this piece of Haskell: -- --
--   mkStrContext $ \name ->
--    case name of
--      "foo" -> vector "x" foo
--   
-- -- It will substitute each value in the vector for x in the -- following Hastache template: -- --
--   {{#foo}}
--    {{x}}
--   {{/foo}}
--   
vector :: (Monad m, Vector v a, MuVar a) => String -> v a -> MuType m -- | Render the elements of two vectors. vector2 :: (Monad m, Vector v a, Vector v b, MuVar a, MuVar b) => String -> String -> v a -> v b -> MuType m instance Typeable Report instance Typeable TemplateException instance Eq Report instance Show Report instance Data Report instance Eq TemplateException instance Show TemplateException instance Data TemplateException instance Exception TemplateException -- | Core benchmarking code. module Criterion -- | A benchmarkable function or action. class Benchmarkable a run :: Benchmarkable a => a -> Int -> IO () -- | A benchmark may consist of either a single Benchmarkable item -- with a name, created with bench, or a (possibly nested) group -- of Benchmarks, created with bgroup. data Benchmark -- | A container for a pure function to benchmark, and an argument to -- supply to it each time it is evaluated. data Pure -- | Apply an argument to a function, and evaluate the result to head -- normal form (NF). nf :: NFData b => (a -> b) -> a -> Pure -- | Apply an argument to a function, and evaluate the result to weak head -- normal form (WHNF). whnf :: (a -> b) -> a -> Pure -- | Perform an action, then evaluate its result to head normal form. This -- is particularly useful for forcing a lazy IO action to be completely -- performed. nfIO :: NFData a => IO a -> IO () -- | Perform an action, then evaluate its result to weak head normal form -- (WHNF). This is useful for forcing an IO action whose result is an -- expression to be evaluated down to a more useful value. whnfIO :: IO a -> IO () -- | Create a single benchmark. bench :: Benchmarkable b => String -> b -> Benchmark -- | Group several benchmarks together under a common name. bgroup :: String -> [Benchmark] -> Benchmark -- | Run a single benchmark, and return timings measured when executing it. runBenchmark :: Benchmarkable b => Environment -> b -> Criterion Sample -- | Run, and analyse, one or more benchmarks. runAndAnalyse :: (String -> Bool) -> Environment -> Benchmark -> Criterion () -- | Wrappers for compiling and running benchmarks quickly and easily. See -- defaultMain below for an example. module Criterion.Main -- | A benchmarkable function or action. class Benchmarkable a run :: Benchmarkable a => a -> Int -> IO () -- | A benchmark may consist of either a single Benchmarkable item -- with a name, created with bench, or a (possibly nested) group -- of Benchmarks, created with bgroup. data Benchmark -- | A container for a pure function to benchmark, and an argument to -- supply to it each time it is evaluated. data Pure -- | Create a single benchmark. bench :: Benchmarkable b => String -> b -> Benchmark -- | Group several benchmarks together under a common name. bgroup :: String -> [Benchmark] -> Benchmark -- | Apply an argument to a function, and evaluate the result to head -- normal form (NF). nf :: NFData b => (a -> b) -> a -> Pure -- | Apply an argument to a function, and evaluate the result to weak head -- normal form (WHNF). whnf :: (a -> b) -> a -> Pure -- | Perform an action, then evaluate its result to head normal form. This -- is particularly useful for forcing a lazy IO action to be completely -- performed. nfIO :: NFData a => IO a -> IO () -- | Perform an action, then evaluate its result to weak head normal form -- (WHNF). This is useful for forcing an IO action whose result is an -- expression to be evaluated down to a more useful value. whnfIO :: IO a -> IO () -- | An entry point that can be used as a main function. -- --
--   import Criterion.Main
--   
--   fib :: Int -> Int
--   fib 0 = 0
--   fib 1 = 1
--   fib n = fib (n-1) + fib (n-2)
--   
--   main = defaultMain [
--          bgroup "fib" [ bench "10" $ whnf fib 10
--                       , bench "35" $ whnf fib 35
--                       , bench "37" $ whnf fib 37
--                       ]
--                      ]
--   
defaultMain :: [Benchmark] -> IO () -- | An entry point that can be used as a main function, with -- configurable defaults. -- -- Example: -- --
--   import Criterion.Config
--   import qualified Criterion.MultiMap as M
--   import Criterion.Main
--   
--   myConfig = defaultConfig {
--                -- Always GC between runs.
--                cfgPerformGC = ljust True
--              }
--   
--   main = defaultMainWith myConfig (return ()) [
--            bench "fib 30" $ whnf fib 30
--          ]
--   
-- -- If you save the above example as "Fib.hs", you should be able -- to compile it as follows: -- --
--   ghc -O --make Fib
--   
-- -- Run "Fib --help" on the command line to get a list of command -- line options. defaultMainWith :: Config -> Criterion () -> [Benchmark] -> IO () -- | The standard options accepted on the command line. defaultOptions :: [OptDescr (IO Config)] -- | Parse command line options. parseArgs :: Config -> [OptDescr (IO Config)] -> [String] -> IO (Config, [String])