module Run where import Control.Monad.Error import Benchmark import Definitions import Report import Shellish hiding ( run ) import Standard import qualified TabularRST as TR benchMany :: [TestRepo] -> [TestBinary] -> [Benchmark a] -> Command [(Test a, Maybe MemTimeOutput)] benchMany repos bins benches = do fmap concat $ forM (map repoAndVariants repos) $ \rs -> do res <- sequence [ do let test = Test bench repo bin memtime <- run test return (test, memtime) | repo <- rs, bin <- bins, bench <- benches ] let tables = repoTables benchmarks res if length tables == 1 then echo_n $ TR.render id id id $ tabulateRepo formatTimeResult (head tables) else error "Not expecting more than one table for a repo and its variants" return res where repoAndVariants r = map (r `tweakVia`) (trVariants r) tweakVia tr v = case vId v of DefaultVariant -> tr _ -> tr { trPath = variantRepoName v (trPath tr) , trName = trName tr ++ " " ++ vShortName v }