Fix naming in benchmarks

* bench:Prelude.Serial
- foldrMToStream -> foldrToStream
- scan -> scanl'

* bench:Prelude.ZipSerial
- zip -> zipWith
- zipM -> zipWithM

* bench:Prelude.ZipAsync
- zipAsync -> zipAsyncWith
- zipAsyncM -> zipAsyncWithM
This commit is contained in:
adithyaov 2020-11-11 22:40:12 +05:30 committed by Adithya Kumar
parent f10c944b55
commit 053a38c6a1
3 changed files with 35 additions and 33 deletions

View File

@ -437,9 +437,9 @@ foldrMElem e =
else xs)
(return P.False)
{-# INLINE foldrMToStream #-}
foldrMToStream :: Monad m => SerialT m Int -> m (SerialT Identity Int)
foldrMToStream = S.foldr S.cons S.nil
{-# INLINE foldrToStream #-}
foldrToStream :: Monad m => SerialT m Int -> m (SerialT Identity Int)
foldrToStream = S.foldr S.cons S.nil
{-# INLINE foldrMBuild #-}
foldrMBuild :: Monad m => SerialT m Int -> m [Int]
@ -573,8 +573,8 @@ o_1_space_elimination_folds value =
]
, bgroup "Identity"
[ benchIdentitySink value "foldrMElem" (foldrMElem value)
, benchIdentitySink value "foldrMToStreamLength"
(S.length . runIdentity . foldrMToStream)
, benchIdentitySink value "foldrToStreamLength"
(S.length . runIdentity . foldrToStream)
, benchPureSink value "foldrMToListLength"
(P.length . runIdentity . foldrMBuild)
]
@ -855,9 +855,9 @@ o_n_space_traversable value =
-- maps and scans
-------------------------------------------------------------------------------
{-# INLINE scan #-}
scan :: MonadIO m => Int -> SerialT m Int -> m ()
scan n = composeN n $ S.scanl' (+) 0
{-# INLINE scanl' #-}
scanl' :: MonadIO m => Int -> SerialT m Int -> m ()
scanl' n = composeN n $ S.scanl' (+) 0
{-# INLINE scanlM' #-}
scanlM' :: MonadIO m => Int -> SerialT m Int -> m ()
@ -949,7 +949,7 @@ o_1_space_mapping value =
, benchIOSink value "timestamped" timestamped
-- Scanning
, benchIOSink value "scanl'" (scan 1)
, benchIOSink value "scanl'" (scanl' 1)
, benchIOSink value "scanl1'" (scanl1' 1)
, benchIOSink value "scanlM'" (scanlM' 1)
, benchIOSink value "postscanl'" (postscanl' 1)
@ -965,7 +965,7 @@ o_1_space_mappingX4 value =
, benchIOSink value "mapM" (mapM serially 4)
, benchIOSink value "trace" (trace 4)
, benchIOSink value "scan" (scan 4)
, benchIOSink value "scanl'" (scanl' 4)
, benchIOSink value "scanl1'" (scanl1' 4)
, benchIOSink value "scanlM'" (scanlM' 4)
, benchIOSink value "postscanl'" (postscanl' 4)

View File

@ -22,14 +22,14 @@ moduleName = "Prelude.ZipAsync"
-- Zipping
-------------------------------------------------------------------------------
{-# INLINE zipAsync #-}
zipAsync :: (S.IsStream t, S.MonadAsync m) => Int -> Int -> t m (Int, Int)
zipAsync count n =
{-# INLINE zipAsyncWith #-}
zipAsyncWith :: (S.IsStream t, S.MonadAsync m) => Int -> Int -> t m (Int, Int)
zipAsyncWith count n =
S.zipAsyncWith (,) (sourceUnfoldrM count n) (sourceUnfoldrM count (n + 1))
{-# INLINE zipAsyncM #-}
zipAsyncM :: (S.IsStream t, S.MonadAsync m) => Int -> Int -> t m (Int, Int)
zipAsyncM count n =
{-# INLINE zipAsyncWithM #-}
zipAsyncWithM :: (S.IsStream t, S.MonadAsync m) => Int -> Int -> t m (Int, Int)
zipAsyncWithM count n =
S.zipAsyncWithM
(curry return)
(sourceUnfoldrM count n)
@ -44,8 +44,10 @@ zipAsyncAp count n =
o_1_space_joining :: Int -> [Benchmark]
o_1_space_joining value =
[ bgroup "joining"
[ benchIOSrc serially "zipAsync (2,x/2)" (zipAsync (value `div` 2))
, benchIOSrc serially "zipAsyncM (2,x/2)" (zipAsyncM (value `div` 2))
[ benchIOSrc serially "zipAsyncWith (2,x/2)" (zipAsyncWith
(value `div` 2))
, benchIOSrc serially "zipAsyncWithM (2,x/2)" (zipAsyncWithM
(value `div` 2))
, benchIOSrc serially "zipAsyncAp (2,x/2)" (zipAsyncAp (value `div` 2))
, benchIOSink value "fmap zipAsyncly" $ fmapN S.zipAsyncly 1
]

View File

@ -19,7 +19,7 @@
{-# OPTIONS_GHC -fplugin Test.Inspection.Plugin #-}
#endif
import Prelude hiding (zip)
import Prelude hiding (zipWith)
import Streamly.Prelude (MonadAsync)
import qualified Streamly.Prelude as S
@ -54,9 +54,9 @@ sourceUnfoldrM count start = S.unfoldrM step start
then return Nothing
else return (Just (cnt, cnt + 1))
{-# INLINE zip #-}
zip :: Int -> Int -> IO ()
zip count n =
{-# INLINE zipWith #-}
zipWith :: Int -> Int -> IO ()
zipWith count n =
S.drain $
S.zipWith
(,)
@ -64,14 +64,14 @@ zip count n =
(S.serially $ sourceUnfoldrM count (n + 1))
#ifdef INSPECTION
inspect $ hasNoTypeClasses 'zip
inspect $ 'zip `hasNoType` ''SPEC
inspect $ 'zip `hasNoType` ''D.Step
inspect $ hasNoTypeClasses 'zipWith
inspect $ 'zipWith `hasNoType` ''SPEC
inspect $ 'zipWith `hasNoType` ''D.Step
#endif
{-# INLINE zipM #-}
zipM :: Int -> Int -> IO ()
zipM count n =
{-# INLINE zipWithM #-}
zipWithM :: Int -> Int -> IO ()
zipWithM count n =
S.drain $
S.zipWithM
(curry return)
@ -79,16 +79,16 @@ zipM count n =
(sourceUnfoldrM count (n + 1))
#ifdef INSPECTION
inspect $ hasNoTypeClasses 'zipM
inspect $ 'zipM `hasNoType` ''SPEC
inspect $ 'zipM `hasNoType` ''D.Step
inspect $ hasNoTypeClasses 'zipWithM
inspect $ 'zipWithM `hasNoType` ''SPEC
inspect $ 'zipWithM `hasNoType` ''D.Step
#endif
o_1_space_joining :: Int -> [Benchmark]
o_1_space_joining value =
[ bgroup "joining"
[ benchIOSrc1 "zip (2,x/2)" (zip (value `div` 2))
, benchIOSrc1 "zipM (2,x/2)" (zipM (value `div` 2))
[ benchIOSrc1 "zip (2,x/2)" (zipWith (value `div` 2))
, benchIOSrc1 "zipM (2,x/2)" (zipWithM (value `div` 2))
]
]