Skip to content

Commit

Permalink
Compare decoding speed with hermes-json
Browse files Browse the repository at this point in the history
  • Loading branch information
ethercrow authored and phadej committed Feb 11, 2023
1 parent e85d9cc commit 535dc55
Show file tree
Hide file tree
Showing 5 changed files with 140 additions and 0 deletions.
6 changes: 6 additions & 0 deletions benchmarks/aeson-benchmarks.cabal
Expand Up @@ -104,6 +104,12 @@ executable aeson-benchmark-suite
other-modules: Compare.JsonBuilder
build-depends: json-builder

if impl(ghc >=8.10)
build-depends: hermes-json >=0.2.0.1
other-modules:
CompareWithHermes
Twitter.Hermes

if !flag(text2)
-- buffer-builder might work with text-2 sometime
build-depends: buffer-builder
Expand Down
69 changes: 69 additions & 0 deletions benchmarks/bench/CompareWithHermes.hs
@@ -0,0 +1,69 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}

module CompareWithHermes (benchmark) where

import Prelude.Compat
import Bench

import Data.Maybe (fromMaybe)
import qualified Data.Aeson as A
import qualified Data.Aeson.Decoding as A.D
import qualified Data.Aeson.Parser.Internal as I
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BL
import qualified Data.Hermes as H
import qualified Twitter as T
import Twitter.Manual () -- fair comparison with manual Hermes decoders
import Twitter.Hermes

import Utils

decode :: BL.ByteString -> T.Result
decode s = fromMaybe (error "fail to parse via Aeson") $ A.decode s

decode' :: BL.ByteString -> T.Result
decode' s = fromMaybe (error "fail to parse via Aeson") $ A.decode' s

decodeS :: BS.ByteString -> T.Result
decodeS s = fromMaybe (error "fail to parse via Aeson") $ A.decodeStrict' s

decodeTS :: BS.ByteString -> T.Result
decodeTS s = fromMaybe (error "fail to parse via Aeson") $ A.D.decodeStrict s

decodeIP :: BL.ByteString -> T.Result
decodeIP s = fromMaybe (error "fail to parse via Parser.decodeWith") $
I.decodeWith I.jsonEOF A.fromJSON s

decodeH :: BS.ByteString -> T.Result
decodeH s = case H.decodeEither twitterResultDecoder s of
Right result -> result
Left err -> error (show err)

benchmark :: Benchmark
benchmark =
env (readL enFile) $ \enA ->
env (readS enFile) $ \enS ->
env (readL jpFile) $ \jpA ->
env (readS jpFile) $ \jpS ->
bgroup "compare-hermes" [
bgroup "decode" [
bgroup "en" [
bench "aeson/lazy" $ nf decode enA
, bench "aeson/strict" $ nf decode' enA
, bench "aeson/stricter" $ nf decodeS enS
, bench "aeson/parser" $ nf decodeIP enA
, bench "aeson/tokens/strict" $ nf decodeTS enS
, bench "hermes" $ nf decodeH enS
]
, bgroup "jp" [
bench "aeson" $ nf decode jpA
, bench "aeson/stricter" $ nf decodeS jpS
, bench "aeson/tokens/strict" $ nf decodeTS jpS
, bench "hermes" $ nf decodeH jpS
]
]
]
where
enFile = "twitter100.json"
jpFile = "jp100.json"
50 changes: 50 additions & 0 deletions benchmarks/bench/Twitter/Hermes.hs
@@ -0,0 +1,50 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Twitter.Hermes where

import Prelude.Compat

import Data.Int (Int64)

import qualified Data.Hermes as H
import qualified Twitter as T

twitterResultDecoder :: H.Value -> H.Decoder T.Result
twitterResultDecoder = H.withObject $ \obj ->
T.Result
<$> H.atKey "results" (H.list storyDecoder) obj
<*> H.atKey "max_id" int64 obj
<*> H.atKey "since_id" int64 obj
<*> H.atKey "refresh_url" H.text obj
<*> H.atKey "next_page" H.text obj
<*> H.atKey "results_per_page" H.int obj
<*> H.atKey "page" H.int obj
<*> H.atKey "completed_in" H.double obj
<*> H.atKey "since_id_str" H.text obj
<*> H.atKey "max_id_str" H.text obj
<*> H.atKey "query" H.text obj

storyDecoder :: H.Value -> H.Decoder T.Story
storyDecoder = H.withObject $ \obj ->
T.Story
<$> H.atKey "from_user_id_str" H.text obj
<*> H.atKey "profile_image_url" H.text obj
<*> H.atKey "created_at" H.text obj
<*> H.atKey "from_user" H.text obj
<*> H.atKey "id_str" H.text obj
<*> H.atKey "metadata" metadataDecoder obj
<*> H.atKey "to_user_id" (H.nullable int64) obj
<*> H.atKey "text" H.text obj
<*> H.atKey "id" int64 obj
<*> H.atKey "from_user_id" int64 obj
<*> pure Nothing -- our bench corpus doesn't have any geolocated tweets
<*> H.atKey "iso_language_code" H.text obj
<*> H.atKey "to_user_id_str" (H.nullable H.text) obj
<*> H.atKey "source" H.text obj

int64 :: H.Value -> H.Decoder Int64
int64 = fmap fromIntegral <$> H.int

metadataDecoder :: H.Value -> H.Decoder T.Metadata
metadataDecoder = H.withObject $ \obj ->
T.Metadata <$> H.atKey "result_type" H.text obj
13 changes: 13 additions & 0 deletions benchmarks/bench/aeson-benchmark-suite.hs
Expand Up @@ -29,6 +29,12 @@ import qualified AesonMap
import qualified AutoCompare
import qualified Compare
import qualified CompareWithJSON
<<<<<<< HEAD:benchmarks/bench/aeson-benchmark-suite.hs
=======
#ifdef MIN_VERSION_hermes_json
import qualified CompareWithHermes
#endif
>>>>>>> Use hermes only with GHC > 8.8:benchmarks/bench/Suite.hs
import qualified Dates
import qualified GitHub
import qualified Issue673
Expand All @@ -42,6 +48,10 @@ import Utils
import qualified UnescapePureText1 as Text1
#endif

#if __GLASGOW_HASKELL__ >=810
import qualified CompareWithHermes
#endif

-------------------------------------------------------------------------------
-- Decode bench
-------------------------------------------------------------------------------
Expand Down Expand Up @@ -136,3 +146,6 @@ main = do
]
++ Compare.benchmarks -- compares to different libs (encoding)
++ [ CompareWithJSON.benchmark ]
#if __GLASGOW_HASKELL__ >=810
++ [ CompareWithHermes.benchmark ]
#endif
2 changes: 2 additions & 0 deletions cabal.project
Expand Up @@ -6,5 +6,7 @@ packages: benchmarks
tests: true
benchmarks: true

allow-newer: hermes-json:attoparsec-iso8601

-- packages: https://hackage.haskell.org/package/libperf-0.1/candidate/libperf-0.1.tar.gz
-- packages: https://hackage.haskell.org/package/tasty-perfbench-0.1/candidate/tasty-perfbench-0.1.tar.gz

0 comments on commit 535dc55

Please sign in to comment.