[commit: packages/text] master: Add benchmarks for gh-165 (2e73fe2)
git at git.haskell.org
git at git.haskell.org
Tue Aug 8 15:23:29 UTC 2017
Repository : ssh://git@git.haskell.org/text
On branch : master
Link : http://git.haskell.org/packages/text.git/commitdiff/2e73fe2d0e92b22201cecc6b21514a164c4c974e
>---------------------------------------------------------------
commit 2e73fe2d0e92b22201cecc6b21514a164c4c974e
Author: Bryan O'Sullivan <bos at serpentine.com>
Date: Mon Aug 7 20:33:21 2017 -0700
Add benchmarks for gh-165
I used the code from the gist as the source for the Concat module.
>---------------------------------------------------------------
2e73fe2d0e92b22201cecc6b21514a164c4c974e
benchmarks/haskell/Benchmarks.hs | 2 ++
benchmarks/haskell/Benchmarks/Concat.hs | 25 +++++++++++++++++++++++++
benchmarks/text-benchmarks.cabal | 1 +
3 files changed, 28 insertions(+)
diff --git a/benchmarks/haskell/Benchmarks.hs b/benchmarks/haskell/Benchmarks.hs
index f074ab4..fdecba7 100644
--- a/benchmarks/haskell/Benchmarks.hs
+++ b/benchmarks/haskell/Benchmarks.hs
@@ -10,6 +10,7 @@ import System.FilePath ((</>))
import System.IO (IOMode (WriteMode), openFile, hSetEncoding, utf8)
import qualified Benchmarks.Builder as Builder
+import qualified Benchmarks.Concat as Concat
import qualified Benchmarks.DecodeUtf8 as DecodeUtf8
import qualified Benchmarks.EncodeUtf8 as EncodeUtf8
import qualified Benchmarks.Equality as Equality
@@ -41,6 +42,7 @@ benchmarks = do
-- Traditional benchmarks
bs <- sequence
[ Builder.benchmark
+ , Concat.benchmark
, DecodeUtf8.benchmark "html" (tf "libya-chinese.html")
, DecodeUtf8.benchmark "xml" (tf "yiwiki.xml")
, DecodeUtf8.benchmark "ascii" (tf "ascii.txt")
diff --git a/benchmarks/haskell/Benchmarks/Concat.hs b/benchmarks/haskell/Benchmarks/Concat.hs
new file mode 100644
index 0000000..f670e88
--- /dev/null
+++ b/benchmarks/haskell/Benchmarks/Concat.hs
@@ -0,0 +1,25 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+module Benchmarks.Concat (benchmark) where
+
+import Control.Monad.Trans.Writer
+import Criterion (Benchmark, bgroup, bench, whnf)
+import Data.Text as T
+
+benchmark :: IO Benchmark
+benchmark = return $ bgroup "Concat"
+ [ bench "append" $ whnf (append4 "Text 1" "Text 2" "Text 3") "Text 4"
+ , bench "concat" $ whnf (concat4 "Text 1" "Text 2" "Text 3") "Text 4"
+ , bench "write" $ whnf (write4 "Text 1" "Text 2" "Text 3") "Text 4"
+ ]
+
+append4, concat4, write4 :: Text -> Text -> Text -> Text -> Text
+
+{-# NOINLINE append4 #-}
+append4 x1 x2 x3 x4 = x1 `append` x2 `append` x3 `append` x4
+
+{-# NOINLINE concat4 #-}
+concat4 x1 x2 x3 x4 = T.concat [x1, x2, x3, x4]
+
+{-# NOINLINE write4 #-}
+write4 x1 x2 x3 x4 = execWriter $ tell x1 >> tell x2 >> tell x3 >> tell x4
diff --git a/benchmarks/text-benchmarks.cabal b/benchmarks/text-benchmarks.cabal
index 268e6db..b21b61a 100644
--- a/benchmarks/text-benchmarks.cabal
+++ b/benchmarks/text-benchmarks.cabal
@@ -47,6 +47,7 @@ executable text-benchmarks
ghc-prim,
integer-gmp,
stringsearch,
+ transformers,
utf8-string,
vector
More information about the ghc-commits
mailing list