Skip to content

Instantly share code, notes, and snippets.

@yihuang
Forked from qzchenwl/lazy_vs_st.hs
Created March 27, 2012 00:51
Show Gist options
  • Save yihuang/2211202 to your computer and use it in GitHub Desktop.
Save yihuang/2211202 to your computer and use it in GitHub Desktop.
lazy vs ST
{-# LANGUAGE BangPatterns #-}
module Main (fib1, fib2, fib3, fib4, main) where
import Control.Monad
import Control.Monad.ST
import Data.STRef
import Criterion.Main
fib1 :: Int -> Integer
fib1 n = fst $ fib' n
where fib' 0 = (1, 1)
fib' n = sum $ fib' (n-1)
sum (!a, !b) = (b, a + b)
fib2 :: Int -> Integer
fib2 n = fib' (1,1) (n-1)
where fib' (_, b) 0 = b
fib' (a, b) n = fib' (b, a+b) (n-1)
fib3 :: Int -> Integer
fib3 n = runST $ do
a <- newSTRef 1
b <- newSTRef 1
replicateM_ (n-1) $ do
!a' <- readSTRef a
!b' <- readSTRef b
writeSTRef a b'
writeSTRef b $! a'+b'
readSTRef b
fib4 :: Int -> Integer
fib4 n = runST $ do
a <- newSTRef 1
b <- newSTRef 1
replicateM_ (n-1) $ do
!a' <- readSTRef a
!b' <- readSTRef b
if a' > b'
then writeSTRef b $! a'+b'
else writeSTRef a $! a'+b'
a'' <- readSTRef a
b'' <- readSTRef b
if a'' > b''
then return a''
else return b''
main = do
let n = 20000
defaultMain
[ bgroup (show n)
[ bench "normal" $ whnf fib1 n
, bench "tail recur" $ whnf fib2 n
, bench "st" $ whnf fib3 n
, bench "st'" $ whnf fib4 n
]
]
{-
$ ./fibs
warming up
estimating clock resolution...
mean is 1.761012 us (320001 iterations)
found 1693 outliers among 319999 samples (0.5%)
1372 (0.4%) high severe
estimating cost of a clock call...
mean is 125.4355 ns (18 iterations)
found 1 outliers among 18 samples (5.6%)
1 (5.6%) high mild
benchmarking 20000/normal
mean: 5.329309 ms, lb 5.316950 ms, ub 5.357324 ms, ci 0.950
std dev: 91.28458 us, lb 49.79853 us, ub 185.9230 us, ci 0.950
found 4 outliers among 100 samples (4.0%)
3 (3.0%) high mild
1 (1.0%) high severe
variance introduced by outliers: 9.467%
variance is slightly inflated by outliers
benchmarking 20000/tail recur
mean: 4.251586 ms, lb 4.228011 ms, ub 4.278794 ms, ci 0.950
std dev: 130.4312 us, lb 114.5906 us, ub 149.0773 us, ci 0.950
found 1 outliers among 100 samples (1.0%)
variance introduced by outliers: 25.790%
variance is moderately inflated by outliers
benchmarking 20000/st
mean: 4.340554 ms, lb 4.331833 ms, ub 4.350415 ms, ci 0.950
std dev: 47.30373 us, lb 41.83483 us, ub 54.34751 us, ci 0.950
benchmarking 20000/st'
mean: 4.653138 ms, lb 4.642843 ms, ub 4.667488 ms, ci 0.950
std dev: 61.53674 us, lb 48.35118 us, ub 91.07268 us, ci 0.950
found 4 outliers among 100 samples (4.0%)
3 (3.0%) high mild
1 (1.0%) high severe
variance introduced by outliers: 6.562%
variance is slightly inflated by outliers
-}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment