Skip to content
Snippets Groups Projects
Commit d71e9d72 authored by Ben Gamari's avatar Ben Gamari :turtle:
Browse files

With and without ticks

parent 055bdf57
No related branches found
No related tags found
No related merge requests found
......@@ -69,15 +69,13 @@ collectArgsTicks_OnStack = go mempty
in (e', as, t:ts)
go as a = (a, as, [])
collectArgsTicksBenchmarks :: Int -> Benchmark
collectArgsTicksBenchmarks len = bgroup ("length="++show len)
collectArgsTicksBenchmarks :: Expr -> [Benchmark]
collectArgsTicksBenchmarks xs =
[ bench "sequence" $ nf (collectArgsTicks_Seq) xs
, bench "dlist" $ nf (collectArgsTicks_DList) xs
, bench "list" $ nf (collectArgsTicks_List) xs
, bench "on-stack" $ nf (collectArgsTicks_OnStack) xs
]
where
xs = appChain len
collectArgs_Seq :: Expr -> (Expr, Seq.Seq Expr)
collectArgs_Seq = go mempty
......@@ -110,7 +108,7 @@ collectArgs_OnStack = go
go a = (a, [])
collectArgsBenchmarks :: Int -> Benchmark
collectArgsBenchmarks len = bgroup ("length="++show len)
collectArgsBenchmarks len = lengthGroup len
[ bench "sequence" $ nf (collectArgs_Seq) xs
, bench "dlist" $ nf (collectArgs_DList) xs
, bench "list" $ nf (collectArgs_List) xs
......@@ -142,7 +140,7 @@ rebuild_DList = go mempty
go acc [] = toList acc
rebuildBenchmarks :: Int -> Benchmark
rebuildBenchmarks len = bgroup ("length="++show len)
rebuildBenchmarks len = lengthGroup len
[ bench "sequence" $ whnf (length . rebuild_Seq) xs
, bench "dlist" $ whnf (length . rebuild_DList) xs
, bench "list" $ whnf (length . rebuild_List) xs
......@@ -151,9 +149,22 @@ rebuildBenchmarks len = bgroup ("length="++show len)
xs = [1..len]
lengths = [1,2,5,10,20,50,100,200]
lengthGroup :: Int -> [Benchmark] -> Benchmark
lengthGroup n = bgroup ("length=" ++ show n)
main :: IO ()
main = defaultMain
[ bgroup "rebuild" $ map rebuildBenchmarks lengths
, bgroup "collectArgs" $ map collectArgsBenchmarks lengths
, bgroup "collectArgsTicks" $ map collectArgsTicksBenchmarks lengths
, bgroup "collectArgsTicks"
[ bgroup "no-ticks"
[ lengthGroup len $ collectArgsTicksBenchmarks $ appChain len
| len <- lengths
]
, bgroup "with-ticks"
[ lengthGroup len $ collectArgsTicksBenchmarks $ appTickChain len
| len <- lengths
]
]
]
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment