diff --git a/containers-tests/benchmarks/Combined.hs b/containers-tests/benchmarks/Combined.hs index 031badd55292cb83496889ffc1e31de029e15c30..9b1d274d02f7222be17dcadcfc0b6a5d1fc27eb3 100644 --- a/containers-tests/benchmarks/Combined.hs +++ b/containers-tests/benchmarks/Combined.hs @@ -2,6 +2,7 @@ module Main where import Map import LookupGE.Map +import Sequence import SetOperations.Map import Set @@ -17,5 +18,5 @@ main = do , Set.benchmark , bgroup "IntMap" [] , bgroup "IntSet" [] - , bgroup "Sequence" [] + , Sequence.benchmark ] diff --git a/containers-tests/benchmarks/Sequence.hs b/containers-tests/benchmarks/Sequence.hs index 261e8dc08f5df170db33bc5417c3d01bc00d836e..b12cd477320eace6790e724c4e8d07c6933e278e 100644 --- a/containers-tests/benchmarks/Sequence.hs +++ b/containers-tests/benchmarks/Sequence.hs @@ -1,180 +1,176 @@ -module Main where +module Sequence (benchmark) where import Control.Applicative import Control.DeepSeq (rnf) import Control.Exception (evaluate) import Control.Monad.Trans.State.Strict -import Gauge (bench, bgroup, defaultMain, nf) +import Gauge (bench, bgroup, defaultMain, env, nf) +import Gauge.Benchmark (Benchmark) import Data.Foldable (foldl', foldr') import qualified Data.Sequence as S import qualified Data.Foldable import Data.Traversable (traverse, sequenceA) import System.Random (mkStdGen, randoms) -main = do - let s10 = S.fromList [1..10] :: S.Seq Int - s100 = S.fromList [1..100] :: S.Seq Int - s1000 = S.fromList [1..1000] :: S.Seq Int - s10000 = S.fromList [1..10000] :: S.Seq Int - evaluate $ rnf [s10, s100, s1000, s10000] +benchmark :: Benchmark +benchmark = let g = mkStdGen 1 - let rlist n = map (`mod` (n+1)) (take 10000 (randoms g)) :: [Int] - r10 = rlist 10 - r100 = rlist 100 - r1000 = rlist 1000 - r10000 = rlist 10000 - evaluate $ rnf [r10, r100, r1000, r10000] - let rs10 = S.fromList r10 - rs100 = S.fromList r100 - rs1000 = S.fromList r1000 - rs10000 = S.fromList r10000 - evaluate $ rnf [rs10, rs100, rs1000, rs10000] - let u10 = S.replicate 10 () :: S.Seq () - u100 = S.replicate 100 () :: S.Seq () - u1000 = S.replicate 1000 () :: S.Seq () - u10000 = S.replicate 10000 () :: S.Seq () - evaluate $ rnf [u10, u100, u1000, u10000] - defaultMain - [ bgroup "splitAt/append" - [ bench "10" $ nf (shuffle r10) s10 - , bench "100" $ nf (shuffle r100) s100 - , bench "1000" $ nf (shuffle r1000) s1000 - ] - , bgroup "fromList" - [ bench "10" $ nf S.fromList [(0 :: Int)..9] - , bench "100" $ nf S.fromList [(0 :: Int)..99] - , bench "1000" $ nf S.fromList [(0 :: Int)..999] - , bench "10000" $ nf S.fromList [(0 :: Int)..9999] - , bench "100000" $ nf S.fromList [(0 :: Int)..99999] - ] - , bgroup "partition" - [ bench "10" $ nf (S.partition even) s10 - , bench "100" $ nf (S.partition even) s100 - , bench "1000" $ nf (S.partition even) s1000 - , bench "10000" $ nf (S.partition even) s10000 - ] - , bgroup "foldl'" - [ bench "10" $ nf (foldl' (+) 0) s10 - , bench "100" $ nf (foldl' (+) 0) s100 - , bench "1000" $ nf (foldl' (+) 0) s1000 - , bench "10000" $ nf (foldl' (+) 0) s10000 - ] - , bgroup "foldr'" - [ bench "10" $ nf (foldr' (+) 0) s10 - , bench "100" $ nf (foldr' (+) 0) s100 - , bench "1000" $ nf (foldr' (+) 0) s1000 - , bench "10000" $ nf (foldr' (+) 0) s10000 - ] - , bgroup "update" - [ bench "10" $ nf (updatePoints r10 10) s10 - , bench "100" $ nf (updatePoints r100 10) s100 - , bench "1000" $ nf (updatePoints r1000 10) s1000 - ] - , bgroup "adjust" - [ bench "10" $ nf (adjustPoints r10 (+10)) s10 - , bench "100" $ nf (adjustPoints r100 (+10)) s100 - , bench "1000" $ nf (adjustPoints r1000 (+10)) s1000 - ] - , bgroup "deleteAt" - [ bench "10" $ nf (deleteAtPoints r10) s10 - , bench "100" $ nf (deleteAtPoints r100) s100 - , bench "1000" $ nf (deleteAtPoints r1000) s1000 - ] - , bgroup "insertAt" - [ bench "10" $ nf (insertAtPoints r10 10) s10 - , bench "100" $ nf (insertAtPoints r100 10) s100 - , bench "1000" $ nf (insertAtPoints r1000 10) s1000 - ] - , bgroup "traverseWithIndex/State" - [ bench "10" $ nf multiplyDown s10 - , bench "100" $ nf multiplyDown s100 - , bench "1000" $ nf multiplyDown s1000 - ] - , bgroup "sequenceA.mapWithIndex/State" - [ bench "10" $ nf multiplyDownMap s10 - , bench "100" $ nf multiplyDownMap s100 - , bench "1000" $ nf multiplyDownMap s1000 - ] - , bgroup "traverse/State" - [ bench "10" $ nf multiplyUp s10 - , bench "100" $ nf multiplyUp s100 - , bench "1000" $ nf multiplyUp s1000 - ] - , bgroup "replicateA/State" - [ bench "10" $ nf stateReplicate 10 - , bench "100" $ nf stateReplicate 100 - , bench "1000" $ nf stateReplicate 1000 - ] - , bgroup "zip" - [ bench "ix10000/5000" $ nf (\(xs,ys) -> S.zip xs ys `S.index` 5000) (s10000, u10000) - , bench "nf100" $ nf (uncurry S.zip) (s100, u100) - , bench "nf10000" $ nf (uncurry S.zip) (s10000, u10000) - ] - , bgroup "fromFunction" - [ bench "ix10000/5000" $ nf (\s -> S.fromFunction s (+1) `S.index` (s `div` 2)) 10000 - , bench "nf10" $ nf (\s -> S.fromFunction s (+1)) 10 - , bench "nf100" $ nf (\s -> S.fromFunction s (+1)) 100 - , bench "nf1000" $ nf (\s -> S.fromFunction s (+1)) 1000 - , bench "nf10000" $ nf (\s -> S.fromFunction s (+1)) 10000 - ] - , bgroup "<*>" - [ bench "ix500/1000^2" $ - nf (\s -> ((+) <$> s <*> s) `S.index` (S.length s `div` 2)) (S.fromFunction 1000 (+1)) - , bench "ix500000/1000^2" $ - nf (\s -> ((+) <$> s <*> s) `S.index` (S.length s * S.length s `div` 2)) (S.fromFunction 1000 (+1)) - , bench "ixBIG" $ - nf (\s -> ((+) <$> s <*> s) `S.index` (S.length s * S.length s `div` 2)) - (S.fromFunction (floor (sqrt $ fromIntegral (maxBound::Int))-10) (+1)) - , bench "nf100/2500/rep" $ - nf (\(s,t) -> (,) <$> replicate s () <*> replicate t ()) (100,2500) - , bench "nf100/2500/ff" $ - nf (\(s,t) -> (,) <$> S.fromFunction s (+1) <*> S.fromFunction t (*2)) (100,2500) - , bench "nf500/500/rep" $ - nf (\(s,t) -> (,) <$> replicate s () <*> replicate t ()) (500,500) - , bench "nf500/500/ff" $ - nf (\(s,t) -> (,) <$> S.fromFunction s (+1) <*> S.fromFunction t (*2)) (500,500) - , bench "nf2500/100/rep" $ - nf (\(s,t) -> (,) <$> replicate s () <*> replicate t ()) (2500,100) - , bench "nf2500/100/ff" $ - nf (\(s,t) -> (,) <$> S.fromFunction s (+1) <*> S.fromFunction t (*2)) (2500,100) - ] - , bgroup "sort" - [ bgroup "already sorted" - [ bench "10" $ nf S.sort s10 - , bench "100" $ nf S.sort s100 - , bench "1000" $ nf S.sort s1000 - , bench "10000" $ nf S.sort s10000] - , bgroup "random" - [ bench "10" $ nf S.sort rs10 - , bench "100" $ nf S.sort rs100 - , bench "1000" $ nf S.sort rs1000 - , bench "10000" $ nf S.sort rs10000] - ] - , bgroup "unstableSort" - [ bgroup "already sorted" - [ bench "10" $ nf S.unstableSort s10 - , bench "100" $ nf S.unstableSort s100 - , bench "1000" $ nf S.unstableSort s1000 - , bench "10000" $ nf S.unstableSort s10000] - , bgroup "random" - [ bench "10" $ nf S.unstableSort rs10 - , bench "100" $ nf S.unstableSort rs100 - , bench "1000" $ nf S.unstableSort rs1000 - , bench "10000" $ nf S.unstableSort rs10000] - ] - , bgroup "unstableSortOn" - [ bgroup "already sorted" - [ bench "10" $ nf (S.unstableSortOn id) s10 - , bench "100" $ nf (S.unstableSortOn id) s100 - , bench "1000" $ nf (S.unstableSortOn id) s1000 - , bench "10000" $ nf (S.unstableSortOn id) s10000] - , bgroup "random" - [ bench "10" $ nf (S.unstableSortOn id) rs10 - , bench "100" $ nf (S.unstableSortOn id) rs100 - , bench "1000" $ nf (S.unstableSortOn id) rs1000 - , bench "10000" $ nf (S.unstableSortOn id) rs10000] - ] - ] + rlist n = map (`mod` (n+1)) (take 10000 (randoms g)) :: [Int] + mkInput :: (Int -> a) -> (a, a, a, a) + mkInput f = (f 10, f 100, f 1000, f 10000) + in env (pure + ( mkInput (S.fromList . enumFromTo 1) + , mkInput rlist + , mkInput (S.fromList . rlist) + , mkInput (\n -> S.replicate n ()) + ) + ) + (\ ~( (s10, s100, s1000, s10000) + , (r10, r100, r1000, r10000) + , (rs10, rs100, rs1000, rs10000) + , (u10, u100, u1000, u10000)) -> + bgroup "Sequence" + [ bgroup "splitAt/append" + [ bench "10" $ nf (shuffle r10) s10 + , bench "100" $ nf (shuffle r100) s100 + , bench "1000" $ nf (shuffle r1000) s1000 + ] + , bgroup "fromList" + [ bench "10" $ nf S.fromList [(0 :: Int)..9] + , bench "100" $ nf S.fromList [(0 :: Int)..99] + , bench "1000" $ nf S.fromList [(0 :: Int)..999] + , bench "10000" $ nf S.fromList [(0 :: Int)..9999] + , bench "100000" $ nf S.fromList [(0 :: Int)..99999] + ] + , bgroup "partition" + [ bench "10" $ nf (S.partition even) s10 + , bench "100" $ nf (S.partition even) s100 + , bench "1000" $ nf (S.partition even) s1000 + , bench "10000" $ nf (S.partition even) s10000 + ] + , bgroup "foldl'" + [ bench "10" $ nf (foldl' (+) 0) s10 + , bench "100" $ nf (foldl' (+) 0) s100 + , bench "1000" $ nf (foldl' (+) 0) s1000 + , bench "10000" $ nf (foldl' (+) 0) s10000 + ] + , bgroup "foldr'" + [ bench "10" $ nf (foldr' (+) 0) s10 + , bench "100" $ nf (foldr' (+) 0) s100 + , bench "1000" $ nf (foldr' (+) 0) s1000 + , bench "10000" $ nf (foldr' (+) 0) s10000 + ] + , bgroup "update" + [ bench "10" $ nf (updatePoints r10 10) s10 + , bench "100" $ nf (updatePoints r100 10) s100 + , bench "1000" $ nf (updatePoints r1000 10) s1000 + ] + , bgroup "adjust" + [ bench "10" $ nf (adjustPoints r10 (+10)) s10 + , bench "100" $ nf (adjustPoints r100 (+10)) s100 + , bench "1000" $ nf (adjustPoints r1000 (+10)) s1000 + ] + , bgroup "deleteAt" + [ bench "10" $ nf (deleteAtPoints r10) s10 + , bench "100" $ nf (deleteAtPoints r100) s100 + , bench "1000" $ nf (deleteAtPoints r1000) s1000 + ] + , bgroup "insertAt" + [ bench "10" $ nf (insertAtPoints r10 10) s10 + , bench "100" $ nf (insertAtPoints r100 10) s100 + , bench "1000" $ nf (insertAtPoints r1000 10) s1000 + ] + , bgroup "traverseWithIndex/State" + [ bench "10" $ nf multiplyDown s10 + , bench "100" $ nf multiplyDown s100 + , bench "1000" $ nf multiplyDown s1000 + ] + , bgroup "sequenceA.mapWithIndex/State" + [ bench "10" $ nf multiplyDownMap s10 + , bench "100" $ nf multiplyDownMap s100 + , bench "1000" $ nf multiplyDownMap s1000 + ] + , bgroup "traverse/State" + [ bench "10" $ nf multiplyUp s10 + , bench "100" $ nf multiplyUp s100 + , bench "1000" $ nf multiplyUp s1000 + ] + , bgroup "replicateA/State" + [ bench "10" $ nf stateReplicate 10 + , bench "100" $ nf stateReplicate 100 + , bench "1000" $ nf stateReplicate 1000 + ] + , bgroup "zip" + [ bench "ix10000/5000" $ nf (\(xs,ys) -> S.zip xs ys `S.index` 5000) (s10000, u10000) + , bench "nf100" $ nf (uncurry S.zip) (s100, u100) + , bench "nf10000" $ nf (uncurry S.zip) (s10000, u10000) + ] + , bgroup "fromFunction" + [ bench "ix10000/5000" $ nf (\s -> S.fromFunction s (+1) `S.index` (s `div` 2)) 10000 + , bench "nf10" $ nf (\s -> S.fromFunction s (+1)) 10 + , bench "nf100" $ nf (\s -> S.fromFunction s (+1)) 100 + , bench "nf1000" $ nf (\s -> S.fromFunction s (+1)) 1000 + , bench "nf10000" $ nf (\s -> S.fromFunction s (+1)) 10000 + ] + , bgroup "<*>" + [ bench "ix500/1000^2" $ + nf (\s -> ((+) <$> s <*> s) `S.index` (S.length s `div` 2)) (S.fromFunction 1000 (+1)) + , bench "ix500000/1000^2" $ + nf (\s -> ((+) <$> s <*> s) `S.index` (S.length s * S.length s `div` 2)) (S.fromFunction 1000 (+1)) + , bench "ixBIG" $ + nf (\s -> ((+) <$> s <*> s) `S.index` (S.length s * S.length s `div` 2)) + (S.fromFunction (floor (sqrt $ fromIntegral (maxBound::Int))-10) (+1)) + , bench "nf100/2500/rep" $ + nf (\(s,t) -> (,) <$> replicate s () <*> replicate t ()) (100,2500) + , bench "nf100/2500/ff" $ + nf (\(s,t) -> (,) <$> S.fromFunction s (+1) <*> S.fromFunction t (*2)) (100,2500) + , bench "nf500/500/rep" $ + nf (\(s,t) -> (,) <$> replicate s () <*> replicate t ()) (500,500) + , bench "nf500/500/ff" $ + nf (\(s,t) -> (,) <$> S.fromFunction s (+1) <*> S.fromFunction t (*2)) (500,500) + , bench "nf2500/100/rep" $ + nf (\(s,t) -> (,) <$> replicate s () <*> replicate t ()) (2500,100) + , bench "nf2500/100/ff" $ + nf (\(s,t) -> (,) <$> S.fromFunction s (+1) <*> S.fromFunction t (*2)) (2500,100) + ] + , bgroup "sort" + [ bgroup "already sorted" + [ bench "10" $ nf S.sort s10 + , bench "100" $ nf S.sort s100 + , bench "1000" $ nf S.sort s1000 + , bench "10000" $ nf S.sort s10000] + , bgroup "random" + [ bench "10" $ nf S.sort rs10 + , bench "100" $ nf S.sort rs100 + , bench "1000" $ nf S.sort rs1000 + , bench "10000" $ nf S.sort rs10000] + ] + , bgroup "unstableSort" + [ bgroup "already sorted" + [ bench "10" $ nf S.unstableSort s10 + , bench "100" $ nf S.unstableSort s100 + , bench "1000" $ nf S.unstableSort s1000 + , bench "10000" $ nf S.unstableSort s10000] + , bgroup "random" + [ bench "10" $ nf S.unstableSort rs10 + , bench "100" $ nf S.unstableSort rs100 + , bench "1000" $ nf S.unstableSort rs1000 + , bench "10000" $ nf S.unstableSort rs10000] + ] + , bgroup "unstableSortOn" + [ bgroup "already sorted" + [ bench "10" $ nf (S.unstableSortOn id) s10 + , bench "100" $ nf (S.unstableSortOn id) s100 + , bench "1000" $ nf (S.unstableSortOn id) s1000 + , bench "10000" $ nf (S.unstableSortOn id) s10000] + , bgroup "random" + [ bench "10" $ nf (S.unstableSortOn id) rs10 + , bench "100" $ nf (S.unstableSortOn id) rs100 + , bench "1000" $ nf (S.unstableSortOn id) rs1000 + , bench "10000" $ nf (S.unstableSortOn id) rs10000] + ] + ] + ) {- -- This is around 4.6 times as slow as insertAt diff --git a/containers-tests/containers-tests.cabal b/containers-tests/containers-tests.cabal index 1b3b448e470f04e6bd629e75bff9c3c853a69e64..db4c78617c52b02b15e83d27230e2ad0cd29bc90 100644 --- a/containers-tests/containers-tests.cabal +++ b/containers-tests/containers-tests.cabal @@ -110,6 +110,8 @@ benchmark combined-benchmarks , containers-tests , deepseq >=1.1.0.0 && <1.5 , gauge >=0.2.3 && <0.3 + , random <1.2 + , transformers benchmark intmap-benchmarks default-language: Haskell2010