Skip to content

Instantly share code, notes, and snippets.

@rampion
Last active December 19, 2015 10:09
Show Gist options
  • Star 1 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save rampion/5938169 to your computer and use it in GitHub Desktop.
Save rampion/5938169 to your computer and use it in GitHub Desktop.
module Main where
import Criterion.Main
import qualified Data.List.Ordered as O
import qualified Data.List as L
import qualified Data.Set as S
import qualified Data.IntSet as IS
repeatsTail, orderedIntersect, listIntersect, setIntersect :: [Integer] -> [Integer] -> [Integer] -> [Integer]
intsetIntersect :: [Int] -> [Int] -> [Int] -> [Int]
repeatsTail f s t = go f s t []
where go [] _ _ acc = reverse acc
go _ [] _ acc = reverse acc
go _ _ [] acc = reverse acc
go a@(x:xs) b@(y:ys) c@(z:zs) acc
| x == y && y == z = go xs ys zs (x:acc)
| x <= y && x <= z = go xs b c acc
| y <= x && y <= z = go a ys c acc
| otherwise = go a b zs acc
orderedIntersect a b c = O.isect a $ O.isect b c
listIntersect a b c = L.intersect a $ L.intersect b c
setIntersect a b c = S.toList (S.intersection (S.fromList a) (S.intersection (S.fromList b) (S.fromList c)))
intsetIntersect a b c = IS.toList (IS.intersection (IS.fromList a) (IS.intersection (IS.fromList b) (IS.fromList c)))
fibsLessThan100 :: Integral a => [a]
fibsLessThan100 = takeWhile (<100) . drop 1 $ fibs
where fibs = 1 : 1 : zipWith (+) fibs (tail fibs)
primesLessThan100 :: Integral a => [a]
primesLessThan100 = takeWhile (<100) primes
where primes = (2:) $ [3..] `O.minus` composites
composites = foldr merge [] [ map (p*) [p..] | p <- primes ]
merge (x:xs) ys = x : O.union xs ys
oddsLessThan100 :: Integral a => [a]
oddsLessThan100 = [1, 3..99]
go f = f fibsLessThan100 primesLessThan100 oddsLessThan100
main = defaultMain [
bench "repeatsTail" . flip nf integerArgs $ \(a,b,c) -> repeatsTail a b c,
bench "Data.List.Ordered.isect" . flip nf integerArgs $ \(a,b,c) -> orderedIntersect a b c,
bench "Data.List.intersect" . flip nf integerArgs $ \(a,b,c) -> listIntersect a b c,
bench "Data.Set.intersect" . flip nf integerArgs $ \(a,b,c) -> setIntersect a b c,
bench "Data.IntSet.intersect" . flip nf intArgs $ \(a,b,c) -> intsetIntersect a b c
]
where integerArgs :: ([Integer], [Integer], [Integer])
integerArgs = (fibsLessThan100, primesLessThan100, oddsLessThan100)
intArgs :: ([Int], [Int], [Int])
intArgs = (fibsLessThan100, primesLessThan100, oddsLessThan100)
warming up
estimating clock resolution...
mean is 3.262077 us (160001 iterations)
found 28401 outliers among 159999 samples (17.8%)
25368 (15.9%) low severe
3033 (1.9%) high severe
estimating cost of a clock call...
mean is 90.74326 ns (26 iterations)
found 3 outliers among 26 samples (11.5%)
3 (11.5%) high severe
benchmarking repeatsTail
mean: 11.09914 us, lb 10.57613 us, ub 12.23400 us, ci 0.950
std dev: 3.764360 us, lb 2.101762 us, ub 7.015260 us, ci 0.950
found 19 outliers among 100 samples (19.0%)
4 (4.0%) high mild
15 (15.0%) high severe
variance introduced by outliers: 97.870%
variance is severely inflated by outliers
benchmarking Data.List.Ordered.isect
mean: 2.889594 us, lb 2.764070 us, ub 3.193310 us, ci 0.950
std dev: 944.8768 ns, lb 461.2368 ns, ub 1.863115 us, ci 0.950
found 18 outliers among 100 samples (18.0%)
5 (5.0%) high mild
13 (13.0%) high severe
variance introduced by outliers: 97.860%
variance is severely inflated by outliers
benchmarking Data.List.intersect
mean: 21.58114 us, lb 20.56325 us, ub 23.98248 us, ci 0.950
std dev: 7.593801 us, lb 3.694492 us, ub 13.91247 us, ci 0.950
found 15 outliers among 100 samples (15.0%)
4 (4.0%) high mild
11 (11.0%) high severe
variance introduced by outliers: 98.876%
variance is severely inflated by outliers
benchmarking Data.Set.intersect
mean: 29.81241 us, lb 28.30306 us, ub 33.72211 us, ci 0.950
std dev: 11.52247 us, lb 5.509201 us, ub 23.43350 us, ci 0.950
found 15 outliers among 100 samples (15.0%)
3 (3.0%) high mild
12 (12.0%) high severe
variance introduced by outliers: 98.897%
variance is severely inflated by outliers
benchmarking Data.IntSet.intersect
mean: 5.586984 us, lb 5.329440 us, ub 6.230935 us, ci 0.950
std dev: 1.943859 us, lb 871.9458 ns, ub 3.892892 us, ci 0.950
found 18 outliers among 100 samples (18.0%)
5 (5.0%) high mild
13 (13.0%) high severe
variance introduced by outliers: 97.876%
variance is severely inflated by outliers
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment