Skip to content
Snippets Groups Projects
Commit 7fd8f185 authored by tibbe's avatar tibbe
Browse files

Add benchmarks for decodeUtf8'

Also make it possible to run the Pure benchmark with a very short input
string. This lets us test the constant overheads in functions, such as
the one added by unsafePerformIO in decodeUtf8.
parent fb39275d
No related branches found
No related tags found
No related merge requests found
......@@ -38,6 +38,7 @@ module Data.Text.Encoding.Error
, replace
) where
import Control.DeepSeq (NFData (..))
#if __GLASGOW_HASKELL__ >= 610
import Control.Exception (Exception, throw)
#else
......@@ -97,6 +98,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") "принимая"
......
......@@ -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)
......
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