Skip to content

Commit 209a4b8

Browse files
Separate "streamly" stream benchmarks from "streamly-core"
1 parent f1b75fb commit 209a4b8

File tree

3 files changed

+111
-125
lines changed

3 files changed

+111
-125
lines changed

benchmark/Streamly/Benchmark/Data/Stream/Prelude/Exceptions.hs

Lines changed: 110 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -22,19 +22,24 @@
2222
module Main (main) where
2323

2424
import Control.Exception (Exception, throwIO)
25-
import Stream.Common (drain)
25+
import Data.HashMap.Strict (HashMap)
26+
import Data.Proxy (Proxy(..))
27+
import Stream.Common (drain, benchIOSink)
28+
import Streamly.Internal.Data.IsMap.HashMap ()
29+
import Streamly.Internal.Data.Stream (Stream)
30+
import System.IO (Handle, hClose, hPutChar)
2631

2732
import qualified Data.IORef as Ref
2833
import qualified Data.Map.Strict as Map
2934

30-
import System.IO (Handle, hClose, hPutChar)
35+
import qualified Stream.Common as Common
36+
import qualified Streamly.Internal.Data.Fold as Fold
3137
import qualified Streamly.FileSystem.Handle as FH
3238
import qualified Streamly.Internal.FileSystem.Handle as IFH
33-
import qualified Streamly.Internal.Data.Unfold as IUF
34-
import qualified Streamly.Internal.Data.Unfold.Prelude as IUF
35-
3639
import qualified Streamly.Internal.Data.Stream as Stream
3740
import qualified Streamly.Internal.Data.Stream.Prelude as Stream
41+
import qualified Streamly.Internal.Data.Unfold as IUF
42+
import qualified Streamly.Internal.Data.Unfold.Prelude as IUF
3843

3944
import Test.Tasty.Bench hiding (env)
4045
import Prelude hiding (last, length)
@@ -213,11 +218,8 @@ o_1_space_copy_exceptions_toChunks env =
213218
]
214219
]
215220

216-
moduleName :: String
217-
moduleName = "Data.Stream.Prelude.Exceptions"
218-
219-
benchmarks :: BenchEnv -> Int -> [Benchmark]
220-
benchmarks env size =
221+
excBenchmarks :: BenchEnv -> Int -> [Benchmark]
222+
excBenchmarks env size =
221223
[ bgroup (o_1_space_prefix moduleName) $ concat
222224
[ o_1_space_serial_exceptions size
223225
, o_1_space_copy_exceptions_readChunks env
@@ -226,7 +228,104 @@ benchmarks env size =
226228
]
227229
]
228230

231+
{-# INLINE pollCounts #-}
232+
pollCounts :: Stream IO Int -> IO ()
233+
pollCounts = drain . Stream.parTapCount (const True) f
234+
235+
where
236+
237+
f = Stream.drain . Stream.rollingMap2 (-) . Stream.delayPost 1
238+
239+
{-# INLINE takeInterval #-}
240+
takeInterval :: Double -> Stream IO Int -> IO ()
241+
takeInterval i = drain . Stream.takeInterval i
242+
243+
-- Inspection testing is disabled for takeInterval
244+
-- Enable it when looking at it throughly
245+
#ifdef INSPECTION
246+
-- inspect $ hasNoType 'takeInterval ''SPEC
247+
-- inspect $ hasNoTypeClasses 'takeInterval
248+
-- inspect $ 'takeInterval `hasNoType` ''D.Step
249+
#endif
250+
251+
{-# INLINE dropInterval #-}
252+
dropInterval :: Double -> Stream IO Int -> IO ()
253+
dropInterval i = drain . Stream.dropInterval i
254+
255+
-- Inspection testing is disabled for dropInterval
256+
-- Enable it when looking at it throughly
257+
#ifdef INSPECTION
258+
-- inspect $ hasNoTypeClasses 'dropInterval
259+
-- inspect $ 'dropInterval `hasNoType` ''D.Step
260+
#endif
261+
262+
-- XXX Decide on the time interval
263+
{-# INLINE _intervalsOfSum #-}
264+
_intervalsOfSum :: Stream.MonadAsync m => Double -> Stream m Int -> m ()
265+
_intervalsOfSum i = drain . Stream.intervalsOf i Fold.sum
266+
267+
timeBenchmarks :: BenchEnv -> Int -> [Benchmark]
268+
timeBenchmarks _env size =
269+
[ benchIOSink size "parTapCount 1 second" pollCounts
270+
, benchIOSink size "takeInterval-all" (takeInterval 10000)
271+
, benchIOSink size "dropInterval-all" (dropInterval 10000)
272+
]
273+
274+
-------------------------------------------------------------------------------
275+
-- Grouping/Splitting
276+
-------------------------------------------------------------------------------
277+
278+
{-# INLINE classifySessionsOf #-}
279+
classifySessionsOf :: Stream.MonadAsync m => (Int -> Int) -> Stream m Int -> m ()
280+
classifySessionsOf getKey =
281+
Common.drain
282+
. Stream.classifySessionsOf
283+
(const (return False)) 3 (Fold.take 10 Fold.sum)
284+
. Stream.timestamped
285+
. fmap (\x -> (getKey x, x))
286+
287+
{-# INLINE classifySessionsOfHash #-}
288+
classifySessionsOfHash :: Stream.MonadAsync m =>
289+
(Int -> Int) -> Stream m Int -> m ()
290+
classifySessionsOfHash getKey =
291+
Common.drain
292+
. Stream.classifySessionsByGeneric
293+
(Proxy :: Proxy (HashMap k))
294+
1 False (const (return False)) 3 (Fold.take 10 Fold.sum)
295+
. Stream.timestamped
296+
. fmap (\x -> (getKey x, x))
297+
298+
o_1_space_grouping :: BenchEnv -> Int -> [Benchmark]
299+
o_1_space_grouping _env value =
300+
-- Buffering operations using heap proportional to group/window sizes.
301+
[ bgroup "grouping"
302+
[ benchIOSink value "classifySessionsOf (10000 buckets)"
303+
(classifySessionsOf (getKey 10000))
304+
, benchIOSink value "classifySessionsOf (64 buckets)"
305+
(classifySessionsOf (getKey 64))
306+
, benchIOSink value "classifySessionsOfHash (10000 buckets)"
307+
(classifySessionsOfHash (getKey 10000))
308+
, benchIOSink value "classifySessionsOfHash (64 buckets)"
309+
(classifySessionsOfHash (getKey 64))
310+
]
311+
]
312+
313+
where
314+
315+
getKey :: Int -> Int -> Int
316+
getKey n = (`mod` n)
317+
318+
moduleName :: String
319+
moduleName = "Data.Stream.Prelude"
320+
229321
main :: IO ()
230322
main = do
231323
env <- mkHandleBenchEnv
232-
runWithCLIOpts defaultStreamSize (benchmarks env)
324+
runWithCLIOpts defaultStreamSize (allBenchmarks env)
325+
326+
where
327+
328+
allBenchmarks env size =
329+
excBenchmarks env size
330+
++ timeBenchmarks env size
331+
++ o_1_space_grouping env size

benchmark/Streamly/Benchmark/Data/Stream/Reduce.hs

Lines changed: 0 additions & 56 deletions
Original file line numberDiff line numberDiff line change
@@ -24,26 +24,14 @@ import qualified Streamly.Internal.Data.Refold.Type as Refold
2424
import qualified Streamly.Internal.Data.Fold as FL
2525
import qualified Stream.Common as Common
2626

27-
#ifndef USE_STREAMLY_CORE
28-
import Data.HashMap.Strict (HashMap)
29-
import Data.Proxy (Proxy(..))
30-
import Streamly.Internal.Data.IsMap.HashMap ()
31-
#endif
32-
3327
import Streamly.Internal.Data.Stream (Stream)
3428
import qualified Streamly.Internal.Data.Stream as S
35-
#ifndef USE_STREAMLY_CORE
36-
import qualified Streamly.Data.Stream.Prelude as S
37-
import qualified Streamly.Internal.Data.Stream.Prelude as S
38-
#endif
3929

4030
import Test.Tasty.Bench
4131
import Streamly.Benchmark.Common
4232
import Stream.Common
4333
import Prelude hiding (reverse, tail)
4434

45-
46-
4735
-- Apply transformation g count times on a stream of length len
4836
{-# INLINE iterateSource #-}
4937
iterateSource ::
@@ -146,27 +134,9 @@ o_1_space_grouping value =
146134
, benchIOSink value "refoldMany" refoldMany
147135
, benchIOSink value "foldIterateM" foldIterateM
148136
, benchIOSink value "refoldIterateM" refoldIterateM
149-
150-
#ifndef USE_STREAMLY_CORE
151-
, benchIOSink value "classifySessionsOf (10000 buckets)"
152-
(classifySessionsOf (getKey 10000))
153-
, benchIOSink value "classifySessionsOf (64 buckets)"
154-
(classifySessionsOf (getKey 64))
155-
, benchIOSink value "classifySessionsOfHash (10000 buckets)"
156-
(classifySessionsOfHash (getKey 10000))
157-
, benchIOSink value "classifySessionsOfHash (64 buckets)"
158-
(classifySessionsOfHash (getKey 64))
159-
#endif
160137
]
161138
]
162139

163-
#ifndef USE_STREAMLY_CORE
164-
where
165-
166-
getKey :: Int -> Int -> Int
167-
getKey n = (`mod` n)
168-
#endif
169-
170140
-------------------------------------------------------------------------------
171141
-- Size conserving transformations (reordering, buffering, etc.)
172142
-------------------------------------------------------------------------------
@@ -189,32 +159,6 @@ o_n_heap_buffering value =
189159
]
190160
]
191161

192-
-------------------------------------------------------------------------------
193-
-- Grouping/Splitting
194-
-------------------------------------------------------------------------------
195-
196-
#ifndef USE_STREAMLY_CORE
197-
{-# INLINE classifySessionsOf #-}
198-
classifySessionsOf :: S.MonadAsync m => (Int -> Int) -> Stream m Int -> m ()
199-
classifySessionsOf getKey =
200-
Common.drain
201-
. S.classifySessionsOf
202-
(const (return False)) 3 (FL.take 10 FL.sum)
203-
. S.timestamped
204-
. fmap (\x -> (getKey x, x))
205-
206-
{-# INLINE classifySessionsOfHash #-}
207-
classifySessionsOfHash :: S.MonadAsync m =>
208-
(Int -> Int) -> Stream m Int -> m ()
209-
classifySessionsOfHash getKey =
210-
Common.drain
211-
. S.classifySessionsByGeneric
212-
(Proxy :: Proxy (HashMap k))
213-
1 False (const (return False)) 3 (FL.take 10 FL.sum)
214-
. S.timestamped
215-
. fmap (\x -> (getKey x, x))
216-
#endif
217-
218162
-------------------------------------------------------------------------------
219163
-- Mixed Transformation
220164
-------------------------------------------------------------------------------

benchmark/Streamly/Benchmark/Data/Stream/Transform.hs

Lines changed: 1 addition & 58 deletions
Original file line numberDiff line numberDiff line change
@@ -24,28 +24,21 @@
2424
module Stream.Transform (benchmarks) where
2525

2626
import Control.Monad.IO.Class (MonadIO(..))
27-
27+
import Streamly.Internal.Data.Stream (Stream)
2828
import System.Random (randomRIO)
2929

3030
import qualified Streamly.Internal.Data.Fold as FL
3131
import qualified Streamly.Internal.Data.Scanl as Scanl
3232

3333
import qualified Stream.Common as Common
3434
import qualified Streamly.Internal.Data.Unfold as Unfold
35-
36-
import Streamly.Internal.Data.Stream (Stream)
3735
import qualified Streamly.Internal.Data.Stream as Stream
38-
#ifndef USE_STREAMLY_CORE
39-
import qualified Streamly.Internal.Data.Stream.Prelude as Stream
40-
#endif
4136

4237
import Test.Tasty.Bench
4338
import Stream.Common hiding (scanl')
4439
import Streamly.Benchmark.Common
4540
import Prelude hiding (sequence, mapM)
4641

47-
48-
4942
-------------------------------------------------------------------------------
5043
-- Pipelines (stream-to-stream transformations)
5144
-------------------------------------------------------------------------------
@@ -98,17 +91,6 @@ sequence = Common.drain . Stream.sequence
9891
tap :: MonadIO m => Int -> Stream m Int -> m ()
9992
tap n = composeN n $ Stream.tap FL.sum
10093

101-
#ifndef USE_STREAMLY_CORE
102-
{-# INLINE pollCounts #-}
103-
pollCounts :: Int -> Stream IO Int -> IO ()
104-
pollCounts n =
105-
composeN n (Stream.parTapCount (const True) f)
106-
107-
where
108-
109-
f = Stream.drain . Stream.rollingMap2 (-) . Stream.delayPost 1
110-
#endif
111-
11294
{-# INLINE _timestamped #-}
11395
_timestamped :: MonadIO m => Stream m Int -> m ()
11496
_timestamped = Stream.drain . Stream.timestamped
@@ -142,9 +124,6 @@ o_1_space_mapping value =
142124
sequence (sourceUnfoldrAction value n)
143125
, benchIOSink value "mapM" (mapM 1)
144126
, benchIOSink value "tap" (tap 1)
145-
#ifndef USE_STREAMLY_CORE
146-
, benchIOSink value "parTapCount 1 second" (pollCounts 1)
147-
#endif
148127
-- XXX tasty-bench hangs benchmarking this
149128
-- , benchIOSink value "timestamped" _timestamped
150129
-- Scanning
@@ -314,31 +293,6 @@ takeWhileTrue value n = composeN n $ Stream.takeWhile (<= (value + 1))
314293
takeWhileMTrue :: MonadIO m => Int -> Int -> Stream m Int -> m ()
315294
takeWhileMTrue value n = composeN n $ Stream.takeWhileM (return . (<= (value + 1)))
316295

317-
#if !defined(USE_STREAMLY_CORE)
318-
{-# INLINE takeInterval #-}
319-
takeInterval :: Double -> Int -> Stream IO Int -> IO ()
320-
takeInterval i n = composeN n (Stream.takeInterval i)
321-
322-
-- Inspection testing is disabled for takeInterval
323-
-- Enable it when looking at it throughly
324-
#ifdef INSPECTION
325-
-- inspect $ hasNoType 'takeInterval ''SPEC
326-
-- inspect $ hasNoTypeClasses 'takeInterval
327-
-- inspect $ 'takeInterval `hasNoType` ''D.Step
328-
#endif
329-
330-
{-# INLINE dropInterval #-}
331-
dropInterval :: Double -> Int -> Stream IO Int -> IO ()
332-
dropInterval i n = composeN n (Stream.dropInterval i)
333-
334-
-- Inspection testing is disabled for dropInterval
335-
-- Enable it when looking at it throughly
336-
#ifdef INSPECTION
337-
-- inspect $ hasNoTypeClasses 'dropInterval
338-
-- inspect $ 'dropInterval `hasNoType` ''D.Step
339-
#endif
340-
#endif
341-
342296
{-# INLINE dropOne #-}
343297
dropOne :: MonadIO m => Int -> Stream m Int -> m ()
344298
dropOne n = composeN n $ Stream.drop 1
@@ -359,13 +313,6 @@ dropWhileMTrue value n = composeN n $ Stream.dropWhileM (return . (<= (value + 1
359313
dropWhileFalse :: MonadIO m => Int -> Int -> Stream m Int -> m ()
360314
dropWhileFalse value n = composeN n $ Stream.dropWhile (> (value + 1))
361315

362-
#ifndef USE_STREAMLY_CORE
363-
-- XXX Decide on the time interval
364-
{-# INLINE _intervalsOfSum #-}
365-
_intervalsOfSum :: Stream.MonadAsync m => Double -> Int -> Stream m Int -> m ()
366-
_intervalsOfSum i n = composeN n (Stream.intervalsOf i FL.sum)
367-
#endif
368-
369316
{-# INLINE findIndices #-}
370317
findIndices :: MonadIO m => Int -> Int -> Stream m Int -> m ()
371318
findIndices value n = composeN n $ Stream.findIndices (== (value + 1))
@@ -420,10 +367,6 @@ o_1_space_filtering value =
420367
-- , benchIOSink value "takeWhileM-true" (_takeWhileMTrue value 1)
421368
, benchIOSink value "drop-one" (dropOne 1)
422369
, benchIOSink value "drop-all" (dropAll value 1)
423-
#if !defined(USE_STREAMLY_CORE)
424-
, benchIOSink value "takeInterval-all" (takeInterval 10000 1)
425-
, benchIOSink value "dropInterval-all" (dropInterval 10000 1)
426-
#endif
427370
, benchIOSink value "dropWhile-true" (dropWhileTrue value 1)
428371
-- , benchIOSink value "dropWhileM-true" (_dropWhileMTrue value 1)
429372
, benchIOSink

0 commit comments

Comments
 (0)