Separate interleaved benchmarks in another module

This commit is contained in:
Harendra Kumar 2022-10-16 20:43:48 +05:30 committed by Harendra Kumar
parent f7415e9b44
commit 162fc171df
7 changed files with 47 additions and 55 deletions

View File

@ -6,7 +6,7 @@
-- License : BSD3
-- Maintainer : streamly@composewell.com
import Stream.AsyncCommon (allBenchmarks, interleaveBenchmarks)
import Stream.AsyncCommon (allBenchmarks)
import Streamly.Benchmark.Common (runWithCLIOpts, defaultStreamSize)
moduleName :: String
@ -17,9 +17,4 @@ moduleName = "Data.Stream.Concurrent"
-------------------------------------------------------------------------------
main :: IO ()
main =
runWithCLIOpts defaultStreamSize
(\value ->
allBenchmarks moduleName id value
<> interleaveBenchmarks moduleName id value
)
main = runWithCLIOpts defaultStreamSize (allBenchmarks moduleName id)

View File

@ -8,7 +8,6 @@
module Stream.AsyncCommon
( allBenchmarks
, interleaveBenchmarks
)
where
@ -80,19 +79,11 @@ concatAsync2 f count n =
$ Stream.fromList
[sourceUnfoldrM count n, sourceUnfoldrM count (n + 1)]
{-# INLINE interleave2 #-}
interleave2 :: (Config -> Config) -> Int -> Int -> IO ()
interleave2 f count n =
Stream.fold Fold.drain
$ Async.combineWith (f . Async.interleaved)
(sourceUnfoldrM count n) (sourceUnfoldrM count (n + 1))
o_1_space_joining :: Int -> (Config -> Config) -> [Benchmark]
o_1_space_joining value f =
[ bgroup "joining"
[ benchIOSrc1 "async (2 of n/2)" (async2 f (value `div` 2))
, benchIOSrc1 "concat async (2 of n/2)" (concatAsync2 f (value `div` 2))
, benchIOSrc1 "interleave (2 of n/2)" (interleave2 f (value `div` 2))
]
]
@ -156,18 +147,6 @@ concatFmapStreamsWith f outer inner n =
$ Async.concatWith f
$ fmap (sourceUnfoldrM inner) (sourceUnfoldrM outer n)
{-# INLINE concatMapInterleaveStreamsWith #-}
concatMapInterleaveStreamsWith
:: (Config -> Config)
-> Int
-> Int
-> Int
-> IO ()
concatMapInterleaveStreamsWith f outer inner n =
Stream.fold Fold.drain
$ Async.concatMapWith (f . Async.interleaved)
(sourceUnfoldrM inner) (sourceUnfoldrM outer n)
o_1_space_concatMap :: Int -> (Config -> Config) -> [Benchmark]
o_1_space_concatMap value f =
value2 `seq`
@ -187,24 +166,6 @@ o_1_space_concatMap value f =
value2 = round $ sqrt (fromIntegral value :: Double)
-- XXX These do not work with the eager option
o_1_space_concatMapInterleave :: Int -> (Config -> Config) -> [Benchmark]
o_1_space_concatMapInterleave value f =
value2 `seq`
[ bgroup "concat"
[ benchIO "concatMapInterleaveWith (n of 1)"
(concatMapInterleaveStreamsWith f value 1)
, benchIO "concatMapInterleaveWith (sqrt x of sqrt x)"
(concatMapInterleaveStreamsWith f value2 value2)
, benchIO "concatMapInterleaveWith (1 of n)"
(concatMapInterleaveStreamsWith f 1 value)
]
]
where
value2 = round $ sqrt (fromIntegral value :: Double)
-------------------------------------------------------------------------------
-- Monadic outer product
-------------------------------------------------------------------------------
@ -244,10 +205,3 @@ allBenchmarks moduleName modifier value =
, bgroup (o_n_heap_prefix moduleName)
(o_n_heap_buffering value modifier)
]
interleaveBenchmarks :: String -> (Config -> Config) -> Int -> [Benchmark]
interleaveBenchmarks moduleName modifier value =
[ bgroup
(o_1_space_prefix moduleName)
(o_1_space_concatMapInterleave value modifier)
]

View File

@ -19,5 +19,4 @@ moduleName = "Data.Stream.ConcurrentEager"
-------------------------------------------------------------------------------
main :: IO ()
main =
runWithCLIOpts defaultStreamSize (allBenchmarks moduleName Async.eager)
main = runWithCLIOpts defaultStreamSize (allBenchmarks moduleName Async.eager)

View File

@ -0,0 +1,24 @@
{-# LANGUAGE FlexibleContexts #-}
-- |
-- Module : Main
-- Copyright : (c) 2022 Composewell Technologies
--
-- License : BSD3
-- Maintainer : streamly@composewell.com
import Stream.AsyncCommon (allBenchmarks)
import Streamly.Benchmark.Common (runWithCLIOpts, defaultStreamSize)
import qualified Streamly.Internal.Data.Stream.Concurrent as Async
moduleName :: String
moduleName = "Data.Stream.ConcurrentInterleaved"
-------------------------------------------------------------------------------
-- Main
-------------------------------------------------------------------------------
main :: IO ()
main =
runWithCLIOpts
defaultStreamSize (allBenchmarks moduleName Async.interleaved)

View File

@ -51,6 +51,7 @@ rtsOpts exeName benchName0 = unwords [general, exeSpecific, benchSpecific]
"-K8M -M64M"
| "Data.Stream/o-n-space.grouping." `isPrefixOf` benchName = ""
| "Data.Stream/o-n-space." `isPrefixOf` benchName = "-K4M"
| "Data.Stream.ConcurrentInterleaved/o-1-space.monad-outer-product.toNullAp" `isPrefixOf` benchName = "-M32M"
| "Data.Stream.ConcurrentEager/o-1-space.monad-outer-product.toNullAp" `isPrefixOf` benchName = "-M1024M -K4M"
| "Data.Stream.ConcurrentEager/o-1-space." `isPrefixOf` benchName = "-M512M -K4M"
| "Prelude.WSerial/o-n-space." `isPrefixOf` benchName = "-K4M"

View File

@ -257,6 +257,19 @@ benchmark Data.Stream.Async
else
buildable: True
benchmark Data.Stream.ConcurrentInterleaved
import: bench-options-threaded
type: exitcode-stdio-1.0
hs-source-dirs: Streamly/Benchmark/Data/Stream/, Streamly/Benchmark/Data/
main-is: ConcurrentInterleaved.hs
other-modules:
Stream.AsyncCommon
Stream.Common
if flag(use-streamly-core) || impl(ghcjs)
buildable: False
else
buildable: True
benchmark Data.Stream.ConcurrentEager
import: bench-options-threaded
type: exitcode-stdio-1.0

View File

@ -46,6 +46,12 @@ targets =
, "concurrent_cmp"
]
)
, ("Data.Stream.ConcurrentInterleaved",
[ "prelude_concurrent_grp"
, "infinite_grp"
, "concurrent_cmp"
]
)
, ("Prelude.WSerial", ["serial_wserial_cmp"])
, ("Prelude.WSerial",
[ "prelude_serial_grp"