[commit: packages/binary] master: Add small Generics bench to the Put benchmark suite. (fb41919)
git at git.haskell.org
git at git.haskell.org
Tue Apr 19 20:30:36 UTC 2016
Repository : ssh://git@git.haskell.org/binary
On branch : master
Link : http://git.haskell.org/packages/binary.git/commitdiff/fb41919966edc56a6c7052563f48c435a13d8413
>---------------------------------------------------------------
commit fb41919966edc56a6c7052563f48c435a13d8413
Author: Lennart Kolmodin <kolmodin at gmail.com>
Date: Mon Apr 11 22:03:58 2016 +0200
Add small Generics bench to the Put benchmark suite.
>---------------------------------------------------------------
fb41919966edc56a6c7052563f48c435a13d8413
benchmarks/Put.hs | 40 ++++++++++++++++++++++++++++++++++++++++
binary.cabal | 6 ++++++
2 files changed, 46 insertions(+)
diff --git a/benchmarks/Put.hs b/benchmarks/Put.hs
index 6f317c0..c713a0e 100644
--- a/benchmarks/Put.hs
+++ b/benchmarks/Put.hs
@@ -1,4 +1,7 @@
{-# LANGUAGE CPP, ExistentialQuantification #-}
+#ifdef GENERICS
+{-# LANGUAGE DeriveGeneric #-}
+#endif
module Main (main) where
@@ -9,6 +12,10 @@ import qualified Data.ByteString as S
import qualified Data.ByteString.Char8 as C
import qualified Data.ByteString.Lazy as L
+#ifdef GENERICS
+import GHC.Generics
+#endif
+
import Data.Binary
import Data.Binary.Put
import Data.ByteString.Builder as BB
@@ -48,10 +55,33 @@ main = do
bench "Word64s" $ whnf (run . fromWord64s) word64s,
bench "Word64s builder" $ whnf (L.length . toLazyByteString . fromWord64sBuilder) word64s,
bench "[Word64]" $ whnf (run . put) word64s
+
+#ifdef GENERICS
+ , bgroup "Generics" [
+ bench "Struct monoid put" $ whnf (run . fromStructs) structs,
+ bench "Struct put as list" $ whnf (run . put) structs,
+ bench "StructList monoid put" $ whnf (run . fromStructLists) structLists,
+ bench "StructList put as list" $ whnf (run . put) structLists
+ ]
+#endif
]
where
run = L.length . runPut
+#ifdef GENERICS
+data Struct = Struct Word8 Word16 Word32 Word64 deriving Generic
+instance Binary Struct
+
+data StructList = StructList [Struct] deriving Generic
+instance Binary StructList
+
+structs :: [Struct]
+structs = take 10000 $ [ Struct a b 0 0 | a <- [0 .. maxBound], b <- [0 .. maxBound] ]
+
+structLists :: [StructList]
+structLists = replicate 1000 (StructList (take 10 structs))
+#endif
+
-- Input data
smallIntegers :: [Integer]
@@ -135,3 +165,13 @@ fromWord64s (x:xs) = put x >> fromWord64s xs
fromWord64sBuilder :: [Word64] -> BB.Builder
fromWord64sBuilder [] = mempty
fromWord64sBuilder (x:xs) = BB.word64BE x `mappend` fromWord64sBuilder xs
+
+#ifdef GENERICS
+fromStructs :: [Struct] -> Put
+fromStructs [] = return ()
+fromStructs (x:xs) = put x >> fromStructs xs
+
+fromStructLists :: [StructList] -> Put
+fromStructLists [] = return ()
+fromStructLists (x:xs) = put x >> fromStructLists xs
+#endif
diff --git a/binary.cabal b/binary.cabal
index f9a9aef..76428bf 100644
--- a/binary.cabal
+++ b/binary.cabal
@@ -136,6 +136,12 @@ benchmark put
-- build dependencies from using binary source rather than depending on the library
build-depends: array, containers
ghc-options: -O2 -Wall
+ if impl(ghc >= 7.2.1)
+ cpp-options: -DGENERICS
+ other-modules: Data.Binary.Generic
+ if impl(ghc <= 7.6)
+ -- prior to ghc-7.4 generics lived in ghc-prim
+ build-depends: ghc-prim
benchmark generics-bench
type: exitcode-stdio-1.0
More information about the ghc-commits
mailing list