Skip to content
Snippets Groups Projects
Commit 2e73fe2d authored by bos's avatar bos
Browse files

Add benchmarks for gh-165

I used the code from the gist as the source for the Concat module.
parent 45f389b5
No related branches found
No related tags found
No related merge requests found
......@@ -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")
......
{-# 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
......@@ -47,6 +47,7 @@ executable text-benchmarks
ghc-prim,
integer-gmp,
stringsearch,
transformers,
utf8-string,
vector
......
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