[commit: packages/containers] master: Add Applicative benchmarks (8b47db3)
git at git.haskell.org
git at git.haskell.org
Fri Dec 18 22:11:20 UTC 2015
Repository : ssh://git@git.haskell.org/containers
On branch : master
Link : http://git.haskell.org/packages/containers.git/commitdiff/8b47db3af79c31fe5434e95143242a2ef3e1e184
>---------------------------------------------------------------
commit 8b47db3af79c31fe5434e95143242a2ef3e1e184
Author: David Feuer <David.Feuer at gmail.com>
Date: Sat Dec 20 15:02:05 2014 -0500
Add Applicative benchmarks
>---------------------------------------------------------------
8b47db3af79c31fe5434e95143242a2ef3e1e184
benchmarks/Sequence.hs | 17 +++++++++++++++++
1 file changed, 17 insertions(+)
diff --git a/benchmarks/Sequence.hs b/benchmarks/Sequence.hs
index b6b82fa..a152c3b 100644
--- a/benchmarks/Sequence.hs
+++ b/benchmarks/Sequence.hs
@@ -1,6 +1,7 @@
-- > ghc -DTESTING --make -O2 -fforce-recomp -i.. Sequence.hs
module Main where
+import Control.Applicative
import Control.DeepSeq
import Criterion.Main
import Data.List (foldl')
@@ -44,6 +45,22 @@ main = do
, bench "nf1000" $ nf (\s -> S.fromFunction s (+1)) 1000
, bench "nf10000" $ nf (\s -> S.fromFunction s (+1)) 10000
]
+ , bgroup "<*>"
+ [ bench "ix1000/500000" $
+ nf (\s -> ((+) <$> s <*> s) `S.index` (S.length s `div` 2)) (S.fromFunction 1000 (+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)
+ ]
]
-- splitAt+append: repeatedly cut the sequence at a random point
More information about the ghc-commits
mailing list