Skip to content

Instantly share code, notes, and snippets.

@qzchenwl
Created April 4, 2012 17:34
Show Gist options
  • Save qzchenwl/2304141 to your computer and use it in GitHub Desktop.
Save qzchenwl/2304141 to your computer and use it in GitHub Desktop.
Fibs
{-# LANGUAGE BangPatterns #-}
module Main where
import Data.List (transpose)
import Criterion.Main
naiveFib, cachedFib, cachedFib', tailrFib, tailrFib', matrixFib
:: Integer -> Integer
naiveFib 0 = 0
naiveFib 1 = 1
naiveFib n = naiveFib (n-1) + naiveFib (n-2)
cachedFib n = fst $ fib' n
where fib' 0 = (0, 1)
fib' n = nextFib $ fib' (n-1)
nextFib (a, b) = (b, a+b)
cachedFib' n = fst $ fib' n
where fib' 0 = (0, 1)
fib' n = nextFib $ fib' (n-1)
nextFib (!a, !b) = (b, a+b)
tailrFib n = fib' n (0, 1)
where fib' 0 (a, _) = a
fib' n (a, b) = fib' (n-1) (b, a+b)
tailrFib' n = fib' n (0, 1)
where fib' 0 (a, _) = a
fib' n (a, b) = fib' (n-1) (b, a+b)
matrixFib n = head (apply (Matrix [[0,1], [1,1]] ^ n) [0,1])
apply :: Num a => Matrix a -> [a] -> [a]
apply (Matrix as) b = [sum (zipWith (*) a b) | a <- as]
newtype Matrix a = Matrix [[a]] deriving (Eq, Show)
instance Num a => Num (Matrix a) where
Matrix as + Matrix bs = Matrix (zipWith (zipWith (+)) as bs)
Matrix as - Matrix bs = Matrix (zipWith (zipWith (-)) as bs)
Matrix as * Matrix bs =
Matrix [[sum $ zipWith (*) a b | b <- transpose bs] | a <- as]
negate (Matrix as) = Matrix (map (map negate) as)
fromInteger x = Matrix (iterate (0:) (fromInteger x : repeat 0))
abs m = m
signum _ = 1
main = do
let n = 200000
defaultMain
[ bgroup (show n)
[ bench "cached" $ whnf cachedFib n
, bench "cached'" $ whnf cachedFib' n
, bench "tail r" $ whnf tailrFib n
, bench "tail r'" $ whnf tailrFib' n
, bench "matrix" $ whnf matrixFib n
]
]
{-
warming up
estimating clock resolution...
mean is 2.390882 us (320001 iterations)
found 1299 outliers among 319999 samples (0.4%)
1049 (0.3%) high severe
estimating cost of a clock call...
mean is 151.0291 ns (20 iterations)
found 2 outliers among 20 samples (10.0%)
1 (5.0%) high mild
1 (5.0%) high severe
benchmarking 200000/cached
collecting 100 samples, 1 iterations each, in estimated 204.3908 s
mean: 2.075414 s, lb 2.071141 s, ub 2.080365 s, ci 0.950
std dev: 23.47871 ms, lb 20.38473 ms, ub 27.50114 ms, ci 0.950
benchmarking 200000/cached'
collecting 100 samples, 1 iterations each, in estimated 47.23220 s
mean: 475.2971 ms, lb 474.8903 ms, ub 476.2249 ms, ci 0.950
std dev: 2.982402 ms, lb 1.647774 ms, ub 6.023921 ms, ci 0.950
benchmarking 200000/tail r
collecting 100 samples, 1 iterations each, in estimated 206.0718 s
mean: 2.067912 s, lb 2.064274 s, ub 2.072599 s, ci 0.950
std dev: 21.12184 ms, lb 17.56422 ms, ub 26.83161 ms, ci 0.950
benchmarking 200000/tail r'
collecting 100 samples, 1 iterations each, in estimated 209.0623 s
mean: 2.072781 s, lb 2.068384 s, ub 2.078740 s, ci 0.950
std dev: 26.09467 ms, lb 20.59899 ms, ub 34.85976 ms, ci 0.950
found 4 outliers among 100 samples (4.0%)
2 (2.0%) high mild
2 (2.0%) high severe
variance introduced by outliers: 2.374%
variance is slightly inflated by outliers
benchmarking 200000/matrix
mean: 8.511683 ms, lb 8.509580 ms, ub 8.513807 ms, ci 0.950
std dev: 10.93877 us, lb 9.336654 us, ub 13.19360 us, ci 0.950
-}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment