Safe Haskell | None |
---|
All the core types used by the rest of the HSBencher codebase.
- mkBenchmark :: FilePath -> [String] -> BenchSpace a -> Benchmark a
- data Benchmark a = Benchmark {}
- type RunFlags = [String]
- type CompileFlags = [String]
- data BuildMethod = BuildMethod {
- methodName :: String
- canBuild :: FilePredicate
- concurrentBuild :: Bool
- compile :: PathRegistry -> BuildID -> CompileFlags -> FilePath -> BenchM BuildResult
- clean :: PathRegistry -> BuildID -> FilePath -> BenchM ()
- setThreads :: Maybe (Int -> [ParamSetting])
- data BuildResult
- = StandAloneBinary FilePath
- | RunInPlace (RunFlags -> EnvVars -> CommandDescr)
- data FilePredicate
- filePredCheck :: FilePredicate -> FilePath -> IO (Maybe FilePath)
- data BenchSpace meaning
- = And [BenchSpace meaning]
- | Or [BenchSpace meaning]
- | Set meaning ParamSetting
- data ParamSetting
- enumerateBenchSpace :: BenchSpace a -> [[(a, ParamSetting)]]
- compileOptsOnly :: BenchSpace a -> BenchSpace a
- isCompileTime :: ParamSetting -> Bool
- toCompileFlags :: [(a, ParamSetting)] -> CompileFlags
- toRunFlags :: [(a, ParamSetting)] -> RunFlags
- toEnvVars :: [(a, ParamSetting)] -> [(String, String)]
- toCmdPaths :: [(a, ParamSetting)] -> [(String, String)]
- type BuildID = String
- makeBuildID :: FilePath -> CompileFlags -> BuildID
- data DefaultParamMeaning
- data Config = Config {
- benchlist :: [Benchmark DefaultParamMeaning]
- benchsetName :: Maybe String
- benchversion :: (String, Double)
- runTimeOut :: Maybe Double
- maxthreads :: Int
- trials :: Int
- skipTo :: Maybe Int
- runID :: Maybe String
- ciBuildID :: Maybe String
- shortrun :: Bool
- doClean :: Bool
- keepgoing :: Bool
- pathRegistry :: PathRegistry
- hostname :: String
- startTime :: Integer
- resultsFile :: String
- logFile :: String
- gitInfo :: (String, String, Int)
- buildMethods :: [BuildMethod]
- logOut :: OutputStream ByteString
- resultsOut :: OutputStream ByteString
- stdOut :: OutputStream ByteString
- envs :: [[(String, String)]]
- argsBeforeFlags :: Bool
- harvesters :: LineHarvester
- plugIns :: [SomePlugin]
- plugInConfs :: Map String SomePluginConf
- type BenchM a = ReaderT Config IO a
- data CommandDescr = CommandDescr {}
- data RunResult
- = RunCompleted { }
- | RunTimeOut
- | ExitError Int
- emptyRunResult :: RunResult
- data SubProcess = SubProcess {}
- newtype LineHarvester = LineHarvester (ByteString -> (RunResult -> RunResult, Bool))
- orHarvest :: LineHarvester -> LineHarvester -> LineHarvester
- data BenchmarkResult = BenchmarkResult {
- _PROGNAME :: String
- _VARIANT :: String
- _ARGS :: [String]
- _HOSTNAME :: String
- _RUNID :: String
- _CI_BUILD_ID :: String
- _THREADS :: Int
- _DATETIME :: String
- _MINTIME :: Double
- _MEDIANTIME :: Double
- _MAXTIME :: Double
- _MINTIME_PRODUCTIVITY :: Maybe Double
- _MEDIANTIME_PRODUCTIVITY :: Maybe Double
- _MAXTIME_PRODUCTIVITY :: Maybe Double
- _ALLTIMES :: String
- _TRIALS :: Int
- _COMPILER :: String
- _COMPILE_FLAGS :: String
- _RUNTIME_FLAGS :: String
- _ENV_VARS :: String
- _BENCH_VERSION :: String
- _BENCH_FILE :: String
- _UNAME :: String
- _PROCESSOR :: String
- _TOPOLOGY :: String
- _GIT_BRANCH :: String
- _GIT_HASH :: String
- _GIT_DEPTH :: Int
- _WHO :: String
- _ETC_ISSUE :: String
- _LSPCI :: String
- _FULL_LOG :: String
- _MEDIANTIME_ALLOCRATE :: Maybe Word64
- _MEDIANTIME_MEMFOOTPRINT :: Maybe Word64
- _ALLJITTIMES :: String
- emptyBenchmarkResult :: BenchmarkResult
- resultToTuple :: BenchmarkResult -> [(String, String)]
- data SomePlugin = forall p . Plugin p => SomePlugin p
- data SomePluginConf = forall p . Plugin p => SomePluginConf p (PlugConf p)
- data SomePluginFlag = forall p . Plugin p => SomePluginFlag p (PlugFlag p)
- 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)) => Plugin p where
- type PlugFlag p
- type PlugConf p
- plugName :: p -> String
- plugCmdOpts :: p -> (String, [OptDescr (PlugFlag p)])
- foldFlags :: p -> [PlugFlag p] -> PlugConf p -> PlugConf p
- defaultPlugConf :: p -> PlugConf p
- plugInitialize :: p -> Config -> IO Config
- plugUploadRow :: p -> Config -> BenchmarkResult -> IO ()
- genericCmdOpts :: Plugin p => p -> [OptDescr SomePluginFlag]
- getMyConf :: forall p. Plugin p => p -> Config -> PlugConf p
- setMyConf :: forall p. Plugin p => p -> PlugConf p -> Config -> Config
- doc :: Out a => a -> Doc
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.
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.
Benchmark | |
|
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.
BuildMethod | |
|
data BuildResult Source
The result of doing a build. Note that compile
can will throw an exception if compilation fails.
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. |
data FilePredicate Source
A description of a set of files. The description may take one of multiple forms.
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.
And [BenchSpace meaning] | |
Or [BenchSpace meaning] | |
Set meaning ParamSetting |
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.
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.
toEnvVars :: [(a, ParamSetting)] -> [(String, String)]Source
toCmdPaths :: [(a, ParamSetting)] -> [(String, 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 -> 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.
HSBencher Driver Configuration
The global configuration for benchmarking. WARNING! This is an internal data structure. You shouldn't really use it.
Config | |
|
type BenchM a = ReaderT Config IO aSource
A monad for benchmarking This provides access to configuration options, but really, its main purpose is enabling logging.
Subprocesses and system commands
data CommandDescr Source
A self-contained description of a runnable command. Similar to System.Process.CreateProcess but slightly simpler.
Measured results from running a subprocess (benchmark).
RunCompleted | |
| |
RunTimeOut | |
ExitError Int | Contains the returned error code. |
emptyRunResult :: RunResultSource
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.
SubProcess | |
|
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.
LineHarvester (ByteString -> (RunResult -> RunResult, Bool)) |
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
BenchmarkResult | |
|
emptyBenchmarkResult :: BenchmarkResultSource
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.
data SomePlugin Source
forall p . Plugin p => SomePlugin p |
data SomePluginConf Source
Keep a full plugin configuration together with the plugin it goes with.
forall p . Plugin p => SomePluginConf p (PlugConf p) |
data SomePluginFlag Source
Keep a single flag together with the plugin it goes with.
forall p . Plugin p => SomePluginFlag p (PlugFlag p) |
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)) => Plugin p whereSource
An interface for plugins provided in separate packages. These plugins provide new backends for uploading benchmark data.
A configuration flag for the plugin (parsed from the command line)
The full configuration record for the plugin.
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 pSource
Process flags and update a configuration accordingly.
defaultPlugConf :: p -> PlugConf pSource
The default configuration for this plugin.
plugInitialize :: p -> Config -> IO ConfigSource
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 pSource
Retrieve our own Plugin's configuration from the global config. This involves a dynamic type cast.
setMyConf :: forall p. Plugin p => p -> PlugConf p -> Config -> ConfigSource
Encapsulate the policy for where/how to inject the Plugin's conf into the global Config.