Skip to content
Snippets Groups Projects
Commit fb419199 authored by Lennart Kolmodin's avatar Lennart Kolmodin
Browse files

Add small Generics bench to the Put benchmark suite.

parent b768640e
No related branches found
No related tags found
No related merge requests found
{-# 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
......@@ -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
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment