Skip to content

Commit fc8a8c5

Browse files
Fix breakage, and split the stream benchmarks
To reduce memory footprint.
1 parent 0db7ec5 commit fc8a8c5

File tree

12 files changed

+118
-111
lines changed

12 files changed

+118
-111
lines changed

benchmark/Streamly/Benchmark/Data/Stream.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,7 @@ import qualified Stream.Generate as Generation
2525
import qualified Stream.Lift as Lift
2626
import qualified Stream.Reduce as NestedFold
2727
import qualified Stream.Split as Split
28+
import qualified Stream.SplitChunks as SplitChunks
2829
import qualified Stream.Transform as Transformation
2930

3031
import Streamly.Benchmark.Common
@@ -61,6 +62,7 @@ main = do
6162
, Elimination.benchmarks moduleName size
6263
, Exceptions.benchmarks moduleName env size
6364
, Split.benchmarks moduleName env
65+
, SplitChunks.benchmarks moduleName env
6466
, Transformation.benchmarks moduleName size
6567
, NestedFold.benchmarks moduleName size
6668
, Lift.benchmarks moduleName size

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

Lines changed: 4 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -27,14 +27,12 @@ module Stream.Common
2727

2828
-- Benchmark stream generation
2929
, sourceUnfoldr
30-
, sourceUnfoldrM
3130
, sourceUnfoldrAction
3231
, sourceConcatMapId
3332
, sourceFromFoldable
3433
, sourceFromFoldableM
3534

3635
-- Benchmark stream elimination
37-
, benchIOSink
3836
, benchIOSinkPureSrc
3937
, benchIOSrc
4038
, benchIO
@@ -79,15 +77,13 @@ import Control.DeepSeq (NFData)
7977
import Control.Exception (try)
8078
import GHC.Exception (ErrorCall)
8179
import System.Random (randomRIO)
80+
import Streamly.Benchmark.Common (sourceUnfoldrM)
81+
import Streamly.Internal.Data.Stream (Stream)
8282

8383
import qualified Streamly.Internal.Data.Fold as Fold
8484
import qualified Streamly.Internal.Data.Pipe as Pipe
8585
import qualified Streamly.Internal.Data.Scanl as Scanl
8686
import qualified Streamly.Internal.Data.Scanr as Scanr
87-
88-
89-
import Streamly.Internal.Data.Stream (Stream)
90-
import qualified Streamly.Internal.Data.Stream as D
9187
import qualified Streamly.Internal.Data.Stream as Stream
9288

9389
import Test.Tasty.Bench
@@ -107,7 +103,7 @@ append = Stream.append
107103

108104
{-# INLINE append2 #-}
109105
append2 :: Monad m => Stream m a -> Stream m a -> Stream m a
110-
append2 = D.append
106+
append2 = Stream.append
111107

112108
{-# INLINE drain #-}
113109
drain :: Monad m => Stream m a -> m ()
@@ -129,17 +125,6 @@ fromListM = Stream.sequence . Stream.fromList
129125
fromFoldableM :: MonadAsync m => [m a] -> Stream m a
130126
fromFoldableM = Stream.sequence . Stream.fromFoldable
131127

132-
{-# INLINE sourceUnfoldrM #-}
133-
sourceUnfoldrM :: MonadAsync m => Int -> Int -> Stream m Int
134-
sourceUnfoldrM count start = Stream.unfoldrM step start
135-
136-
where
137-
138-
step cnt =
139-
if cnt > start + count
140-
then return Nothing
141-
else return (Just (cnt, cnt + 1))
142-
143128
{-# INLINE sourceUnfoldr #-}
144129
sourceUnfoldr :: Monad m => Int -> Int -> Stream m Int
145130
sourceUnfoldr count start = Stream.unfoldr step start
@@ -170,13 +155,6 @@ sourceFromFoldable value n = Stream.fromFoldable [n..n+value]
170155
sourceFromFoldableM :: Monad m => Int -> Int -> Stream m Int
171156
sourceFromFoldableM value n = Stream.fromFoldableM (fmap return [n..n+value])
172157

173-
{-# INLINE benchIOSink #-}
174-
benchIOSink
175-
:: (NFData b)
176-
=> Int -> String -> (Stream IO Int -> IO b) -> Benchmark
177-
benchIOSink value name f =
178-
bench name $ nfIO $ randomRIO (1,1) >>= f . sourceUnfoldrM value
179-
180158
{-# INLINE benchIOSinkPureSrc #-}
181159
benchIOSinkPureSrc
182160
:: (NFData b)
@@ -201,7 +179,7 @@ benchIO name f = bench name $ nfIO $ randomRIO (1,1) >>= f
201179
sourceConcatMapId :: (Monad m)
202180
=> Int -> Int -> Stream m (Stream m Int)
203181
sourceConcatMapId value n =
204-
Stream.fromList $ fmap (D.fromEffect . return) [n..n+value]
182+
Stream.fromList $ fmap (Stream.fromEffect . return) [n..n+value]
205183

206184
{-# INLINE apDiscardFst #-}
207185
apDiscardFst :: MonadAsync m =>

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

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,6 @@ import qualified Streamly.Internal.Data.Fold as Fold
3535
#ifdef INSPECTION
3636
import GHC.Types (SPEC(..))
3737
import Test.Inspection
38-
import qualified Streamly.Internal.Data.Stream as D
3938
#endif
4039

4140
import Stream.Common
@@ -581,7 +580,7 @@ eqByPure value n = eqBy' (sourceUnfoldr value n)
581580
#ifdef INSPECTION
582581
inspect $ hasNoTypeClasses 'eqByPure
583582
inspect $ 'eqByPure `hasNoType` ''SPEC
584-
inspect $ 'eqByPure `hasNoType` ''D.Step
583+
inspect $ 'eqByPure `hasNoType` ''S.Step
585584
#endif
586585

587586
{-# INLINE eqInstance #-}
@@ -603,7 +602,7 @@ cmpByPure value n = cmpBy' (sourceUnfoldr value n)
603602
#ifdef INSPECTION
604603
inspect $ hasNoTypeClasses 'cmpByPure
605604
inspect $ 'cmpByPure `hasNoType` ''SPEC
606-
inspect $ 'cmpByPure `hasNoType` ''D.Step
605+
inspect $ 'cmpByPure `hasNoType` ''S.Step
607606
#endif
608607

609608
{-# INLINE ordInstance #-}
@@ -642,7 +641,7 @@ eqBy value n = eqBy' (sourceUnfoldrM value n)
642641
#ifdef INSPECTION
643642
inspect $ hasNoTypeClasses 'eqBy
644643
inspect $ 'eqBy `hasNoType` ''SPEC
645-
inspect $ 'eqBy `hasNoType` ''D.Step
644+
inspect $ 'eqBy `hasNoType` ''S.Step
646645
#endif
647646

648647
{-# INLINE cmpBy #-}
@@ -652,7 +651,7 @@ cmpBy value n = cmpBy' (sourceUnfoldrM value n)
652651
#ifdef INSPECTION
653652
inspect $ hasNoTypeClasses 'cmpBy
654653
inspect $ 'cmpBy `hasNoType` ''SPEC
655-
inspect $ 'cmpBy `hasNoType` ''D.Step
654+
inspect $ 'cmpBy `hasNoType` ''S.Step
656655
#endif
657656

658657
o_1_space_elimination_multi_stream :: Int -> [Benchmark]

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

Lines changed: 7 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -23,23 +23,22 @@ module Stream.Expand (benchmarks) where
2323
#ifdef INSPECTION
2424
import GHC.Types (SPEC(..))
2525
import Test.Inspection
26-
27-
import qualified Streamly.Internal.Data.Stream as D
2826
#endif
2927

30-
import qualified Stream.Common as Common
31-
import qualified Streamly.Internal.Data.Unfold as UF
32-
3328
import Streamly.Data.Stream (Stream)
3429
import Streamly.Data.Unfold (Unfold)
30+
31+
import qualified Stream.Common as Common
32+
import qualified Streamly.Internal.Data.Unfold as UF
3533
import qualified Streamly.Internal.Data.Stream as S
3634
import qualified Streamly.Internal.Data.Unfold as Unfold
3735
import qualified Streamly.Internal.Data.Fold as Fold
3836
import qualified Streamly.Internal.Data.Stream as Stream
3937
import qualified Streamly.Internal.Data.StreamK as StreamK
38+
4039
import Test.Tasty.Bench
4140
import Stream.Common
42-
import Streamly.Benchmark.Common
41+
import Streamly.Benchmark.Common hiding (benchIOSrc)
4342
import Prelude hiding (concatMap, zipWith)
4443

4544
-------------------------------------------------------------------------------
@@ -218,7 +217,7 @@ unfoldSched outer inner n =
218217
inspect $ hasNoTypeClasses 'unfoldSched
219218
-- inspect $ 'unfoldSched `hasNoType` ''SPEC
220219
-- inspect $ 'unfoldSched `hasNoType`
221-
-- ''D.ConcatUnfoldInterleaveState
220+
-- ''Stream.ConcatUnfoldInterleaveState
222221
#endif
223222

224223
o_1_space_joining :: Int -> [Benchmark]
@@ -328,7 +327,7 @@ unfoldEach outer inner start = drain $
328327

329328
#ifdef INSPECTION
330329
inspect $ hasNoTypeClasses 'unfoldEach
331-
inspect $ 'unfoldEach `hasNoType` ''D.UnfoldEachState
330+
inspect $ 'unfoldEach `hasNoType` ''Stream.UnfoldEachState
332331
inspect $ 'unfoldEach `hasNoType` ''SPEC
333332
#endif
334333

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

Lines changed: 5 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -17,28 +17,20 @@ module Stream.Generate (benchmarks) where
1717
import Control.DeepSeq (NFData(..))
1818
import Control.Monad.IO.Class (MonadIO)
1919
import Data.Functor.Identity (Identity(..))
20+
import Streamly.Internal.Data.Stream (Stream)
2021
import Streamly.Internal.Data.Time.Units (AbsTime)
2122

2223
import qualified GHC.Exts as GHC
2324
import qualified Streamly.Internal.Data.Fold as Fold
24-
25-
import Stream.Common
26-
import Streamly.Internal.Data.Stream (Stream)
2725
import qualified Streamly.Internal.Data.Stream as Stream
2826

2927
import Test.Tasty.Bench
30-
import Streamly.Benchmark.Common
28+
import Stream.Common
29+
import Streamly.Benchmark.Common hiding (benchIOSrc)
3130
import qualified Prelude
3231

3332
import Prelude hiding (repeat, replicate, iterate)
3433

35-
-------------------------------------------------------------------------------
36-
-- Generation
37-
-------------------------------------------------------------------------------
38-
39-
toStreamD :: a -> a
40-
toStreamD = id
41-
4234
-------------------------------------------------------------------------------
4335
-- fromList
4436
-------------------------------------------------------------------------------
@@ -177,8 +169,8 @@ o_1_space_generation value =
177169
, benchIOSrc "fracFromTo" (sourceFracFromTo value)
178170
, benchIOSrc "fromList" (sourceFromList value)
179171
, benchIOSrc "fromListM" (sourceFromListM value)
180-
, benchPureSrc "IsList.fromList" (toStreamD . sourceIsList value)
181-
, benchPureSrc "IsString.fromString" (toStreamD . sourceIsString value)
172+
, benchPureSrc "IsList.fromList" (sourceIsList value)
173+
, benchPureSrc "IsString.fromString" (sourceIsString value)
182174
, benchIOSrc "enumerateFrom" (enumerateFrom value)
183175
, benchIOSrc "enumerateFromTo" (enumerateFromTo value)
184176
, benchIOSrc "enumerateFromThen" (enumerateFromThen value)

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

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -14,17 +14,16 @@ module Stream.Lift (benchmarks) where
1414
import Control.DeepSeq (NFData(..))
1515
import Control.Monad.State.Strict (StateT, get, put)
1616
import Data.Functor.Identity (Identity)
17-
import Stream.Common (sourceUnfoldr, sourceUnfoldrM, benchIOSrc)
17+
import Stream.Common (sourceUnfoldr, benchIOSrc)
1818
import System.Random (randomRIO)
19+
import Streamly.Internal.Data.Stream (Stream)
1920

2021
import qualified Stream.Common as Common
2122
import qualified Streamly.Internal.Data.Fold as Fold
22-
23-
import Streamly.Internal.Data.Stream (Stream)
2423
import qualified Streamly.Internal.Data.Stream as Stream
2524

2625
import Test.Tasty.Bench
27-
import Streamly.Benchmark.Common
26+
import Streamly.Benchmark.Common hiding (benchIOSrc)
2827
import Prelude hiding (reverse, tail)
2928

3029
-------------------------------------------------------------------------------

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

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -19,16 +19,15 @@ import Control.Monad.IO.Class (MonadIO(..))
1919
import Data.Maybe (isJust)
2020
import Data.Monoid (Sum(..))
2121
import GHC.Generics (Generic)
22+
import Streamly.Internal.Data.Stream (Stream)
2223

23-
import qualified Streamly.Internal.Data.Refold.Type as Refold
24-
import qualified Streamly.Internal.Data.Fold as FL
2524
import qualified Stream.Common as Common
26-
27-
import Streamly.Internal.Data.Stream (Stream)
25+
import qualified Streamly.Internal.Data.Fold as FL
26+
import qualified Streamly.Internal.Data.Refold.Type as Refold
2827
import qualified Streamly.Internal.Data.Stream as S
2928

3029
import Test.Tasty.Bench
31-
import Streamly.Benchmark.Common
30+
import Streamly.Benchmark.Common hiding (benchIOSrc)
3231
import Stream.Common
3332
import Prelude hiding (reverse, tail)
3433

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

Lines changed: 0 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,6 @@ import qualified Streamly.Internal.Data.Array as Array
3030
import qualified Streamly.Internal.Data.Fold as Fold
3131
import qualified Streamly.Internal.Data.Stream as Stream
3232
import qualified Streamly.Internal.FileSystem.Handle as Handle
33-
import qualified Streamly.Internal.Unicode.Stream as Unicode
3433

3534
import Test.Tasty.Bench hiding (env)
3635
import Prelude hiding (last, length)
@@ -277,28 +276,9 @@ o_1_space_reduce_read_split env =
277276
]
278277
]
279278

280-
-- | Split on a character sequence.
281-
splitOnSeqUtf8 :: String -> Handle -> IO Int
282-
splitOnSeqUtf8 str inh =
283-
(Stream.fold Fold.length
284-
$ Stream.splitSepBySeq_ (Array.fromList str) Fold.drain
285-
$ Unicode.decodeUtf8Chunks
286-
$ Handle.readChunks inh) -- >>= print
287-
288-
o_1_space_reduce_toChunks_split :: BenchEnv -> [Benchmark]
289-
o_1_space_reduce_toChunks_split env =
290-
[ bgroup "FileSplitSeqUtf8"
291-
[ mkBenchSmall "splitOnSeqUtf8 word abcdefgh"
292-
env $ \inh _ -> splitOnSeqUtf8 "abcdefgh" inh
293-
, mkBenchSmall "splitOnSeqUtf8 KR abcdefghijklmnopqrstuvwxyz"
294-
env $ \inh _ -> splitOnSeqUtf8 "abcdefghijklmnopqrstuvwxyz" inh
295-
]
296-
]
297-
298279
benchmarks :: String -> BenchEnv -> [Benchmark]
299280
benchmarks moduleName env =
300281
[ bgroup (o_1_space_prefix moduleName) $ concat
301282
[ o_1_space_reduce_read_split env
302-
, o_1_space_reduce_toChunks_split env
303283
]
304284
]
Lines changed: 73 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,73 @@
1+
2+
-- |
3+
-- Module : Stream.SplitChunks
4+
-- Copyright : (c) 2019 Composewell Technologies
5+
-- License : BSD-3-Clause
6+
-- Maintainer : [email protected]
7+
-- Stability : experimental
8+
-- Portability : GHC
9+
10+
{-# LANGUAGE CPP #-}
11+
{-# LANGUAGE ScopedTypeVariables #-}
12+
13+
#ifdef __HADDOCK_VERSION__
14+
#undef INSPECTION
15+
#endif
16+
17+
#ifdef INSPECTION
18+
{-# LANGUAGE TemplateHaskell #-}
19+
{-# OPTIONS_GHC -fplugin Test.Inspection.Plugin #-}
20+
#endif
21+
22+
module Stream.SplitChunks (benchmarks) where
23+
24+
import System.IO (Handle)
25+
26+
import qualified Streamly.Internal.Data.Array as Array
27+
import qualified Streamly.Internal.Data.Fold as Fold
28+
import qualified Streamly.Internal.Data.Stream as Stream
29+
import qualified Streamly.Internal.FileSystem.Handle as Handle
30+
import qualified Streamly.Internal.Unicode.Stream as Unicode
31+
32+
import Test.Tasty.Bench hiding (env)
33+
import Prelude hiding (last, length)
34+
import Streamly.Benchmark.Common
35+
import Streamly.Benchmark.Common.Handle
36+
37+
#ifdef INSPECTION
38+
import Streamly.Internal.Data.Stream (Step(..))
39+
40+
import qualified Streamly.Internal.Data.MutArray as MutArray
41+
import qualified Streamly.Internal.Data.Unfold as Unfold
42+
43+
import Test.Inspection
44+
#endif
45+
46+
-------------------------------------------------------------------------------
47+
-- reduce with splitting transformations
48+
-------------------------------------------------------------------------------
49+
50+
-- | Split on a character sequence.
51+
splitOnSeqUtf8 :: String -> Handle -> IO Int
52+
splitOnSeqUtf8 str inh =
53+
(Stream.fold Fold.length
54+
$ Stream.splitSepBySeq_ (Array.fromList str) Fold.drain
55+
$ Unicode.decodeUtf8Chunks
56+
$ Handle.readChunks inh) -- >>= print
57+
58+
o_1_space_reduce_toChunks_split :: BenchEnv -> [Benchmark]
59+
o_1_space_reduce_toChunks_split env =
60+
[ bgroup "FileSplitSeqUtf8"
61+
[ mkBenchSmall "splitOnSeqUtf8 word abcdefgh"
62+
env $ \inh _ -> splitOnSeqUtf8 "abcdefgh" inh
63+
, mkBenchSmall "splitOnSeqUtf8 KR abcdefghijklmnopqrstuvwxyz"
64+
env $ \inh _ -> splitOnSeqUtf8 "abcdefghijklmnopqrstuvwxyz" inh
65+
]
66+
]
67+
68+
benchmarks :: String -> BenchEnv -> [Benchmark]
69+
benchmarks moduleName env =
70+
[ bgroup (o_1_space_prefix moduleName) $ concat
71+
[ o_1_space_reduce_toChunks_split env
72+
]
73+
]

0 commit comments

Comments
 (0)