Skip to content
Snippets Groups Projects
Commit 7dac6e96 authored by bos's avatar bos
Browse files

Backport integer builder benchmarks

parent 3700f709
No related branches found
No related tags found
No related merge requests found
......@@ -35,6 +35,7 @@ module Data.Text.Encoding.Error
, replace
) where
import Control.DeepSeq (NFData (..))
#if __GLASGOW_HASKELL__ >= 610
import Control.Exception (Exception, throw)
#else
......@@ -94,6 +95,10 @@ instance Show UnicodeException where
instance Exception UnicodeException
instance NFData UnicodeException where
rnf (DecodeError desc w) = rnf desc `seq` rnf w `seq` ()
rnf (EncodeError desc c) = rnf desc `seq` rnf c `seq` ()
-- | Throw a 'UnicodeException' if decoding fails.
strictDecode :: OnDecodeError
strictDecode desc c = throw (DecodeError desc c)
......
......@@ -49,7 +49,8 @@ benchmarks = do
, Equality.benchmark (tf "japanese.txt")
, FileRead.benchmark (tf "russian.txt")
, FoldLines.benchmark (tf "russian.txt")
, Pure.benchmark (tf "japanese.txt")
, Pure.benchmark "tiny "(tf "tiny.txt")
, Pure.benchmark "japanese" (tf "japanese.txt")
, ReadNumbers.benchmark (tf "numbers.txt")
, Replace.benchmark (tf "russian.txt") "принимая" "своем"
, Search.benchmark (tf "russian.txt") "принимая"
......
......@@ -20,18 +20,41 @@ import qualified Data.ByteString.Lazy as LB
import qualified Data.Text as T
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Builder as LTB
import qualified Data.Text.Lazy.Builder.Int as Int
import Data.Int (Int64)
benchmark :: IO Benchmark
benchmark = return $ bgroup "Builder"
[ bench "LazyText" $ nf
(LT.length . LTB.toLazyText . mconcat . map LTB.fromText) texts
, bench "Binary" $ nf
(LB.length . B.toLazyByteString . mconcat . map B.fromByteString)
byteStrings
, bench "Blaze" $ nf
(LB.length . Blaze.toLazyByteString . mconcat . map Blaze.fromString)
strings
[ bgroup "Comparison"
[ bench "LazyText" $ nf
(LT.length . LTB.toLazyText . mconcat . map LTB.fromText) texts
, bench "Binary" $ nf
(LB.length . B.toLazyByteString . mconcat . map B.fromByteString)
byteStrings
, bench "Blaze" $ nf
(LB.length . Blaze.toLazyByteString . mconcat . map Blaze.fromString)
strings
]
, bgroup "Int"
[ bgroup "Decimal"
[ bgroup "Positive" .
flip map numbers $ \n ->
(bench (show (length (show n))) $ nf (LTB.toLazyText . Int.decimal) n)
, bgroup "Negative" .
flip map numbers $ \m ->
let n = negate m in
(bench (show (length (show n))) $ nf (LTB.toLazyText . Int.decimal) n)
]
]
]
where
numbers :: [Int64]
numbers = [
6, 14, 500, 9688, 10654, 620735, 5608880, 37010612,
731223504, 5061580596, 24596952933, 711732309084, 2845910093839,
54601756118340, 735159434806159, 3619097625502435, 95777227510267124,
414944309510675693, 8986407456998704019
]
texts :: [T.Text]
texts = take 200000 $ cycle ["foo", "λx", "由の"]
......
......@@ -18,7 +18,7 @@ module Benchmarks.DecodeUtf8
( benchmark
) where
import Foreign.C.Types (CInt, CSize)
import Foreign.C.Types
import Data.ByteString.Internal (ByteString(..))
import Foreign.Ptr (Ptr, plusPtr)
import Foreign.ForeignPtr (withForeignPtr)
......
......@@ -4,7 +4,7 @@
--
-- * Most pure functions defined the string types
--
{-# LANGUAGE BangPatterns, GADTs, MagicHash #-}
{-# LANGUAGE BangPatterns, CPP, GADTs, MagicHash #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Benchmarks.Pure
( benchmark
......@@ -27,8 +27,8 @@ import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as TB
import qualified Data.Text.Lazy.Encoding as TL
benchmark :: FilePath -> IO Benchmark
benchmark fp = do
benchmark :: String -> FilePath -> IO Benchmark
benchmark kind fp = do
-- Evaluate stuff before actually running the benchmark, we don't want to
-- count it here.
......@@ -100,6 +100,10 @@ benchmark fp = do
, benchBSL $ nf BL.unpack bla
, benchS $ nf UTF8.toString bsa
]
, bgroup "decode'"
[ benchT $ nf T.decodeUtf8' bsa
, benchTL $ nf TL.decodeUtf8' bla
]
, bgroup "drop"
[ benchT $ nf (T.drop (ta_len `div` 3)) ta
, benchTL $ nf (TL.drop (tla_len `div` 3)) tla
......@@ -405,11 +409,11 @@ benchmark fp = do
]
]
where
benchS = bench "String"
benchT = bench "Text"
benchTL = bench "LazyText"
benchBS = bench "ByteString"
benchBSL = bench "LazyByteString"
benchS = bench ("String+" ++ kind)
benchT = bench ("Text+" ++ kind)
benchTL = bench ("LazyText+" ++ kind)
benchBS = bench ("ByteString+" ++ kind)
benchBSL = bench ("LazyByteString+" ++ kind)
c = 'й'
p0 = (== c)
......@@ -425,11 +429,13 @@ benchmark fp = do
replicat n = concat . L.replicate n
short = T.pack "short"
#if !MIN_VERSION_bytestring(0,10,0)
instance NFData BS.ByteString
instance NFData BL.ByteString where
rnf BL.Empty = ()
rnf (BL.Chunk _ ts) = rnf ts
#endif
data B where
B :: NFData a => a -> B
......
......@@ -15,13 +15,19 @@ build-type: Simple
cabal-version: >=1.2
flag llvm
description: use LLVM
default: False
executable text-benchmarks
hs-source-dirs: haskell ..
c-sources: ../cbits/cbits.c
cbits/time_iconv.c
main-is: Benchmarks.hs
ghc-options: -Wall -O2
cpp-options: -DHAVE_DEEPSEQ
if flag(llvm)
ghc-options: -fllvm
cpp-options: -DHAVE_DEEPSEQ -DINTEGER_GMP
build-depends: base == 4.*,
binary,
blaze-builder,
......@@ -33,6 +39,7 @@ executable text-benchmarks
directory,
filepath,
ghc-prim,
integer-gmp,
stringsearch,
utf8-string
......
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