Skip to content

Commit

Permalink
initial HaBench module
Browse files Browse the repository at this point in the history
  • Loading branch information
boegel authored and itkovian committed Nov 6, 2010
1 parent 24b1c0a commit 1e49b9a
Showing 1 changed file with 56 additions and 0 deletions.
56 changes: 56 additions & 0 deletions HaBench.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,56 @@
module HaBench where

import System.IO (FilePath)

-- data type for a benchmark
data Benchmark = Benchmark {
bName :: String,
bCabalFile :: FilePath, -- delivers version, dependencies, author, ...
bWorkloads :: [Workload]
}

-- data type for a workload (benchmark/input set pair)
type InputSet = [Input]
type ValidOutputFP = FilePath
type OutputSpec = [(FilePath, ValidOutputFP)]
data Workload = Workload {
wInput :: InputSet,
wOutput :: OutputSpec,
wTags :: [WorkloadTag]
}

data WorkloadTag = CPU | Memory | Compiler

-- data type for part of the input set for a workload
data Input = InputFile FilePath
| InputParameter Parameter

data Parameter = Parameter {
cmdLineArg :: String,
value :: ParameterValue
}

data ParameterValue = IntValue Int | StringValue String | None

-- data type for output files
data Output = Stdout | Stderr | OutputFile FilePath

-- type class for workload validators
class Validator a where
--isValid :: Monad m => a -> m Bool
isValid :: a -> Workload -> IO Bool

-- simple diff validator
data DiffValidator = DiffValidator
instance Validator DiffValidator where
isValid _ = return . and . map validateOutput . wOutput
where
validateOutput (fp, voFp) = True -- FIXME

-- precision validator
data PrecisionValidator = PrecisionValidator Double
instance Validator PrecisionValidator where
isValid (PrecisionValidator p) _ = return True -- FIXME

-- dummy main
main = putStr "HaBench"

0 comments on commit 1e49b9a

Please sign in to comment.