[commit: packages/binary] master: Add new benchmark suite for encoding. (69915d0)

git at git.haskell.org git at git.haskell.org
Mon Apr 4 11:05:39 UTC 2016


Repository : ssh://git@git.haskell.org/binary

On branch  : master
Link       : http://git.haskell.org/packages/binary.git/commitdiff/69915d0a26ae9eaa6b34367989ee8ed356ed13bb

>---------------------------------------------------------------

commit 69915d0a26ae9eaa6b34367989ee8ed356ed13bb
Author: Lennart Kolmodin <kolmodin at gmail.com>
Date:   Sun Apr 3 22:17:05 2016 +0200

    Add new benchmark suite for encoding.


>---------------------------------------------------------------

69915d0a26ae9eaa6b34367989ee8ed356ed13bb
 benchmarks/Put.hs | 117 ++++++++++++++++++++++++++++++++++++++++++++++++++++++
 binary.cabal      |  13 ++++++
 2 files changed, 130 insertions(+)

diff --git a/benchmarks/Put.hs b/benchmarks/Put.hs
new file mode 100644
index 0000000..c3cae43
--- /dev/null
+++ b/benchmarks/Put.hs
@@ -0,0 +1,117 @@
+{-# LANGUAGE CPP, ExistentialQuantification #-}
+
+module Main (main) where
+
+import Control.DeepSeq
+import Control.Exception (evaluate)
+import Criterion.Main
+import qualified Data.ByteString as S
+import qualified Data.ByteString.Char8 as C
+import qualified Data.ByteString.Lazy as L
+
+import Data.Binary
+import Data.Binary.Put
+
+main :: IO ()
+main = do
+  evaluate $ rnf
+    [ rnf bigIntegers
+    , rnf smallIntegers
+    , rnf smallByteStrings
+    , rnf smallStrings
+    , rnf word8s
+    ]
+  defaultMain
+    [
+      bench "small Integers" $ whnf (run . fromIntegers) smallIntegers,
+      bench "big Integers" $ whnf (run . fromIntegers) bigIntegers,
+
+      bench "[small Integer]" $ whnf (run . put) smallIntegers,
+      bench "[big Integer]" $ whnf (run . put) bigIntegers,
+
+      bench "small ByteStrings" $ whnf (run . fromByteStrings) smallByteStrings,
+      bench "[small ByteString]" $ whnf (run . put) smallByteStrings,
+
+      bench "small Strings" $ whnf (run . fromStrings) smallStrings,
+      bench "[small String]" $ whnf (run . put) smallStrings,
+
+      bench "Word8s" $ whnf (run . fromWord8s) word8s,
+      bench "[Word8]" $ whnf (run . put) word8s,
+      bench "Word16s" $ whnf (run . fromWord16s) word16s,
+      bench "[Word16]" $ whnf (run . put) word16s,
+      bench "Word32s" $ whnf (run . fromWord32s) word32s,
+      bench "[Word32]" $ whnf (run . put) word32s,
+      bench "Word64s" $ whnf (run . fromWord64s) word64s,
+      bench "[Word64]" $ whnf (run . put) word64s
+    ]
+  where
+    run = L.length . runPut
+
+-- Input data
+
+smallIntegers :: [Integer]
+smallIntegers = [0..10000]
+{-# NOINLINE smallIntegers #-}
+
+bigIntegers :: [Integer]
+bigIntegers = [max .. max + 10000]
+  where
+    max :: Integer
+    max = fromIntegral (maxBound :: Word64)
+{-# NOINLINE bigIntegers #-}
+
+smallByteStrings :: [S.ByteString]
+smallByteStrings = replicate 10000 $ C.pack "abcdefghi"
+{-# NOINLINE smallByteStrings #-}
+
+smallStrings :: [String]
+smallStrings = replicate 10000 "abcdefghi"
+{-# NOINLINE smallStrings #-}
+
+word8s :: [Word8]
+word8s = take 10000 $ cycle [minBound .. maxBound]
+{-# NOINLINE word8s #-}
+
+word16s :: [Word16]
+word16s = take 10000 $ cycle [minBound .. maxBound]
+{-# NOINLINE word16s #-}
+
+word32s :: [Word32]
+word32s = take 10000 $ cycle [minBound .. maxBound]
+{-# NOINLINE word32s #-}
+
+word64s :: [Word64]
+word64s = take 10000 $ cycle [minBound .. maxBound]
+{-# NOINLINE word64s #-}
+
+------------------------------------------------------------------------
+-- Benchmarks
+
+fromIntegers :: [Integer] -> Put
+fromIntegers [] = return ()
+fromIntegers (x:xs) = put x >> fromIntegers xs
+
+fromByteStrings :: [S.ByteString] -> Put
+fromByteStrings [] = return ()
+fromByteStrings (x:xs) = put x >> fromByteStrings xs
+
+fromStrings :: [String] -> Put
+fromStrings [] = return ()
+fromStrings (x:xs) = put x >> fromStrings xs
+
+fromWord8s :: [Word8] -> Put
+fromWord8s [] = return ()
+fromWord8s (x:xs) = put x >> fromWord8s xs
+
+fromWord16s :: [Word16] -> Put
+fromWord16s [] = return ()
+fromWord16s (x:xs) = put x >> fromWord16s xs
+
+fromWord32s :: [Word32] -> Put
+fromWord32s [] = return ()
+fromWord32s (x:xs) = put x >> fromWord32s xs
+
+fromWord64s :: [Word64] -> Put
+fromWord64s [] = return ()
+fromWord64s (x:xs) = put x >> fromWord64s xs
+
diff --git a/binary.cabal b/binary.cabal
index 8d94aa7..f9a9aef 100644
--- a/binary.cabal
+++ b/binary.cabal
@@ -124,6 +124,19 @@ benchmark get
   build-depends: array, containers
   ghc-options: -O2 -Wall
 
+benchmark put
+  type: exitcode-stdio-1.0
+  hs-source-dirs: src benchmarks
+  main-is: Put.hs
+  build-depends:
+    base >= 3.0 && < 5,
+    bytestring,
+    criterion == 1.*,
+    deepseq
+  -- build dependencies from using binary source rather than depending on the library
+  build-depends: array, containers
+  ghc-options: -O2 -Wall
+
 benchmark generics-bench
   type: exitcode-stdio-1.0
   hs-source-dirs: src benchmarks



More information about the ghc-commits mailing list