[commit: packages/bytestring] master, revert-46-patch-1, wip/nix-local-build: Benchmark the new partition implementations. (c5da0d2)
git at git.haskell.org
git at git.haskell.org
Tue May 3 22:43:24 UTC 2016
Repository : ssh://git@git.haskell.org/bytestring
On branches: master,revert-46-patch-1,wip/nix-local-build
Link : http://git.haskell.org/packages/bytestring.git/commitdiff/c5da0d2f7a817d9dc2c6b7f1dfbd0ff2e6851926
>---------------------------------------------------------------
commit c5da0d2f7a817d9dc2c6b7f1dfbd0ff2e6851926
Author: Sean <burton.seanr at gmail.com>
Date: Wed Sep 30 11:03:37 2015 +0100
Benchmark the new partition implementations.
>---------------------------------------------------------------
c5da0d2f7a817d9dc2c6b7f1dfbd0ff2e6851926
bench/BenchAll.hs | 48 ++++++++++++++++++++++++++++++++++++++++++++
bench/bench-bytestring.cabal | 1 +
2 files changed, 49 insertions(+)
diff --git a/bench/BenchAll.hs b/bench/BenchAll.hs
index 109ea9a..1f8f69c 100644
--- a/bench/BenchAll.hs
+++ b/bench/BenchAll.hs
@@ -38,6 +38,8 @@ import qualified "bytestring" Data.ByteString.Lazy as OldL
import Foreign
+import System.Random
+
------------------------------------------------------------------------------
-- Benchmark support
------------------------------------------------------------------------------
@@ -149,7 +151,30 @@ benchIntEncodingB n0 w
| n <= 0 = return op
| otherwise = PI.runB w n op >>= loop (n - 1)
+hashInt :: Int -> Int
+hashInt x = iterate step x !! 10
+ where
+ step a = e
+ where b = (a `xor` 61) `xor` (a `shiftR` 16)
+ c = b + (b `shiftL` 3)
+ d = c `xor` (c `shiftR` 4)
+ e = d * 0x27d4eb2d
+ f = e `xor` (e `shiftR` 15)
+
+hashWord8 :: Word8 -> Word8
+hashWord8 = fromIntegral . hashInt . fromIntegral
+
+w :: Int -> Word8
+w = fromIntegral
+
+partitionStrict p = nf (S.partition p) . randomStrict $ mkStdGen 98423098
+ where randomStrict = fst . S.unfoldrN 10000 (Just . random)
+partitionLazy p = nf (L.partition p) . randomLazy $ (0, mkStdGen 98423098)
+ where step (k, g)
+ | k >= 10000 = Nothing
+ | otherwise = let (x, g') = random g in Just (x, (k + 1, g'))
+ randomLazy = L.unfoldr step
-- benchmarks
-------------
@@ -302,4 +327,27 @@ main = do
, benchFE "floatHexFixed" $ fromIntegral >$< P.floatHexFixed
, benchFE "doubleHexFixed" $ fromIntegral >$< P.doubleHexFixed
]
+ , bgroup "partition"
+ [
+ bgroup "strict"
+ [
+ bench "mostlyTrueFast" $ partitionStrict (< (w 225))
+ , bench "mostlyFalseFast" $ partitionStrict (< (w 10))
+ , bench "balancedFast" $ partitionStrict (< (w 128))
+
+ , bench "mostlyTrueSlow" $ partitionStrict (\x -> hashWord8 x < w 225)
+ , bench "mostlyFalseSlow" $ partitionStrict (\x -> hashWord8 x < w 10)
+ , bench "balancedSlow" $ partitionStrict (\x -> hashWord8 x < w 128)
+ ]
+ , bgroup "lazy"
+ [
+ bench "mostlyTrueFast" $ partitionLazy (< (w 225))
+ , bench "mostlyFalseFast" $ partitionLazy (< (w 10))
+ , bench "balancedFast" $ partitionLazy (< (w 128))
+
+ , bench "mostlyTrueSlow" $ partitionLazy (\x -> hashWord8 x < w 225)
+ , bench "mostlyFalseSlow" $ partitionLazy (\x -> hashWord8 x < w 10)
+ , bench "balancedSlow" $ partitionLazy (\x -> hashWord8 x < w 128)
+ ]
+ ]
]
diff --git a/bench/bench-bytestring.cabal b/bench/bench-bytestring.cabal
index 6421301..ae87a10 100644
--- a/bench/bench-bytestring.cabal
+++ b/bench/bench-bytestring.cabal
@@ -42,6 +42,7 @@ executable bench-bytestring-builder
-- we require bytestring due to benchmarking against
-- blaze-textual, which uses blaze-builder
, bytestring >= 0.9
+ , random
-- cabal complains about ../ dirs. However, this is better than symlinks,
-- which probably don't work on windows.
More information about the ghc-commits
mailing list