Skip to content

Commit

Permalink
Add encode/foldable benchmark
Browse files Browse the repository at this point in the history
  • Loading branch information
phadej committed Jun 14, 2016
1 parent 599aa8f commit ba46095
Show file tree
Hide file tree
Showing 3 changed files with 97 additions and 2 deletions.
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
dist
.cabal-sandbox/
cabal.sandbox.config
.stack-work/

*.o
*.hi
Expand Down
80 changes: 80 additions & 0 deletions benchmarks/AesonFoldable.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,80 @@
{-# LANGUAGE OverloadedStrings #-}
import Criterion.Main
import Data.Aeson
import Data.Foldable (toList)

import qualified Data.Sequence as S
import qualified Data.Vector as V
import qualified Data.Vector.Unboxed as U

-------------------------------------------------------------------------------
-- List
-------------------------------------------------------------------------------

newtype L f = L { getL :: f Int }

instance Foldable f => ToJSON (L f) where
toJSON = error "do not use this"
toEncoding = toEncoding . toList . getL

-------------------------------------------------------------------------------
-- Foldable
-------------------------------------------------------------------------------

newtype F f = F { getF :: f Int }

instance Foldable f => ToJSON (F f) where
toJSON = error "do not use this"
toEncoding = foldable . getF

-------------------------------------------------------------------------------
-- Values
-------------------------------------------------------------------------------

valueList :: [Int]
valueList = [1..1000]

valueSeq :: S.Seq Int
valueSeq = S.fromList valueList

valueVector :: V.Vector Int
valueVector = V.fromList valueList

valueUVector :: U.Vector Int
valueUVector = U.fromList valueList

-------------------------------------------------------------------------------
-- Main
-------------------------------------------------------------------------------

benchEncode
:: ToJSON a
=> String
-> a
-> Benchmark
benchEncode name val
= bench name $ nf encode val

main :: IO ()
main = defaultMain
[ bgroup "encode"
[ bgroup "List"
[ benchEncode "-" valueList
, benchEncode "L" $ L valueList
, benchEncode "F" $ F valueList
]
, bgroup "Seq"
[ benchEncode "-" valueSeq
, benchEncode "L" $ L valueSeq
, benchEncode "F" $ F valueSeq
]
, bgroup "Vector"
[ benchEncode "-" valueVector
, benchEncode "L" $ L valueVector
, benchEncode "F" $ F valueVector
]
, bgroup "Vector.Unboxed"
[ benchEncode "-" valueUVector
]
]
]
18 changes: 16 additions & 2 deletions benchmarks/aeson-benchmarks.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -174,6 +174,20 @@ executable aeson-benchmark-map
hashable,
tagged,
text,
transformers,
transformers-compat,
unordered-containers

executable aeson-benchmark-foldable
main-is: AesonFoldable.hs
ghc-options: -Wall -O2 -rtsopts
build-depends:
aeson-benchmarks,
base,
criterion >= 1.0,
bytestring,
containers,
deepseq,
hashable,
tagged,
text,
unordered-containers,
vector

0 comments on commit ba46095

Please sign in to comment.