Add append benchmark to linear benchmarks

This commit is contained in:
Harendra Kumar 2018-05-06 05:13:10 +05:30
parent be37a7a69d
commit cf1388b330
3 changed files with 22 additions and 2 deletions

View File

@ -4,7 +4,7 @@ print_help () {
echo "Usage: $0 "
echo " [--quick] [--append] "
echo " [--no-graphs] [--no-measure]"
echo " [--benchmark]"
echo " [--benchmark <linear|nested>]"
echo " [--compare] [--base commit] [--candidate commit]"
echo " -- <gauge options>"
echo

View File

@ -10,6 +10,7 @@ import Data.Functor.Identity (Identity, runIdentity)
import System.Random (randomRIO)
import qualified LinearOps as Ops
import Streamly
import Gauge
-- We need a monadic bind here to make sure that the function f does not get
@ -17,6 +18,9 @@ import Gauge
benchIO :: (NFData b) => String -> (Ops.Stream m Int -> IO b) -> Benchmark
benchIO name f = bench name $ nfIO $ randomRIO (1,1000) >>= f . Ops.source
benchIOAppend :: (NFData b) => String -> (Int -> IO b) -> Benchmark
benchIOAppend name f = bench name $ nfIO $ randomRIO (1,1000) >>= f
_benchId :: (NFData b) => String -> (Ops.Stream m Int -> Identity b) -> Benchmark
_benchId name f = bench name $ nf (runIdentity . f) (Ops.source 10)
@ -45,6 +49,12 @@ main = do
, benchIO "dropWhile-true" Ops.dropWhileTrue
]
, benchIO "zip" Ops.zip
, bgroup "append"
[ benchIOAppend "streamly" $ Ops.append streamly
, benchIOAppend "costreamly" $ Ops.append costreamly
, benchIOAppend "coparallely" $ Ops.append coparallely
, benchIOAppend "parallely" $ Ops.append parallely
]
, bgroup "compose"
[ benchIO "mapM" Ops.composeMapM
, benchIO "map-with-all-in-filter" Ops.composeMapAllInFilter

View File

@ -9,7 +9,7 @@ module LinearOps where
import Prelude
(Monad, Int, (+), ($), (.), return, fmap, even, (>), (<=),
subtract, undefined, Maybe)
subtract, undefined, Maybe, Monoid, foldMap)
import qualified Streamly as S
import qualified Streamly.Prelude as S
@ -103,6 +103,16 @@ dropWhileTrue = transform . S.dropWhile (<= maxValue)
zip src = transform $ (S.zipWith (,) src src)
concat _n = return ()
-------------------------------------------------------------------------------
-- Append
-------------------------------------------------------------------------------
{-# INLINE append #-}
append
:: (Monoid (t m Int), Monad m, Monad (t m))
=> (t m Int -> S.StreamT m Int) -> Int -> m ()
append t n = runStream $ t $ foldMap return [n..n+value]
-------------------------------------------------------------------------------
-- Composition
-------------------------------------------------------------------------------