hsbencher-1.5.3.1: Flexible benchmark runner for Haskell and non-Haskell benchmarks.

Safe HaskellNone

HSBencher.Types

Contents

Description

All the core types used by the rest of the HSBencher codebase.

Synopsis

Benchmark building

The basic types for describing a single benchmark.

mkBenchmark :: FilePath -> [String] -> BenchSpace a -> Benchmark aSource

Make a Benchmark data structure given the core, required set of fields, and uses defaults to fill in the rest. Takes target, cmdargs, configs.

data Benchmark a Source

The all-inclusive datatype for a single Benchmark. Do NOT construct values of this type directly. Rather, you should make your code robust against future addition of fields to this datatype. Use mkBenchmark followed by customizing only the fields you need.

Constructors

Benchmark 

Fields

target :: FilePath

The target file or directory.

cmdargs :: [String]

Command line argument to feed the benchmark executable.

configs :: BenchSpace a

The configration space to iterate over.

progname :: Maybe String

Optional name to use INSTEAD of the basename from target.

benchTimeOut :: Maybe Double

Specific timeout for this benchmark in seconds. Overrides global setting.

Instances

Eq a => Eq (Benchmark a) 
Ord a => Ord (Benchmark a) 
Show a => Show (Benchmark a) 
Generic (Benchmark a) 
Out a => Out (Benchmark a) 

type RunFlags = [String]Source

The arguments passed (in a build-method specific way) to the running benchmark.

type CompileFlags = [String]Source

The arguments passed (in a build-method specific way) into the compilation process.

Build method interface and applicability

A build method is applicable to a subset of target files (FilePredicate) and has a particular interface that HSbencher relies upon.

data BuildMethod Source

A completely encapsulated method of building benchmarks. Cabal and Makefiles are two examples of this. The user may extend it with their own methods.

Constructors

BuildMethod 

Fields

methodName :: String

Identifies this build method for humans. , buildsFiles :: FilePredicate , canBuild :: FilePath -> IO Bool

canBuild :: FilePredicate

Can this method build a given file/directory?

concurrentBuild :: Bool

More than one build can happen at once. This implies that compile always returns StandAloneBinary.

compile :: PathRegistry -> BuildID -> CompileFlags -> FilePath -> BenchM BuildResult
 
clean :: PathRegistry -> BuildID -> FilePath -> BenchM ()

Clean any left-over build results.

setThreads :: Maybe (Int -> [ParamSetting])

Synthesize a list of compile/runtime settings that will control the number of threads.

Instances

data BuildResult Source

The result of doing a build. Note that compile can will throw an exception if compilation fails.

Constructors

StandAloneBinary FilePath

This binary can be copied and executed whenever.

RunInPlace (RunFlags -> EnvVars -> CommandDescr)

In this case the build return what you need to do the benchmark run, but the directory contents cannot be touched until after than run is finished.

Instances

data FilePredicate Source

A description of a set of files. The description may take one of multiple forms.

Constructors

WithExtension String

E.g. .hs, WITH the dot.

IsExactly String

E.g. Makefile | SatisfiesPredicate (String -> Bool)

InDirectoryWithExactlyOne FilePredicate

A common pattern. For example, we can build a file foo.c, if it lives in a directory with exactly one Makefile.

PredOr FilePredicate FilePredicate

Logical or.

AnyFile 

filePredCheck :: FilePredicate -> FilePath -> IO (Maybe FilePath)Source

This function gives meaning to the FilePred type. It returns a filepath to signal True and Nothing otherwise.

Benchmark configuration spaces

Describe how many different ways you want to run your benchmarks.

data BenchSpace meaning Source

A datatype for describing (generating) benchmark configuration spaces. This is accomplished by nested conjunctions and disjunctions. For example, varying threads from 1-32 would be a 32-way Or. Combining that with profiling on/off (product) would create a 64-config space.

While the ParamSetting provides an *implementation* of the behavior, this datatype can also be decorated with a (more easily machine readable) meaning of the corresponding setting. For example, indicating that the setting controls the number of threads.

Constructors

And [BenchSpace meaning] 
Or [BenchSpace meaning] 
Set meaning ParamSetting 

Instances

Eq meaning => Eq (BenchSpace meaning) 
Ord meaning => Ord (BenchSpace meaning) 
Read meaning => Read (BenchSpace meaning) 
Show meaning => Show (BenchSpace meaning) 
Generic (BenchSpace meaning) 
Out a => Out (BenchSpace a) 

data ParamSetting Source

Different types of parameters that may be set or varied.

Constructors

RuntimeParam String

String contains runtime options, expanded and tokenized by the shell.

CompileParam String

String contains compile-time options, expanded and tokenized by the shell.

RuntimeEnv String String

The name of the env var and its value, respectively. For now Env Vars ONLY affect runtime.

CmdPath String String

Takes CMD PATH, and establishes a benchmark-private setting to use PATH for CMD. For example `CmdPath ghc ghc-7.6.3`. | Threads Int -- ^ Shorthand: builtin support for changing the number of threads across a number of separate build methods. | TimeOut Double -- ^ Set the timeout for this benchmark.

enumerateBenchSpace :: BenchSpace a -> [[(a, ParamSetting)]]Source

Exhaustively compute all configurations described by a benchmark configuration space.

compileOptsOnly :: BenchSpace a -> BenchSpace aSource

Strip all runtime options, leaving only compile-time options. This is useful for figuring out how many separate compiles need to happen.

isCompileTime :: ParamSetting -> BoolSource

Is it a setting that affects compile time?

toCompileFlags :: [(a, ParamSetting)] -> CompileFlagsSource

Extract the parameters that affect the compile-time arguments.

toRunFlags :: [(a, ParamSetting)] -> RunFlagsSource

Extract the parameters that affect the runtime arguments.

type BuildID = StringSource

A BuildID should uniquely identify a particular (compile-time) configuration, but consist only of characters that would be reasonable to put in a filename. This is used to keep build results from colliding.

makeBuildID :: FilePath -> CompileFlags -> BuildIDSource

Performs a simple reformatting (stripping disallowed characters) to create a build ID corresponding to a set of compile flags. To make it unique we also append the target path.

HSBench Driver Configuration

data Config Source

The global configuration for benchmarking. WARNING! This is an internal data structure. You shouldn't really use it.

Constructors

Config 

Fields

benchlist :: [Benchmark DefaultParamMeaning]
 
benchsetName :: Maybe String

What identifies this set of benchmarks? Used to create fusion table.

benchversion :: (String, Double)

benchlist file name and version number (e.g. X.Y) , threadsettings :: [Int] -- ^ A list of #threads to test. 0 signifies non-threaded mode.

runTimeOut :: Maybe Double

Timeout in seconds for running benchmarks (if not specified by the benchmark specifically)

maxthreads :: Int
 
trials :: Int

number of runs of each configuration

skipTo :: Maybe Int

Where to start in the config space.

runID :: Maybe String

An over-ride for the run ID.

ciBuildID :: Maybe String

The build ID from the continuous integration system.

shortrun :: Bool
 
doClean :: Bool
 
keepgoing :: Bool

keep going after error

pathRegistry :: PathRegistry

Paths to executables.

hostname :: String
 
startTime :: Integer

Seconds since Epoch.

resultsFile :: String

Where to put timing results.

logFile :: String

Where to put more verbose testing output.

gitInfo :: (String, String, Int)

Branch, revision hash, depth.

buildMethods :: [BuildMethod]

Starts with cabalmakeghc, can be extended by user.

logOut :: OutputStream ByteString
 
resultsOut :: OutputStream ByteString
 
stdOut :: OutputStream ByteString
 
envs :: [[(String, String)]]
 
argsBeforeFlags :: Bool

A global setting to control whether executables are given their 'flags/params' after their regular arguments. This is here because some executables don't use proper command line parsing.

harvesters :: LineHarvester

A stack of line harvesters that gather RunResult details.

doFusionUpload :: Bool
 
fusionConfig :: FusionConfig
 

Instances

type BenchM a = ReaderT Config IO aSource

A monad for benchamrking. This provides access to configuration options, but really, its main purpose is enabling logging.

data FusionConfig Source

Constructors

FusionConfig 

Fields

fusionTableID :: Maybe TableId

This must be Just whenever doFusionUpload is true.

fusionClientID :: Maybe String
 
fusionClientSecret :: Maybe String
 
serverColumns :: [String]

Record the ordering of columns server side.

Instances

Subprocesses and system commands

data CommandDescr Source

A self-contained description of a runnable command. Similar to System.Process.CreateProcess but slightly simpler.

Constructors

CommandDescr 

Fields

command :: CmdSpec

Executable and arguments

envVars :: [(String, String)]

Environment variables to APPEND to current env.

timeout :: Maybe Double

Optional timeout in seconds.

workingDir :: Maybe FilePath

Optional working directory to switch to before running command.

data RunResult Source

Measured results from running a subprocess (benchmark).

Constructors

RunCompleted 

Fields

realtime :: Double

Benchmark time in seconds, may be different than total process time.

productivity :: Maybe Double

Seconds

allocRate :: Maybe Word64

Bytes allocated per mutator-second

memFootprint :: Maybe Word64

High water mark of allocated memory, in bytes.

RunTimeOut 
ExitError Int

Contains the returned error code.

data SubProcess Source

A running subprocess.

Constructors

SubProcess 

Fields

wait :: IO RunResult
 
process_out :: InputStream ByteString

A stream of lines.

process_err :: InputStream ByteString

A stream of lines.

newtype LineHarvester Source

A line harvester takes a single line of input and possible extracts data from it which it can then add to a RunResult.

The boolean result indicates whether the line was used or not.

Instances

Show LineHarvester 
Monoid LineHarvester

We can stack up line harvesters. ALL of them get to run on each line.

orHarvest :: LineHarvester -> LineHarvester -> LineHarvesterSource

Run the second harvester only if the first fails.

Benchmark outputs for upload

data BenchmarkResult Source

This contains all the contextual information for a single benchmark run, which makes up a row in a table of benchmark results. Note that multiple trials (actual executions) go into a single BenchmarkResult

emptyBenchmarkResult :: BenchmarkResultSource

A default value, useful for filling in only the fields that are relevant to a particular benchmark.

For convenience -- large records demand pretty-printing

doc :: Out a => a -> Doc

doc is the equivalent of show

This is a specialised variant of docPrec, using precedence context zero.