Skip to content

Instantly share code, notes, and snippets.

@adept
Created July 26, 2012 09:57
Show Gist options
  • Save adept/3181299 to your computer and use it in GitHub Desktop.
Save adept/3181299 to your computer and use it in GitHub Desktop.
Bit parsing speed
module Main where
import Control.Applicative
import System.Environment
import Control.Monad
import qualified Data.ByteString.Lazy as BSL
import Data.Bits
import Data.Binary.Get
import Data.Binary.Bits.Get as Bits
import Criterion.Main
data Cnt = Cnt !Int deriving Show
readBitByBit content =
let l = BSL.length content
res = runGet (runBitGet (getAllBits (l*8))) content
in res
where
getAllBits 0 = return $ Cnt 0
getAllBits n = do
b <- getBool
let c = if b then 1 else 0
Cnt rest <- getAllBits (n-1)
return $ Cnt $ c+rest
readByteByByte content =
let l = BSL.length content
res = runGet (runBitGet (getAllBits l)) content
in res
where
getAllBits 0 = return $ Cnt 0
getAllBits n = do
b <- Bits.getWord8 8
let c = sum [1 |n<-[0..7], testBit b n]
Cnt rest <- getAllBits (n-1)
return $ Cnt $ c+rest
read8BitsAtOnce content = do
let l = BSL.length content
let res = runGet (runBitGet (getAllBits l)) content
return res
where
getAllBits 0 = return $ Cnt 0
getAllBits n = do
let blk = count <$> bool <*> bool <*> bool <*> bool <*> bool <*> bool <*> bool <*> bool
c <- block blk
Cnt rest <- getAllBits (n-1)
return $ Cnt $ c+rest
count a b c d e f g h = length $ filter (==True) [a,b,c,d,e,f,g,h]
main = do
let fname = "stockdb.hi" -- approx 32K
raw <- BSL.readFile fname
defaultMain [ bench "1 bit at a time" $ whnf readBitByBit raw
, bench "1 byte at a time + testBit" $ whnf readByteByByte raw
, bench "8 bits at a time" $ whnfIO (read8BitsAtOnce raw)
]
{-
warming up
estimating clock resolution...
mean is 8.378154 us (80001 iterations)
found 2250 outliers among 79999 samples (2.8%)
1172 (1.5%) high mild
1078 (1.3%) high severe
estimating cost of a clock call...
mean is 544.7900 ns (77 iterations)
found 10 outliers among 77 samples (13.0%)
2 (2.6%) high mild
8 (10.4%) high severe
benchmarking 1 bit at a time
collecting 100 samples, 1 iterations each, in estimated 88.67671 s
mean: 834.7386 ms, lb 833.0525 ms, ub 837.1857 ms, ci 0.950
std dev: 10.30825 ms, lb 7.862752 ms, ub 16.31547 ms, ci 0.950
benchmarking 1 byte at a time + testBit
collecting 100 samples, 1 iterations each, in estimated 5.750108 s
mean: 56.64881 ms, lb 56.38399 ms, ub 56.94305 ms, ci 0.950
std dev: 1.424958 ms, lb 1.187093 ms, ub 1.964934 ms, ci 0.950
found 2 outliers among 100 samples (2.0%)
1 (1.0%) high severe
variance introduced by outliers: 19.012%
variance is moderately inflated by outliers
benchmarking 8 bits at a time
collecting 100 samples, 1 iterations each, in estimated 7.785916 s
mean: 75.72581 ms, lb 75.44328 ms, ub 76.02788 ms, ci 0.950
std dev: 1.505365 ms, lb 1.364304 ms, ub 1.734008 ms, ci 0.950
variance introduced by outliers: 13.225%
variance is moderately inflated by outliers
-}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment