hsbencher-1.20.0.3: Launch and gather data from Haskell and non-Haskell benchmarks.

Safe HaskellNone
LanguageHaskell2010

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 a Source

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

canonicalBenchName :: [Benchmark a] -> Benchmark a -> String Source

The canonical name of a benchmark that is entered in results tables and used in messages printed to the user.

This takes the full benchmark LIST which this benchmark is part of. That may be used in the future to ensure this canonical name is unique.

prettyBenchName :: [Benchmark a] -> Benchmark a -> String Source

This may return something prettier than canonicalBenchName, but should only be used for printing informative messages to the user, not for entering data in any results table.

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

Where is the benchmark to run? This must be a single target file or directory. The convention is that this file or directory, when combined with a BuildMethod, provides a self-contained way to build one benchmark. The buildMethods field of the Config had better contain some build method that knows how to handle this 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 to identify this benchmark, INSTEAD of the basename from target.

benchTimeOut :: Maybe Double

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

overrideMethod :: Maybe BuildMethod

Force use of this specific build method.

Instances

Show a => Show (Benchmark a) 
Generic (Benchmark a) 
Out a => Out (Benchmark a) 
type Rep (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 :: Config -> BuildID -> CompileFlags -> FilePath -> BenchM BuildResult

Identify the benchmark to build by its target FilePath. Compile it.

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.

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) 
type Rep (BenchSpace meaning) 

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.

RuntimeArg String

Runtime "args" are like runtime params but are more prominent. They typically are part of the "key" of the benchmark.

CompileParam String

String contains compile-time options, expanded and tokenized by the shell. CompileEnv String String -- ^ Establish an environment variable binding during compile time.

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

CPUSet CPUAffinity

Set the cpu affinity in a particular way before launching the benchmark process.

data CPUAffinity Source

Constructors

Packed

Picks cores packed into as few NUMA domains as possible.

SpreadOut

Picks cores spread over as many NUMA domains as possible.

Default 

andAddParam :: ParamSetting -> Config -> Config Source

Modify a config by Anding in an extra param setting to *every* configs field of *every* benchmark in the global Config.

compileOptsOnly :: BenchSpace a -> BenchSpace a Source

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

isCompileTime :: ParamSetting -> Bool Source

Is it a setting that affects compile time?

toCompileFlags :: [(a, ParamSetting)] -> CompileFlags Source

Extract ALL the parameters that affect the compile-time arguments.

type BuildID = String Source

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 -> BuildID Source

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.

data DefaultParamMeaning Source

A default notion of what extra benchmark arguments actually *mean*.

Constructors

Threads Int

Set the number of threads.

Variant String

Which schedulerimplementationetc.

NoMeaning 

HSBencher Driver Configuration

data Config Source

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

This is isomorphic to `Maybe (IO ())` but it has a Show instance.

Constructors

Config 

Fields

benchlist :: [Benchmark DefaultParamMeaning]
 
extraParams :: [ParamSetting]

Extra parameter settings to fold into EVERY benchmark we run.

benchsetName :: Maybe String

What identifies this set of benchmarks? In some upload backends this is the name of the dataset or 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

In parallel compile/run phases use at most this many threads. Defaults to getNumProcessors.

trials :: Int

number of runs of each configuration

skipTo :: Maybe Int

Where to start in the config space.

runOnly :: Maybe Int

How many configurations to run before stopping.

retryFailed :: Maybe Int

How many times to retry failed benchmark configs.

runID :: Maybe String

An over-ride for the run ID.

ciBuildID :: Maybe String

The build ID from the continuous integration system.

shortrun :: Bool

An alternate mode to run very small sizes of benchmarks for testing. HSBencher relies on a convention where benchmarks WITHOUT command-line arguments must do a short run.

doClean :: Bool

Invoke the build method's clean operation before compilation.

doLSPCI :: Bool

Use the "lspci" command to gather more machine details on each run.

keepgoing :: Bool

Keep going after error.

pathRegistry :: PathRegistry

Paths to executables

hostname :: String

Manually override the machine hostname. Defaults to the output of the hostname command.

defTopology :: String

The default for the TOPOLOGY field, if a benchmark does not specify. Usually, what cores we run on is fixed for a whole run of hsbencher.

startTime :: Integer

Seconds since Epoch.

resultsFile :: String

Where to put timing results.

logFile :: String

Where to put full, verbose testing output.

gitInfo :: (String, String, Int)

Branch, revision hash, depth.

buildMethods :: [BuildMethod]

Known methods for building benchmark targets. Starts with cabalmakeghc, can be extended by user.

binDir :: FilePath

The path for build products that is managed (and cleared) by HSBencher. Usually a relative path.

systemCleaner :: CleanupAction

An optional action to run between benchmark runs to make sure the system is clean. For example, this could kill off zombie processes if any were left by previous benchmark trials.

logOut :: OutputStream ByteString

Internal use only

resultsOut :: OutputStream ByteString

Internal use only

stdOut :: OutputStream ByteString

Internal use only A set of environment variable configurations to test

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.

plugIns :: [SomePlugin]

Each plugin, and, if configured, its configuration.

plugInConfs :: Map String SomePluginConf

Maps the plugName to its config.

Instances

type BenchM a = ReaderT Config IO a Source

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

data CleanupAction Source

Constructors

NoCleanup 
Cleanup (IO ()) 

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.

tolerateError :: Bool

Does a crash of the process mean we throw away any data the program already printed? Usually False.

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.

jittime :: Maybe Double

Time to JIT compile the benchmark, counted separately from realtime.

custom :: [(Tag, SomeResult)]
 
RunTimeOut 
ExitError Int

Contains the returned error code.

emptyRunResult :: RunResult Source

A default RunResult that is a good starting point for filling in desired fields. (This way, one remains robust to additional fields that are added in the future.)

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 -> LineHarvester Source

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

Constructors

BenchmarkResult 

Fields

_PROGNAME :: String

Which benchmark are we running

_VARIANT :: String

If there are multiple ways to run the benchmark, this shoud record which was used.

_ARGS :: [String]

Command line arguments.

_HOSTNAME :: String

Which machine did we run on?

_RUNID :: String

A unique identifier for the full hsbencher that included this benchmark.

_CI_BUILD_ID :: String

When launched from Jenkins or Travis, it can help to record where we came from.

_THREADS :: Int

If multithreaded, how many CPU threads did this benchmark run with, zero otherwise.

_DATETIME :: String
 
_MINTIME :: Double

Time of the fastest run

_MEDIANTIME :: Double

Time of the median run

_MAXTIME :: Double

Time of the slowest run

_MINTIME_PRODUCTIVITY :: Maybe Double

GC productivity (if recorded) for the mintime run.

_MEDIANTIME_PRODUCTIVITY :: Maybe Double

GC productivity (if recorded) for the mediantime run.

_MAXTIME_PRODUCTIVITY :: Maybe Double

GC productivity (if recorded) for the maxtime run.

_ALLTIMES :: String

Space separated list of numbers, should be one number for each TRIAL

_TRIALS :: Int

How many times to [re]run each benchmark.

_COMPILER :: String
 
_COMPILE_FLAGS :: String

Flags used during compilation

_RUNTIME_FLAGS :: String

Flags passed at runtime, possibly in addition to ARGS

_ENV_VARS :: String

Environment variables set for this benchmark run

_BENCH_VERSION :: String

If the benchmark *suite* tracks its version number, put it here.

_BENCH_FILE :: String
 
_UNAME :: String

Information about the host machine that ran the benchmark.

_PROCESSOR :: String
 
_TOPOLOGY :: String

Some freeform indication of what cores we ran on

_GIT_BRANCH :: String

Which branch was the benchmark run from

_GIT_HASH :: String

Which exact revision of the code was run.

_GIT_DEPTH :: Int

How many git commits deep was that rev (rough proxy for age)

_WHO :: String

Was anyone else logged into the machine?

_ETC_ISSUE :: String

Information about the host machine from etcissue

_LSPCI :: String

Information about the host machine from the lspci command

_FULL_LOG :: String

Optionally record the full stdout from the benchmarking process.

_MEDIANTIME_ALLOCRATE :: Maybe Word64

If recorded, the allocation rate of the median run.

_MEDIANTIME_MEMFOOTPRINT :: Maybe Word64

If recorded, the memory footprint (high water mark) of the median run

_ALLJITTIMES :: String

Space separated list of numbers, JIT compile times (if applicable), with a 1-1 correspondence to the exec times in ALLTIMES. Time should not be double counted as JIT and exec time; these should be disjoint.

_RETRIES :: Int

The number of times any trial of the benchmark was reexecuted because of failure.

_CUSTOM :: [(Tag, SomeResult)]

A List of custom results The tag corresponds to column "title"

emptyBenchmarkResult :: BenchmarkResult Source

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

resultToTuple :: BenchmarkResult -> [(String, String)] Source

Convert the Haskell representation of a benchmark result into a tuple for upload to a typical database backend.

tupleToResult :: [(String, String)] -> BenchmarkResult Source

Perform some validation and then convert raw CSV data to a BenchmarkResult.

data SomePlugin Source

Constructors

forall p . Plugin p => SomePlugin p 

data SomePluginConf Source

Keep a full plugin configuration together with the plugin it goes with.

Constructors

forall p . Plugin p => SomePluginConf p (PlugConf p) 

Instances

data SomePluginFlag Source

Keep a single flag together with the plugin it goes with.

Constructors

forall p . Plugin p => SomePluginFlag p (PlugFlag p) 

Instances

class (Show p, Eq p, Ord p, Show (PlugFlag p), Ord (PlugFlag p), Typeable (PlugFlag p), Show (PlugConf p), Ord (PlugConf p), Typeable (PlugConf p), Default p, Default (PlugConf p)) => Plugin p where Source

An interface for plugins provided in separate packages. These plugins provide new backends for uploading benchmark data.

Associated Types

type PlugFlag p Source

A configuration flag for the plugin (parsed from the command line)

type PlugConf p Source

The full configuration record for the plugin.

Methods

plugName :: p -> String Source

Each plugin must have a unique name.

plugCmdOpts :: p -> (String, [OptDescr (PlugFlag p)]) Source

Options for command line parsing. These should probably be disjoint from the options used by other plugins; so use very specific names.

Finally, note that the String returned here is a header line that is printed before the usage documentation when the benchmark executable is invoked with `-h`.

foldFlags :: p -> [PlugFlag p] -> PlugConf p -> PlugConf p Source

Process flags and update a configuration accordingly.

plugInitialize :: p -> Config -> IO Config Source

Take any initialization actions, which may include reading or writing files and connecting to network services, as the main purpose of plugin is to provide backends for data upload.

Note that the initialization process can CHANGE the Config (it returns a new one).

plugUploadRow :: p -> Config -> BenchmarkResult -> IO () Source

This is the raison d'etre for the class. Upload a single row of benchmark data.

genericCmdOpts :: Plugin p => p -> [OptDescr SomePluginFlag] Source

Make the command line flags for a particular plugin generic so that they can be mixed together with other plugins options.

getMyConf :: forall p. Plugin p => p -> Config -> PlugConf p Source

Retrieve our own Plugin's configuration from the global config. This involves a dynamic type cast.

If there is no configuration for this plugin currently registered, the default configuration for that plugin is returned.

setMyConf :: forall p. Plugin p => p -> PlugConf p -> Config -> Config Source

Encapsulate the policy for where/how to inject the Plugin's conf into the global Config.

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.