criterion-1.1.4.0: Robust, reliable performance measurement and analysis

Copyright(c) 2009-2014 Bryan O'Sullivan
LicenseBSD-style
Maintainerbos@serpentine.com
Stabilityexperimental
PortabilityGHC
Safe HaskellTrustworthy
LanguageHaskell98

Criterion.Report

Contents

Description

Reporting functions.

Synopsis

Documentation

formatReport Source #

Arguments

:: [Report] 
-> Text

Hastache template.

-> IO Text 

Format a series of Report values using the given Hastache template.

report :: [Report] -> Criterion () Source #

Write out a series of Report values to a single file, if configured to do so.

tidyTails :: KDE -> KDE Source #

Trim long flat tails from a KDE plot.

Rendering helper functions

data TemplateException Source #

A problem arose with a template.

Constructors

TemplateNotFound FilePath

The template could not be found.

Instances

Eq TemplateException Source # 
Data TemplateException Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TemplateException -> c TemplateException #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TemplateException #

toConstr :: TemplateException -> Constr #

dataTypeOf :: TemplateException -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TemplateException) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TemplateException) #

gmapT :: (forall b. Data b => b -> b) -> TemplateException -> TemplateException #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TemplateException -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TemplateException -> r #

gmapQ :: (forall d. Data d => d -> u) -> TemplateException -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TemplateException -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TemplateException -> m TemplateException #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TemplateException -> m TemplateException #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TemplateException -> m TemplateException #

Read TemplateException Source # 
Show TemplateException Source # 
Generic TemplateException Source # 
Exception TemplateException Source # 
type Rep TemplateException Source # 
type Rep TemplateException = D1 (MetaData "TemplateException" "Criterion.Report" "criterion-1.1.4.0-Drjr6tt0xtzItYFutLLq49" False) (C1 (MetaCons "TemplateNotFound" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)))

loadTemplate Source #

Arguments

:: [FilePath]

Search path.

-> FilePath

Name of template file.

-> IO Text 

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.

includeFile Source #

Arguments

:: MonadIO m 
=> [FilePath]

Directories to search.

-> Text

Name of the file to search for.

-> m Text 

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".

getTemplateDir :: IO FilePath Source #

Return the path to the template and other files used for generating reports.

vector Source #

Arguments

:: (Monad m, Vector v a, MuVar a) 
=> String

Name to use when substituting.

-> v a 
-> MuType m 

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}}

vector2 Source #

Arguments

:: (Monad m, Vector v a, Vector v b, MuVar a, MuVar b) 
=> String

Name for elements from the first vector.

-> String

Name for elements from the second vector.

-> v a

First vector.

-> v b

Second vector.

-> MuType m 

Render the elements of two vectors.