| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Development.Benchmark.Rules
Description
This module provides a bunch of Shake rules to build multiple revisions of a project and analyse their performance.
It assumes a project bench suite composed of examples that runs a fixed set of experiments on every example
Your code must implement all of the GetFoo oracles and the IsExample class,
instantiate the Shake rules, and probably want a set of targets.
The results of the benchmarks and the analysis are recorded in the file system, using the following structure:
build-folder ├── binaries │ └── git-reference │ ├── ghc.path - path to ghc used to build the executable │ └── executable - binary for this version │ └── commitid - Git commit id for this reference ├─ example │ ├── results.csv - aggregated results for all the versions │ └── git-reference │ ├── experiment.gcStats.log - RTS -s output │ ├── experiment.csv - stats for the experiment │ ├── experiment.svg - Graph of bytes over elapsed time │ ├── experiment.diff.svg - idem, including the previous version │ ├── experiment.heap.svg - Heap profile │ ├── experiment.log - bench stdout │ └── results.csv - results of all the experiments for the example ├── results.csv - aggregated results of all the experiments and versions └── experiment.svg - graph of bytes over elapsed time, for all the included versions
For diff graphs, the "previous version" is the preceding entry in the list of versions in the config file. A possible improvement is to obtain this info via `git rev-list`.
Synopsis
- buildRules :: FilePattern -> MkBuildRules BuildSystem -> Rules ()
- data MkBuildRules buildSystem = MkBuildRules {
- findGhc :: buildSystem -> FilePath -> IO FilePath
- executableName :: String
- projectDepends :: Action ()
- buildProject :: buildSystem -> [CmdOption] -> OutputFolder -> Action ()
- benchRules :: RuleResultForExample example => FilePattern -> MkBenchRules BuildSystem example -> Rules ()
- data MkBenchRules buildSystem example = forall setup. MkBenchRules {
- setupProject :: Action setup
- benchProject :: setup -> buildSystem -> [CmdOption] -> BenchProject example -> Action ()
- warmupProject :: buildSystem -> FilePath -> [CmdOption] -> example -> Action ()
- executableName :: String
- data BenchProject example = BenchProject {
- outcsv :: FilePath
- exePath :: FilePath
- exeExtraArgs :: [String]
- example :: example
- experiment :: Escaped String
- data ProfilingMode
- csvRules :: forall example. RuleResultForExample example => FilePattern -> Rules ()
- svgRules :: FilePattern -> Rules ()
- heapProfileRules :: FilePattern -> Rules ()
- phonyRules :: (Traversable t, IsExample e) => String -> String -> ProfilingMode -> FilePath -> t e -> Rules ()
- allTargetsForExample :: IsExample e => ProfilingMode -> FilePath -> e -> Action [FilePath]
- newtype GetExample = GetExample String
- newtype GetExamples = GetExamples ()
- class (Binary e, Eq e, Hashable e, NFData e, Show e, Typeable e) => IsExample e where
- getExampleName :: e -> String
- type RuleResultForExample e = (RuleResult GetExample ~ Maybe e, RuleResult GetExamples ~ [e], IsExample e)
- newtype GetExperiments = GetExperiments ()
- newtype GetVersions = GetVersions ()
- newtype GetCommitId = GetCommitId String
- newtype GetBuildSystem = GetBuildSystem ()
- data BuildSystem
- findGhcForBuildSystem :: BuildSystem -> FilePath -> IO FilePath
- newtype Escaped a = Escaped {
- escaped :: a
- newtype Unescaped a = Unescaped {
- unescaped :: a
- escapeExperiment :: Unescaped String -> Escaped String
- unescapeExperiment :: Escaped String -> Unescaped String
- data GitCommit
Documentation
buildRules :: FilePattern -> MkBuildRules BuildSystem -> Rules () Source #
Rules that drive a build system to build various revisions of a project
data MkBuildRules buildSystem Source #
Constructors
| MkBuildRules | |
Fields
| |
benchRules :: RuleResultForExample example => FilePattern -> MkBenchRules BuildSystem example -> Rules () Source #
data MkBenchRules buildSystem example Source #
Constructors
| forall setup. MkBenchRules | |
Fields
| |
data BenchProject example Source #
Constructors
| BenchProject | |
Fields
| |
data ProfilingMode Source #
Constructors
| NoProfiling | |
| CheapHeapProfiling Seconds |
Instances
| Eq ProfilingMode Source # | |
Defined in Development.Benchmark.Rules Methods (==) :: ProfilingMode -> ProfilingMode -> Bool # (/=) :: ProfilingMode -> ProfilingMode -> Bool # | |
csvRules :: forall example. RuleResultForExample example => FilePattern -> Rules () Source #
Rules to aggregate the CSV output of individual experiments
svgRules :: FilePattern -> Rules () Source #
Rules to produce charts for the GC stats
heapProfileRules :: FilePattern -> Rules () Source #
Arguments
| :: (Traversable t, IsExample e) | |
| => String | prefix |
| -> String | Executable name |
| -> ProfilingMode | |
| -> FilePath | |
| -> t e | |
| -> Rules () |
allTargetsForExample :: IsExample e => ProfilingMode -> FilePath -> e -> Action [FilePath] Source #
newtype GetExample Source #
Constructors
| GetExample String |
Instances
| Eq GetExample Source # | |
Defined in Development.Benchmark.Rules | |
| Show GetExample Source # | |
Defined in Development.Benchmark.Rules Methods showsPrec :: Int -> GetExample -> ShowS # show :: GetExample -> String # showList :: [GetExample] -> ShowS # | |
| Hashable GetExample Source # | |
Defined in Development.Benchmark.Rules | |
| Binary GetExample Source # | |
Defined in Development.Benchmark.Rules | |
| NFData GetExample Source # | |
Defined in Development.Benchmark.Rules Methods rnf :: GetExample -> () # | |
newtype GetExamples Source #
Constructors
| GetExamples () |
Instances
| Eq GetExamples Source # | |
Defined in Development.Benchmark.Rules | |
| Show GetExamples Source # | |
Defined in Development.Benchmark.Rules Methods showsPrec :: Int -> GetExamples -> ShowS # show :: GetExamples -> String # showList :: [GetExamples] -> ShowS # | |
| Hashable GetExamples Source # | |
Defined in Development.Benchmark.Rules | |
| Binary GetExamples Source # | |
Defined in Development.Benchmark.Rules | |
| NFData GetExamples Source # | |
Defined in Development.Benchmark.Rules Methods rnf :: GetExamples -> () # | |
class (Binary e, Eq e, Hashable e, NFData e, Show e, Typeable e) => IsExample e where Source #
Knowledge needed to run an example
Methods
getExampleName :: e -> String Source #
type RuleResultForExample e = (RuleResult GetExample ~ Maybe e, RuleResult GetExamples ~ [e], IsExample e) Source #
newtype GetExperiments Source #
Constructors
| GetExperiments () |
Instances
| Eq GetExperiments Source # | |
Defined in Development.Benchmark.Rules Methods (==) :: GetExperiments -> GetExperiments -> Bool # (/=) :: GetExperiments -> GetExperiments -> Bool # | |
| Show GetExperiments Source # | |
Defined in Development.Benchmark.Rules Methods showsPrec :: Int -> GetExperiments -> ShowS # show :: GetExperiments -> String # showList :: [GetExperiments] -> ShowS # | |
| Hashable GetExperiments Source # | |
Defined in Development.Benchmark.Rules | |
| Binary GetExperiments Source # | |
Defined in Development.Benchmark.Rules Methods put :: GetExperiments -> Put # get :: Get GetExperiments # putList :: [GetExperiments] -> Put # | |
| NFData GetExperiments Source # | |
Defined in Development.Benchmark.Rules Methods rnf :: GetExperiments -> () # | |
| type RuleResult GetExperiments Source # | |
Defined in Development.Benchmark.Rules | |
newtype GetVersions Source #
Constructors
| GetVersions () |
Instances
| Eq GetVersions Source # | |
Defined in Development.Benchmark.Rules | |
| Show GetVersions Source # | |
Defined in Development.Benchmark.Rules Methods showsPrec :: Int -> GetVersions -> ShowS # show :: GetVersions -> String # showList :: [GetVersions] -> ShowS # | |
| Hashable GetVersions Source # | |
Defined in Development.Benchmark.Rules | |
| Binary GetVersions Source # | |
Defined in Development.Benchmark.Rules | |
| NFData GetVersions Source # | |
Defined in Development.Benchmark.Rules Methods rnf :: GetVersions -> () # | |
| type RuleResult GetVersions Source # | |
Defined in Development.Benchmark.Rules | |
newtype GetCommitId Source #
Constructors
| GetCommitId String |
Instances
| Eq GetCommitId Source # | |
Defined in Development.Benchmark.Rules | |
| Show GetCommitId Source # | |
Defined in Development.Benchmark.Rules Methods showsPrec :: Int -> GetCommitId -> ShowS # show :: GetCommitId -> String # showList :: [GetCommitId] -> ShowS # | |
| Hashable GetCommitId Source # | |
Defined in Development.Benchmark.Rules | |
| Binary GetCommitId Source # | |
Defined in Development.Benchmark.Rules | |
| NFData GetCommitId Source # | |
Defined in Development.Benchmark.Rules Methods rnf :: GetCommitId -> () # | |
| type RuleResult GetCommitId Source # | |
Defined in Development.Benchmark.Rules | |
newtype GetBuildSystem Source #
Constructors
| GetBuildSystem () |
Instances
| Eq GetBuildSystem Source # | |
Defined in Development.Benchmark.Rules Methods (==) :: GetBuildSystem -> GetBuildSystem -> Bool # (/=) :: GetBuildSystem -> GetBuildSystem -> Bool # | |
| Show GetBuildSystem Source # | |
Defined in Development.Benchmark.Rules Methods showsPrec :: Int -> GetBuildSystem -> ShowS # show :: GetBuildSystem -> String # showList :: [GetBuildSystem] -> ShowS # | |
| Hashable GetBuildSystem Source # | |
Defined in Development.Benchmark.Rules | |
| Binary GetBuildSystem Source # | |
Defined in Development.Benchmark.Rules Methods put :: GetBuildSystem -> Put # get :: Get GetBuildSystem # putList :: [GetBuildSystem] -> Put # | |
| NFData GetBuildSystem Source # | |
Defined in Development.Benchmark.Rules Methods rnf :: GetBuildSystem -> () # | |
| type RuleResult GetBuildSystem Source # | |
Defined in Development.Benchmark.Rules | |
data BuildSystem Source #
Default build system that handles Cabal and Stack
Instances
findGhcForBuildSystem :: BuildSystem -> FilePath -> IO FilePath Source #
Instances
| Eq a => Eq (Unescaped a) Source # | |
| Show a => Show (Unescaped a) Source # | |
| Hashable a => Hashable (Unescaped a) Source # | |
Defined in Development.Benchmark.Rules | |
| ToJSON a => ToJSON (Unescaped a) Source # | |
Defined in Development.Benchmark.Rules | |
| FromJSON a => FromJSON (Unescaped a) Source # | |
| Binary a => Binary (Unescaped a) Source # | |
| NFData a => NFData (Unescaped a) Source # | |
Defined in Development.Benchmark.Rules | |
Instances
| Eq GitCommit Source # | |
| Show GitCommit Source # | |
| Generic GitCommit Source # | |
| Hashable GitCommit Source # | |
Defined in Development.Benchmark.Rules | |
| ToJSON GitCommit Source # | |
Defined in Development.Benchmark.Rules | |
| FromJSON GitCommit Source # | |
| Binary GitCommit Source # | |
| NFData GitCommit Source # | |
Defined in Development.Benchmark.Rules | |
| type Rep GitCommit Source # | |
Defined in Development.Benchmark.Rules type Rep GitCommit = D1 ('MetaData "GitCommit" "Development.Benchmark.Rules" "shake-bench-0.1.0.3-9iZtOhtMvLmBAUDRjvlAYZ" 'False) (C1 ('MetaCons "GitCommit" 'PrefixI 'True) ((S1 ('MetaSel ('Just "gitName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "parent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "include") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) | |