Skip to content
Snippets Groups Projects
Commit 62f1c97c authored by bos's avatar bos
Browse files

Allow decoding of multiple files when benchmarking

parent 30a05097
No related branches found
No related tags found
No related merge requests found
......@@ -39,7 +39,10 @@ benchmarks = do
-- Traditional benchmarks
bs <- sequence
[ Builder.benchmark
, DecodeUtf8.benchmark (tf "russian.txt")
, DecodeUtf8.benchmark "xml" (tf "yiwiki.xml")
, DecodeUtf8.benchmark "ascii" (tf "ascii.txt")
, DecodeUtf8.benchmark "russian" (tf "russian.txt")
, DecodeUtf8.benchmark "japanese" (tf "japanese.txt")
, EncodeUtf8.benchmark "επανάληψη 竺法蘭共譯"
, Equality.benchmark (tf "japanese.txt")
, FileRead.benchmark (tf "russian.txt")
......
......@@ -23,7 +23,8 @@ import Data.ByteString.Internal (ByteString(..))
import Foreign.Ptr (Ptr, plusPtr)
import Foreign.ForeignPtr (withForeignPtr)
import Data.Word (Word8)
import Criterion (Benchmark, bgroup, bench, nf)
import qualified Criterion as C
import Criterion (Benchmark, bgroup, nf)
import qualified Codec.Binary.UTF8.Generic as U8
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
......@@ -32,10 +33,11 @@ import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
benchmark :: FilePath -> IO Benchmark
benchmark fp = do
benchmark :: String -> FilePath -> IO Benchmark
benchmark kind fp = do
bs <- B.readFile fp
lbs <- BL.readFile fp
let bench name = C.bench (name ++ "+" ++ kind)
return $ bgroup "DecodeUtf8"
[ bench "Strict" $ nf T.decodeUtf8 bs
, bench "IConv" $ iconv bs
......
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