Safe Haskell | None |
---|
- type RunFlags = [String]
- type CompileFlags = [String]
- data FilePredicate
- filePredCheck :: FilePredicate -> FilePath -> IO (Maybe FilePath)
- data BuildResult
- = StandAloneBinary FilePath
- | RunInPlace (RunFlags -> EnvVars -> CommandDescr)
- 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])
- mkBenchmark :: FilePath -> [String] -> BenchSpace a -> Benchmark a
- data Benchmark a = Benchmark {}
- 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
- 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, Maybe LineHarvester)
- doFusionUpload :: Bool
- fusionConfig :: FusionConfig
- type BenchM a = ReaderT Config IO a
- data FusionConfig = FusionConfig {}
- data CommandDescr = CommandDescr {}
- data RunResult
- = RunCompleted { }
- | RunTimeOut
- | ExitError Int
- data SubProcess = SubProcess {}
- newtype LineHarvester = LineHarvester (ByteString -> Maybe Double)
- data BenchmarkResult = BenchmarkResult {
- _PROGNAME :: String
- _VARIANT :: String
- _ARGS :: [String]
- _HOSTNAME :: String
- _RUNID :: 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
- emptyBenchmarkResult :: BenchmarkResult
- doc :: Out a => a -> Doc
Benchmark building
type CompileFlags = [String]Source
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.
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 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 | |
|
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.
Benchmark configuration spaces
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
toRunFlags :: [(a, ParamSetting)] -> RunFlagsSource
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.
HSBench 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 benchamrking. This provides access to configuration options, but really, its main purpose is enabling logging.
data FusionConfig Source
FusionConfig | |
|
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. |
data SubProcess Source
A running subprocess.
SubProcess | |
|
newtype LineHarvester Source
Things like SELFTIMED that should be monitored. type Tags = [String]
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.