Skip to content

Commit 0ec450b

Browse files
AndreasPKtreeowl
authored andcommitted
Refactor SetOperations.hs
* Benchmark names are now unique. * Benchmarks are no longer run twice with identical data. * Benchmark names constructed by swapping arguments are indicated by a _swap postfix. * Refactored the code to make it easier to understand. This fixes #621.
1 parent 0e0ac14 commit 0ec450b

File tree

1 file changed

+33
-11
lines changed

1 file changed

+33
-11
lines changed

benchmarks/SetOperations/SetOperations.hs

Lines changed: 33 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,32 +1,54 @@
11
{-# LANGUAGE BangPatterns #-}
2+
{-# LANGUAGE ScopedTypeVariables #-}
23

34
module SetOperations (benchmark) where
45

56
import Gauge (bench, defaultMain, whnf)
67
import Data.List (partition)
8+
import Data.Tuple as Tuple
79

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 ()
916
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+
]
1124

1225
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.
1330
n, s, t :: Int
1431
n = 100000
1532
s {-small-} = n `div` 10
1633
t {-tiny-} = round $ sqrt $ fromIntegral n
1734

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)
2340
]
2441

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)
2950

51+
-- Data variants
3052
all_n = fromList [1..n]
3153

3254
!disj_nn = seqPair $ (all_n, fromList [n+1..n+n])

0 commit comments

Comments
 (0)