Skip to content

Commit ed1f052

Browse files
authored
Add benchmarks for fold functions (#1068)
Define a common set of benchmarks for fold functions, usable for all structures - Set, Map, IntSet, IntMap, Seq, Tree.
1 parent 9d90611 commit ed1f052

File tree

8 files changed

+220
-33
lines changed

8 files changed

+220
-33
lines changed

containers-tests/benchmarks/IntMap.hs

+6-4
Original file line numberDiff line numberDiff line change
@@ -3,13 +3,15 @@ module Main where
33

44
import Control.DeepSeq (rnf)
55
import Control.Exception (evaluate)
6-
import Test.Tasty.Bench (bench, defaultMain, whnf)
6+
import Test.Tasty.Bench (bench, bgroup, defaultMain, whnf)
77
import Data.List (foldl')
88
import qualified Data.IntMap as M
99
import qualified Data.IntMap.Strict as MS
1010
import Data.Maybe (fromMaybe)
1111
import Prelude hiding (lookup)
1212

13+
import Utils.Fold (foldBenchmarks, foldWithKeyBenchmarks)
14+
1315
main = do
1416
let m = M.fromAscList elems_hits :: M.IntMap Int
1517
let m' = M.fromAscList elems_mid :: M.IntMap Int
@@ -36,9 +38,6 @@ main = do
3638
, bench "insertLookupWithKey update" $ whnf (insLookupWithKey elems) m
3739
, bench "map" $ whnf (M.map (+ 1)) m
3840
, bench "mapWithKey" $ whnf (M.mapWithKey (+)) m
39-
, bench "foldlWithKey" $ whnf (ins elems) m
40-
, bench "foldlWithKey'" $ whnf (M.foldlWithKey' sum 0) m
41-
, bench "foldrWithKey" $ whnf (M.foldrWithKey consPair []) m
4241
, bench "delete" $ whnf (del keys) m
4342
, bench "update" $ whnf (upd keys) m
4443
, bench "updateLookupWithKey" $ whnf (upd' keys) m
@@ -54,6 +53,9 @@ main = do
5453
, bench "split" $ whnf (M.split key_mid) m
5554
, bench "splitLookup" $ whnf (M.splitLookup key_mid) m
5655
, bench "eq" $ whnf (\m' -> m' == m') m -- worst case, compares everything
56+
, bgroup "folds" $ foldBenchmarks M.foldr M.foldl M.foldr' M.foldl' foldMap m
57+
, bgroup "folds with key" $
58+
foldWithKeyBenchmarks M.foldrWithKey M.foldlWithKey M.foldrWithKey' M.foldlWithKey' M.foldMapWithKey m
5759
]
5860
where
5961
elems = elems_hits

containers-tests/benchmarks/IntSet.hs

+5-3
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ module Main where
55

66
import Control.DeepSeq (rnf)
77
import Control.Exception (evaluate)
8-
import Test.Tasty.Bench (bench, defaultMain, whnf)
8+
import Test.Tasty.Bench (bench, bgroup, defaultMain, whnf)
99
import Data.List (foldl')
1010
import Data.Monoid (Sum(..), All(..))
1111
import qualified Data.IntSet as IS
@@ -15,6 +15,8 @@ import qualified Data.Set as S
1515
import qualified Data.IntMap as IM
1616
import qualified Data.Map.Strict as M
1717

18+
import Utils.Fold (foldBenchmarks)
19+
1820
main = do
1921
let s = IS.fromAscList elems :: IS.IntSet
2022
s_even = IS.fromAscList elems_even :: IS.IntSet
@@ -56,8 +58,8 @@ main = do
5658
, bench "splitMember:dense" $ whnf (IS.splitMember elem_mid) s
5759
, bench "splitMember:sparse" $ whnf (IS.splitMember elem_sparse_mid) s_sparse
5860
, bench "eq" $ whnf (\s' -> s' == s') s -- worst case, compares everything
59-
, bench "foldMap:dense" $ whnf (IS.foldMap (All . (>0))) s
60-
, bench "foldMap:sparse" $ whnf (IS.foldMap (All . (>0))) s_sparse
61+
, bgroup "folds:dense" $ foldBenchmarks IS.foldr IS.foldl IS.foldr' IS.foldl' IS.foldMap s
62+
, bgroup "folds:sparse" $ foldBenchmarks IS.foldr IS.foldl IS.foldr' IS.foldl' IS.foldMap s_sparse
6163
]
6264
where
6365
bound = 2^12

containers-tests/benchmarks/Map.hs

+6-5
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ module Main where
55
import Control.Applicative (Const(Const, getConst), pure)
66
import Control.DeepSeq (rnf)
77
import Control.Exception (evaluate)
8-
import Test.Tasty.Bench (bench, defaultMain, whnf, nf)
8+
import Test.Tasty.Bench (bench, bgroup, defaultMain, whnf, nf)
99
import Data.Functor.Identity (Identity(..))
1010
import Data.List (foldl')
1111
import qualified Data.Map as M
@@ -16,6 +16,8 @@ import Data.Functor ((<$))
1616
import Data.Coerce
1717
import Prelude hiding (lookup)
1818

19+
import Utils.Fold (foldBenchmarks, foldWithKeyBenchmarks)
20+
1921
main = do
2022
let m = M.fromAscList elems :: M.Map Int Int
2123
m_even = M.fromAscList elems_even :: M.Map Int Int
@@ -70,10 +72,6 @@ main = do
7072
, bench "insertLookupWithKey' absent" $ whnf (insLookupWithKey' elems_even) m_odd
7173
, bench "insertLookupWithKey' present" $ whnf (insLookupWithKey' elems_even) m_even
7274
, bench "mapWithKey" $ whnf (M.mapWithKey (+)) m
73-
, bench "foldlWithKey" $ whnf (ins elems) m
74-
, bench "foldlWithKey'" $ whnf (M.foldlWithKey' sumkv 0) m
75-
, bench "foldrWithKey" $ whnf (M.foldrWithKey consPair []) m
76-
, bench "foldrWithKey'" $ whnf (M.foldrWithKey' consPair []) m
7775
, bench "update absent" $ whnf (upd Just evens) m_odd
7876
, bench "update present" $ whnf (upd Just evens) m_even
7977
, bench "update delete" $ whnf (upd (const Nothing) evens) m
@@ -102,6 +100,9 @@ main = do
102100
, bench "minView" $ whnf (\m' -> case M.minViewWithKey m' of {Nothing -> 0; Just ((k,v),m'') -> k+v+M.size m''}) (M.fromAscList $ zip [1..10::Int] [100..110::Int])
103101
, bench "eq" $ whnf (\m' -> m' == m') m -- worst case, compares everything
104102
, bench "compare" $ whnf (\m' -> compare m' m') m -- worst case, compares everything
103+
, bgroup "folds" $ foldBenchmarks M.foldr M.foldl M.foldr' M.foldl' foldMap m
104+
, bgroup "folds with key" $
105+
foldWithKeyBenchmarks M.foldrWithKey M.foldlWithKey M.foldrWithKey' M.foldlWithKey' M.foldMapWithKey m
105106
]
106107
where
107108
bound = 2^12

containers-tests/benchmarks/Sequence.hs

+4-12
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,8 @@ import qualified Data.Foldable
1111
import Data.Traversable (traverse, sequenceA)
1212
import System.Random (mkStdGen, randoms)
1313

14+
import Utils.Fold (foldBenchmarks)
15+
1416
main = do
1517
let s10 = S.fromList [1..10] :: S.Seq Int
1618
s100 = S.fromList [1..100] :: S.Seq Int
@@ -53,18 +55,6 @@ main = do
5355
, bench "1000" $ nf (S.partition even) s1000
5456
, bench "10000" $ nf (S.partition even) s10000
5557
]
56-
, bgroup "foldl'"
57-
[ bench "10" $ nf (foldl' (+) 0) s10
58-
, bench "100" $ nf (foldl' (+) 0) s100
59-
, bench "1000" $ nf (foldl' (+) 0) s1000
60-
, bench "10000" $ nf (foldl' (+) 0) s10000
61-
]
62-
, bgroup "foldr'"
63-
[ bench "10" $ nf (foldr' (+) 0) s10
64-
, bench "100" $ nf (foldr' (+) 0) s100
65-
, bench "1000" $ nf (foldr' (+) 0) s1000
66-
, bench "10000" $ nf (foldr' (+) 0) s10000
67-
]
6858
, bgroup "update"
6959
[ bench "10" $ nf (updatePoints r10 10) s10
7060
, bench "100" $ nf (updatePoints r100 10) s100
@@ -184,6 +174,8 @@ main = do
184174
, bench "100/10000" $ whnf (uncurry compare) (s100, s10000)
185175
, bench "10000/100" $ whnf (uncurry compare) (s10000, s100)
186176
]
177+
, bgroup "folds 10" $ foldBenchmarks foldr foldl foldr' foldl' foldMap s10
178+
, bgroup "folds 10000" $ foldBenchmarks foldr foldl foldr' foldl' foldMap s10000
187179
]
188180

189181
{-

containers-tests/benchmarks/Set.hs

+4-1
Original file line numberDiff line numberDiff line change
@@ -4,10 +4,12 @@ module Main where
44

55
import Control.DeepSeq (rnf)
66
import Control.Exception (evaluate)
7-
import Test.Tasty.Bench (bench, defaultMain, whnf)
7+
import Test.Tasty.Bench (bench, bgroup, defaultMain, whnf)
88
import Data.List (foldl')
99
import qualified Data.Set as S
1010

11+
import Utils.Fold (foldBenchmarks)
12+
1113
main = do
1214
let s = S.fromAscList elems :: S.Set Int
1315
s_even = S.fromAscList elems_even :: S.Set Int
@@ -55,6 +57,7 @@ main = do
5557
, bench "member.powerSet (15)" $ whnf (\ s -> all (flip S.member s) s) (S.powerSet (S.fromList [1..15]))
5658
, bench "eq" $ whnf (\s' -> s' == s') s -- worst case, compares everything
5759
, bench "compare" $ whnf (\s' -> compare s' s') s -- worst case, compares everything
60+
, bgroup "folds" $ foldBenchmarks S.foldr S.foldl S.foldr' S.foldl' foldMap s
5861
]
5962
where
6063
bound = 2^12

containers-tests/benchmarks/Tree.hs

+8-8
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ module Main where
44
import Control.DeepSeq (NFData, rnf)
55
import Control.Exception (evaluate)
66
import Data.Coerce (coerce)
7-
import Data.Foldable (fold, foldl', toList)
7+
import qualified Data.Foldable as F
88
import Data.Monoid (All(..))
99
#if MIN_VERSION_base(4,18,0)
1010
import Data.Monoid (Sum(..))
@@ -13,20 +13,20 @@ import qualified Data.Foldable1 as Foldable1
1313
import Test.Tasty.Bench (Benchmark, Benchmarkable, bench, bgroup, defaultMain, whnf, nf)
1414
import qualified Data.Tree as T
1515

16+
import Utils.Fold (foldBenchmarks)
17+
1618
main :: IO ()
1719
main = do
1820
evaluate $ rnf ts `seq` rnf tsBool
1921
defaultMain
2022
[ bgroup "Foldable"
21-
[ bgroup "fold" $ forTs tsBool $ whnf fold . (coerce :: T.Tree Bool -> T.Tree All)
22-
, bgroup "foldMap" $ forTs tsBool $ whnf (foldMap All)
23-
, bgroup "foldr_1" $ forTs tsBool $ whnf (foldr (&&) True)
24-
, bgroup "foldr_2" $ forTs ts $ whnf (length . foldr (:) [])
25-
, bgroup "foldr_3" $ forTs ts $ whnf (\t -> foldr (\x k acc -> if acc < 0 then acc else k $! acc + x) id t 0)
26-
, bgroup "foldl'" $ forTs ts $ whnf (foldl' (+) 0)
23+
[ bgroup "folds"
24+
[ bgroup label $ foldBenchmarks foldr foldl F.foldr' F.foldl' foldMap t
25+
| Tree label t <- ts
26+
]
2727
, bgroup "foldr1" $ forTs tsBool $ whnf (foldr1 (&&))
2828
, bgroup "foldl1" $ forTs ts $ whnf (foldl1 (+))
29-
, bgroup "toList" $ forTs ts $ nf toList
29+
, bgroup "toList" $ forTs ts $ nf F.toList
3030
, bgroup "elem" $ forTs ts $ whnf (elem 0)
3131
, bgroup "maximum" $ forTs ts $ whnf maximum
3232
, bgroup "sum" $ forTs ts $ whnf sum
+151
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,151 @@
1+
{-# LANGUAGE CPP #-}
2+
{-# LANGUAGE BangPatterns #-}
3+
{-# LANGUAGE RankNTypes #-}
4+
{-# LANGUAGE ScopedTypeVariables #-}
5+
6+
module Utils.Fold
7+
( foldBenchmarks
8+
, foldWithKeyBenchmarks
9+
) where
10+
11+
import Control.Monad.Trans.State.Strict
12+
#if !(MIN_VERSION_base(4,11,0))
13+
import Data.Semigroup (Semigroup((<>)))
14+
#endif
15+
import Data.Monoid (Any(..))
16+
import Prelude hiding (Foldable(..))
17+
import Test.Tasty.Bench (Benchmark, bench, defaultMain, whnf, nf)
18+
import qualified GHC.Exts
19+
20+
-- | Benchmarks for folds on a structure of @Int@s.
21+
22+
-- See Note [Choice of benchmarks]
23+
foldBenchmarks
24+
:: forall f.
25+
(forall b. (Int -> b -> b) -> b -> f -> b)
26+
-> (forall b. (b -> Int -> b) -> b -> f -> b)
27+
-> (forall b. (Int -> b -> b) -> b -> f -> b)
28+
-> (forall b. (b -> Int -> b) -> b -> f -> b)
29+
-> (forall m. Monoid m => (Int -> m) -> f -> m)
30+
-> f
31+
-> [Benchmark]
32+
foldBenchmarks foldr foldl foldr' foldl' foldMap xs =
33+
[-- foldr
34+
bench "foldr_elem" $ whnf foldr_elem xs
35+
, bench "foldr_cpsSum" $ whnf foldr_cpsSum xs
36+
, bench "foldr_cpsOneShotSum" $ whnf foldr_cpsOneShotSum xs
37+
, bench "foldr_traverseSum" $ whnf foldr_traverseSum xs
38+
39+
-- foldl
40+
, bench "foldl_skip" $ whnf foldl_elem xs
41+
, bench "foldl_cpsSum" $ whnf foldl_cpsSum xs
42+
, bench "foldl_cpsOneShotSum" $ whnf foldl_cpsOneShotSum xs
43+
, bench "foldl_traverseSum" $ whnf foldl_traverseSum xs
44+
45+
-- foldr'
46+
, bench "foldr'_sum" $ whnf (foldr' (+) 0) xs
47+
48+
-- foldl'
49+
, bench "foldl'_sum" $ whnf (foldl' (+) 0) xs
50+
51+
-- foldMap
52+
, bench "foldMap_elem" $ whnf foldMap_elem xs
53+
, bench "foldMap_traverseSum" $ whnf foldMap_traverseSum xs
54+
]
55+
where
56+
foldr_elem :: f -> Bool
57+
foldr_elem = foldr (\x z -> x == minBound || z) False
58+
59+
foldr_cpsSum :: f -> Int
60+
foldr_cpsSum xs = foldr (\x k !acc -> k (x + acc)) id xs 0
61+
62+
foldr_cpsOneShotSum :: f -> Int
63+
foldr_cpsOneShotSum xs =
64+
foldr (\x k -> GHC.Exts.oneShot (\ !acc -> k (x + acc))) id xs 0
65+
66+
foldr_traverseSum :: f -> Int
67+
foldr_traverseSum xs =
68+
execState (foldr (\x z -> modify' (+x) *> z) (pure ()) xs) 0
69+
70+
foldl_elem :: f -> Bool
71+
foldl_elem = foldl (\z x -> x == minBound || z) False
72+
73+
foldl_cpsSum :: f -> Int
74+
foldl_cpsSum xs = foldl (\k x !acc -> k (x + acc)) id xs 0
75+
76+
foldl_cpsOneShotSum :: f -> Int
77+
foldl_cpsOneShotSum xs =
78+
foldl (\k x -> GHC.Exts.oneShot (\ !acc -> k (x + acc))) id xs 0
79+
80+
foldl_traverseSum :: f -> Int
81+
foldl_traverseSum xs =
82+
execState (foldl (\z x -> modify' (+x) *> z) (pure ()) xs) 0
83+
84+
foldMap_elem :: f -> Any
85+
foldMap_elem = foldMap (\x -> Any (x == minBound))
86+
87+
foldMap_traverseSum :: f -> Int
88+
foldMap_traverseSum xs =
89+
execState (runEffect (foldMap (\x -> Effect (modify' (+x))) xs)) 0
90+
{-# INLINE foldBenchmarks #-}
91+
92+
-- | Benchmarks for folds on a structure of @Int@ keys and @Int@ values.
93+
foldWithKeyBenchmarks
94+
:: (forall b. (Int -> Int -> b -> b) -> b -> f -> b)
95+
-> (forall b. (b -> Int -> Int -> b) -> b -> f -> b)
96+
-> (forall b. (Int -> Int -> b -> b) -> b -> f -> b)
97+
-> (forall b. (b -> Int -> Int -> b) -> b -> f -> b)
98+
-> (forall m. Monoid m => (Int -> Int -> m) -> f -> m)
99+
-> f
100+
-> [Benchmark]
101+
foldWithKeyBenchmarks
102+
foldrWithKey foldlWithKey foldrWithKey' foldlWithKey' foldMapWithKey =
103+
foldBenchmarks
104+
(\f -> foldrWithKey (\k x z -> f (k + x) z))
105+
(\f -> foldlWithKey (\z k x -> f z (k + x)))
106+
(\f -> foldrWithKey' (\k x z -> f (k + x) z))
107+
(\f -> foldlWithKey' (\z k x -> f z (k + x)))
108+
(\f -> foldMapWithKey (\k x -> f (k + x)))
109+
{-# INLINE foldWithKeyBenchmarks #-}
110+
111+
newtype Effect f = Effect { runEffect :: f () }
112+
113+
instance Applicative f => Semigroup (Effect f) where
114+
Effect f1 <> Effect f2 = Effect (f1 *> f2)
115+
116+
instance Applicative f => Monoid (Effect f) where
117+
mempty = Effect (pure ())
118+
#if !(MIN_VERSION_base(4,11,0))
119+
mappend = (<>)
120+
#endif
121+
122+
123+
-- Note [Choice of benchmarks]
124+
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~
125+
--
126+
-- foldr_elem, foldl_elem
127+
-- Simple lazy fold that visits every element. In practice:
128+
-- * Worst case for short-circuiting folds
129+
-- * Data.Foldable.toList
130+
--
131+
-- foldr_cpsSum, foldr_cpsOneShotSum, foldl_cpsSum, foldl_cpsOneShotSum
132+
-- The well-known foldl'-via-foldr pattern. GHC.Exts.oneShot is used to help
133+
-- GHC with optimizations. In practice:
134+
-- * Used for early-return with an accumulator
135+
-- * Used by the foldl library
136+
--
137+
-- foldr_traverseSum, foldr_traverseSum
138+
-- Folding with an effect. In practice:
139+
-- * Folds defined using foldr, such as Data.Foldable.traverse_ and friends
140+
--
141+
-- foldl', foldr'
142+
-- Strict folds.
143+
--
144+
-- foldMap_elem
145+
-- Simple lazy fold that visits every element. In practice:
146+
-- * Worst case for lazy folds defined using foldMap, such as
147+
-- Data.Foldable.any, Data.Foldable.find, etc.
148+
--
149+
-- foldMap_traverseSum
150+
-- Folding with an effect. In practice:
151+
-- * With the lens library, using traverseOf_ on a foldMap based fold.

0 commit comments

Comments
 (0)