|
1 | 1 | {-# LANGUAGE BangPatterns #-}
|
| 2 | +{-# LANGUAGE ScopedTypeVariables #-} |
2 | 3 |
|
3 | 4 | module SetOperations (benchmark) where
|
4 | 5 |
|
5 | 6 | import Gauge (bench, defaultMain, whnf)
|
6 | 7 | import Data.List (partition)
|
| 8 | +import Data.Tuple as Tuple |
7 | 9 |
|
8 |
| -benchmark :: ([Int] -> container) -> Bool -> [(String, container -> container -> container)] -> IO () |
| 10 | +-- | Benchmark a set operation for the given container. |
| 11 | +-- Takes the following arguments: |
| 12 | +-- * A way to construct the container |
| 13 | +-- * Flag if we should benchmark the operations with reversed arguments. |
| 14 | +-- * A list of operations. |
| 15 | +benchmark :: forall container. (Show container, Eq container) => ([Int] -> container) -> Bool -> [(String, container -> container -> container)] -> IO () |
9 | 16 | benchmark fromList swap methods = do
|
10 |
| - defaultMain $ [ bench (method_str++"-"++input_str) $ whnf (method input1) input2 | (method_str, method) <- methods, (input_str, input1, input2) <- inputs ] |
| 17 | + |
| 18 | + defaultMain $ [ bench (method_str++"-"++input_str ++ "_" ++ data_sizes) $ |
| 19 | + whnf (method input1) input2 |
| 20 | + |
| 21 | + | (method_str, method) <- methods |
| 22 | + , (input_str, data_sizes, (input1, input2)) <- base_inputs ++ swapped_input |
| 23 | + ] |
11 | 24 |
|
12 | 25 | where
|
| 26 | + -- Data size descriptions, also used in the benchmark names. |
| 27 | + -- They are used to describe how large the input data is, but NOT the data itself. |
| 28 | + -- So for example nn_swap /= nn since the data size for both arguments is the same |
| 29 | + -- but the actual data is different. |
13 | 30 | n, s, t :: Int
|
14 | 31 | n = 100000
|
15 | 32 | s {-small-} = n `div` 10
|
16 | 33 | t {-tiny-} = round $ sqrt $ fromIntegral n
|
17 | 34 |
|
18 |
| - inputs = [ (mode_str, left, right) |
19 |
| - | (mode_str, (left, right)) <- [ ("disj_nn", disj_nn), ("disj_ns", disj_ns), ("disj_nt", disj_nt) |
20 |
| - , ("common_nn", common_nn), ("common_ns", common_ns), ("common_nt", common_nt) |
21 |
| - , ("mix_nn", mix_nn), ("mix_ns", mix_ns), ("mix_nt", mix_nt) |
22 |
| - , ("block_nn", block_nn), ("block_ns", block_ns) |
| 35 | + base_inputs :: [(String,String,(container,container))] |
| 36 | + base_inputs = [ ("disj", "nn", disj_nn), ("disj","ns", disj_ns), ("disj","nt", disj_nt) |
| 37 | + , ("common","nn", common_nn), ("common","ns", common_ns), ("common","nt", common_nt) |
| 38 | + , ("mix","nn", mix_nn), ("mix","ns", mix_ns), ("mix","nt", mix_nt) |
| 39 | + , ("block","nn", block_nn), ("block","ns", block_ns) |
23 | 40 | ]
|
24 | 41 |
|
25 |
| - , (mode_str, left, right) <- replicate 2 (mode_str, left, right) ++ |
26 |
| - replicate (if swap && take 4 mode_str /= "diff" && last mode_str /= last (init mode_str) then 2 else 0) |
27 |
| - (init (init mode_str) ++ [last mode_str] ++ [last (init mode_str)], right, left) |
28 |
| - ] |
| 42 | + -- Input with set arguments swapped. |
| 43 | + swapped_input |
| 44 | + | swap = map swap_input base_inputs |
| 45 | + | otherwise = [] |
| 46 | + |
| 47 | + -- Reverse arguments |
| 48 | + swap_input (name, data_sizes, input_data) = |
| 49 | + (name, reverse data_sizes ++ "_swap", Tuple.swap input_data) |
29 | 50 |
|
| 51 | + -- Data variants |
30 | 52 | all_n = fromList [1..n]
|
31 | 53 |
|
32 | 54 | !disj_nn = seqPair $ (all_n, fromList [n+1..n+n])
|
|
0 commit comments