Skip to content

Commit

Permalink
Added file write benchmarks
Browse files Browse the repository at this point in the history
  • Loading branch information
BebeSparkelSparkel committed Apr 23, 2024
1 parent 19725eb commit c82fe10
Show file tree
Hide file tree
Showing 3 changed files with 49 additions and 0 deletions.
15 changes: 15 additions & 0 deletions benchmarks/haskell/Benchmarks.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NumericUnderscores #-}

module Main
( main
Expand All @@ -8,6 +9,8 @@ module Main
import Test.Tasty.Bench (defaultMain, bgroup, env)
import System.FilePath ((</>))
import System.IO
import qualified Data.Text.Lazy as LT
import Data.String (fromString)

#ifdef mingw32_HOST_OS
import System.Directory (removeFile)
Expand All @@ -19,6 +22,7 @@ import qualified Benchmarks.DecodeUtf8 as DecodeUtf8
import qualified Benchmarks.EncodeUtf8 as EncodeUtf8
import qualified Benchmarks.Equality as Equality
import qualified Benchmarks.FileRead as FileRead
import qualified Benchmarks.FileWrite as FileWrite
import qualified Benchmarks.FoldLines as FoldLines
import qualified Benchmarks.Micro as Micro
import qualified Benchmarks.Multilang as Multilang
Expand Down Expand Up @@ -59,6 +63,13 @@ main = do
let tf = ("benchmarks/text-test-data" </>)
-- Cannot use envWithCleanup, because there is no instance NFData Handle
(sinkFn, sink) <- mkSink
(noBufFP, noBufH) <- mkSink
hSetBuffering noBufH NoBuffering
(lineBufFP, lineBufH) <- mkSink
hSetBuffering lineBufH LineBuffering
(blockBufFP, blockBufH) <- mkSink
hSetBuffering blockBufH $ BlockBuffering Nothing
let writeData = LT.take 500_000 $ LT.cycle $ fromString [minBound..maxBound]
defaultMain
[ Builder.benchmark
, Concat.benchmark
Expand All @@ -77,6 +88,7 @@ main = do
]
, env (Equality.initEnv (tf "japanese.txt")) Equality.benchmark
, FileRead.benchmark (tf "russian.txt")
, FileWrite.benchmark (LT.toStrict writeData) writeData noBufH lineBufH blockBufH
, FoldLines.benchmark (tf "russian.txt")
, Multilang.benchmark
, bgroup "Pure"
Expand All @@ -102,3 +114,6 @@ main = do
]
]
rmSink sinkFn
rmSink noBufFP
rmSink lineBufFP
rmSink blockBufFP
33 changes: 33 additions & 0 deletions benchmarks/haskell/Benchmarks/FileWrite.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,33 @@
-- | Benchmarks simple file writing
--
-- Tested in this benchmark:
--
-- * Writing a file to the disk
--

{-# LANGUAGE BangPatterns #-}

module Benchmarks.FileWrite
( benchmark
) where

import Test.Tasty.Bench (Benchmark, bgroup, bench, nfIO)
import Data.Text (StrictText)
import qualified Data.Text.IO as T
import Data.Text.Lazy (LazyText)
import qualified Data.Text.Lazy.IO as LT
import System.IO (Handle)

benchmark :: StrictText -> LazyText -> Handle -> Handle -> Handle -> Benchmark
benchmark !st !lt !noBufH !lineBufH !blockBufH = bgroup "FileWrite"
[ bgroup "StrictText"
[ bench "NoBuffering" $ nfIO $ T.hPutStr noBufH st
, bench "LineBuffering" $ nfIO $ T.hPutStr lineBufH st
, bench "BlockBuffering" $ nfIO $ T.hPutStr blockBufH st
]
, bgroup "LazyText"
[ bench "NoBuffering" $ nfIO $ LT.hPutStr noBufH lt
, bench "LineBuffering" $ nfIO $ LT.hPutStr lineBufH lt
, bench "BlockBuffering" $ nfIO $ LT.hPutStr blockBufH lt
]
]
1 change: 1 addition & 0 deletions text.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -332,6 +332,7 @@ benchmark text-benchmarks
Benchmarks.EncodeUtf8
Benchmarks.Equality
Benchmarks.FileRead
Benchmarks.FileWrite
Benchmarks.FoldLines
Benchmarks.Micro
Benchmarks.Multilang
Expand Down

0 comments on commit c82fe10

Please sign in to comment.