module Main where import Criterion.Main import Data.Vector (Vector, fromList) import RunTimes main :: IO () main = defaultMain [rtPartitionBench, rtCycleBench] {- Partitions -} rtPartitionBench :: Benchmark rtPartitionBench = bgroup "partitions: Run times" $ concat [rtPartitionRL, rtPartitionWithLocRL, rtPartitionRV] rtPartitionRL :: [Benchmark] rtPartitionRL = map (\(n, xs) -> bench (msg ++ show n) $ nf uniformPartitionRL xs) $ orderList 4 where msg = "uniformPartitionRL: m = 0, n = " rtPartitionWithLocRL :: [Benchmark] rtPartitionWithLocRL = map (\(n, xs) -> bench (msg ++ show n) $ nf uniformPartitionThinRL xs) $ orderListSmall 4 where msg = "uniformPartitionThinRL: m = 0, n = " rtPartitionRV :: [Benchmark] rtPartitionRV = map (\(n, xs) -> bench (msg ++ show n) $ nf uniformPartitionRV xs) $ orderVecs 4 where msg = "uniformPartitionRV: m = 0, n = " -- rtPartitionList :: [Benchmark] -- rtPartitionList = map (\m -> bench (msg ++ show m ++ ", n = 100") $ nf (`uniformPartitionList` list100) m) $ take 4 $ orderSeq 100 -- where -- msg = "uniformPartitionList: m = " {- Cycles -} -- TODO: return it when Vector impl is done. rtCycleBench :: Benchmark rtCycleBench = bgroup "cycles: Run times" $ concat [ rtCycleRV, rtCycleThinRV1, rtCycleThinRV2 ] rtCycleRV :: [Benchmark] rtCycleRV = map ( \n -> bench (msg ++ show n) $ nf uniformCyclePartitionRV n ) $ take 4 $ orderSeq 100 where msg = "uniformCyclePartitionRV: n = " rtCycleThinRV1 :: [Benchmark] rtCycleThinRV1 = map ( \n -> bench (msg ++ show n) $ nf uniformCyclePartitionThinRVnoSelf n ) $ take 4 $ orderSeq $ max 100 minN where msg = "uniformCyclePartitionThinRVnoSelf: n = " rtCycleThinRV2 :: [Benchmark] rtCycleThinRV2 = map ( \n -> bench (msg ++ show n) $ nf uniformCyclePartitionThinRVsimpleEdgeRules n ) $ take 4 $ orderSeq $ max 100 minN where msg = "uniformCyclePartitionThinRVsimpleEdgeRules: n = " {- UTILITIES -} list100 = [1 .. 100] -- IMPORTANT: You must ensure these inputs guarantee termination of -- condition-based functions, such as uniformPartitionThinRL. orderList :: Int -> [(Int, [Int])] orderList k = take k $ map (\n -> (n, [1 .. n])) $ orderSeq 100 orderListSmall :: Int -> [(Int, [Int])] orderListSmall k = take k $ map (\n -> (n, [1 .. n])) $ orderSeq 5 orderVecs :: Int -> [(Int, Vector Int)] orderVecs = map (fmap fromList) . orderList orderVecsSmall :: Int -> [(Int, Vector Int)] orderVecsSmall = map (fmap fromList) . orderListSmall orderSeq :: Int -> [Int] orderSeq = iterate (* 2)